free-4.2/0000755000000000000000000000000012234641053010466 5ustar0000000000000000free-4.2/.ghci0000644000000000000000000000012512234641053011377 0ustar0000000000000000:set -isrc -idist/build/autogen -optP-include -optPdist/build/autogen/cabal_macros.h free-4.2/.gitignore0000644000000000000000000000010412234641053012451 0ustar0000000000000000dist docs wiki TAGS tags wip .DS_Store .*.swp .*.swo *.o *.hi *~ *# free-4.2/.travis.yml0000644000000000000000000000033112234641053012574 0ustar0000000000000000language: haskell notifications: irc: channels: - "irc.freenode.org#haskell-lens" skip_join: true template: - "\x0313free\x03/\x0306%{branch}\x03 \x0314%{commit}\x03 %{build_url} %{message}" free-4.2/.vim.custom0000644000000000000000000000137712234641053012603 0ustar0000000000000000" Add the following to your .vimrc to automatically load this on startup " if filereadable(".vim.custom") " so .vim.custom " endif function StripTrailingWhitespace() let myline=line(".") let mycolumn = col(".") silent %s/ *$// call cursor(myline, mycolumn) endfunction " enable syntax highlighting syntax on " search for the tags file anywhere between here and / set tags=TAGS;/ " highlight tabs and trailing spaces set listchars=tab:‗‗,trail:‗ set list " f2 runs hasktags map :exec ":!hasktags -x -c --ignore src" " strip trailing whitespace before saving " au BufWritePre *.hs,*.markdown silent! cal StripTrailingWhitespace() " rebuild hasktags after saving au BufWritePost *.hs silent! :exec ":!hasktags -x -c --ignore src" free-4.2/CHANGELOG.markdown0000644000000000000000000000142012234641053013516 0ustar00000000000000004.2 ----- * Added `Control.Monad.Trans.Iter` and `Control.Comonad.Trans.Coiter`. 4.1.1 ----- * Added a default signature to `wrap`, based on a construction by @fizruk. 4.0 --- * Updated to work with `semigroupoids` and `comonad` 4.0 * `instance ComonadCofree Maybe NonEmpty` * `instance ComonadCofree (Const b) ((,) b)` 3.4.2 ----- * Generalized `liftF`. * Added `iterM` 3.4.1 ----- * Added support for GHC 7.7's polykinded `Typeable` 3.4 --- * Added instance `MonadFree f (ContT r m)` 3.3.1 ----- * Refactored build system * Removed upper bounds on my own intra-package dependencies 3.3 --- * Added `Control.Alternative.Free` and `Control.MonadPlus.Free` 3.2 --- * Added `Control.Free.Applicative` * Moved `Control.Monad.Free.Church` from `kan-extensions` into this package. free-4.2/free.cabal0000644000000000000000000000431312234641053012374 0ustar0000000000000000name: free category: Control, Monads version: 4.2 license: BSD3 cabal-version: >= 1.10 license-file: LICENSE author: Edward A. Kmett maintainer: Edward A. Kmett stability: provisional homepage: http://github.com/ekmett/free/ bug-reports: http://github.com/ekmett/free/issues copyright: Copyright (C) 2008-2012 Edward A. Kmett synopsis: Monads for free description: Free monads are useful for many tree-like structures and domain specific languages. . A 'Monad' @n@ is a free 'Monad' for @f@ if every 'Monad' homomorphism from @n@ to another monad @m@ is equivalent to a natural transformation from @f@ to @m@. . Cofree comonads provide convenient ways to talk about branching streams and rose-trees, and can be used to annotate syntax trees. . A 'Comonad' @v@ is a cofree 'Comonad' for @f@ if every 'Comonad' homomorphism another comonad @w@ to @v@ is equivalent to a natural transformation from @w@ to @f@. build-type: Simple extra-source-files: .ghci .gitignore .travis.yml .vim.custom README.markdown CHANGELOG.markdown source-repository head type: git location: git://github.com/ekmett/free.git library hs-source-dirs: src default-language: Haskell2010 default-extensions: CPP other-extensions: MultiParamTypeClasses FunctionalDependencies FlexibleInstances UndecidableInstances Rank2Types GADTs build-depends: base == 4.*, bifunctors == 4.*, comonad == 4.*, distributive >= 0.2.1, mtl >= 2.0.1.0 && < 2.2, profunctors == 4.*, semigroupoids == 4.*, semigroups >= 0.8.3.1 && < 1, transformers >= 0.2.0 && < 0.4 if impl(ghc) cpp-options: -DGHC_TYPEABLE exposed-modules: Control.Applicative.Free Control.Alternative.Free Control.Comonad.Cofree Control.Comonad.Cofree.Class Control.Comonad.Trans.Cofree Control.Comonad.Trans.Coiter Control.Monad.Free Control.Monad.Free.Church Control.Monad.Free.Class Control.Monad.Trans.Free Control.Monad.Trans.Iter Control.MonadPlus.Free ghc-options: -Wall free-4.2/LICENSE0000644000000000000000000000266012234641053011477 0ustar0000000000000000Copyright 2008-2012 Edward Kmett All rights reserved. Redistribution and use in source and binary forms, with or without modification, are permitted provided that the following conditions are met: 1. Redistributions of source code must retain the above copyright notice, this list of conditions and the following disclaimer. 2. Redistributions in binary form must reproduce the above copyright notice, this list of conditions and the following disclaimer in the documentation and/or other materials provided with the distribution. 3. Neither the name of the author nor the names of his contributors may be used to endorse or promote products derived from this software without specific prior written permission. THIS SOFTWARE IS PROVIDED BY THE AUTHORS ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE AUTHORS OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. free-4.2/README.markdown0000644000000000000000000000067712234641053013201 0ustar0000000000000000free ==== [![Build Status](https://secure.travis-ci.org/ekmett/free.png?branch=master)](http://travis-ci.org/ekmett/free) This package provides a common definitions for working with free monads, free applicatives, and cofree comonads in Haskell. Contact Information ------------------- Contributions and bug reports are welcome! Please feel free to contact me through github or on the #haskell IRC channel on irc.freenode.net. -Edward Kmett free-4.2/Setup.lhs0000644000000000000000000000016512234641053012300 0ustar0000000000000000#!/usr/bin/runhaskell > module Main (main) where > import Distribution.Simple > main :: IO () > main = defaultMain free-4.2/src/0000755000000000000000000000000012234641053011255 5ustar0000000000000000free-4.2/src/Control/0000755000000000000000000000000012234641053012675 5ustar0000000000000000free-4.2/src/Control/Alternative/0000755000000000000000000000000012234641053015153 5ustar0000000000000000free-4.2/src/Control/Alternative/Free.hs0000644000000000000000000000654212234641053016377 0ustar0000000000000000{-# LANGUAGE CPP #-} {-# LANGUAGE Rank2Types #-} {-# LANGUAGE GADTs #-} #if __GLASGOW_HASKELL__ >= 707 {-# LANGUAGE DeriveDataTypeable #-} #endif {-# OPTIONS_GHC -Wall #-} ----------------------------------------------------------------------------- -- | -- Module : Control.Alternative.Free -- Copyright : (C) 2012 Edward Kmett -- License : BSD-style (see the file LICENSE) -- -- Maintainer : Edward Kmett -- Stability : provisional -- Portability : GADTs, Rank2Types -- -- Left distributive 'Alternative' functors for free, based on a design -- by Stijn van Drongelen. ---------------------------------------------------------------------------- module Control.Alternative.Free ( Alt(..) , runAlt , liftAlt , hoistAlt ) where import Control.Applicative import Data.Functor.Apply import Data.Semigroup #ifdef GHC_TYPEABLE import Data.Typeable #endif -- | The free 'Alternative' for a 'Functor' @f@. data Alt f a where Pure :: a -> Alt f a Ap :: f a -> Alt f (a -> b) -> Alt f b Alt :: [Alt f a] -> Alt f a #if __GLASGOW_HASKELL__ >= 707 deriving (Typeable) #endif -- | Given a natural transformation from @f@ to @g@, this gives a canonical monoidal natural transformation from @'Alt' f@ to @g@. runAlt :: Alternative g => (forall x. f x -> g x) -> Alt f a -> g a runAlt _ (Pure x) = pure x runAlt u (Ap f x) = flip id <$> u f <*> runAlt u x runAlt u (Alt as) = foldr (\a r -> runAlt u a <|> r) empty as instance Functor (Alt f) where fmap f (Pure a) = Pure (f a) fmap f (Ap x y) = Ap x ((f .) <$> y) fmap f (Alt as) = Alt (fmap f <$> as) instance Apply (Alt f) where Pure f <.> y = fmap f y Ap x y <.> z = Ap x (flip <$> y <.> z) Alt as <.> z = Alt (map (<.> z) as) -- This assumes 'left distribution' instance Applicative (Alt f) where pure = Pure Pure f <*> y = fmap f y Ap x y <*> z = Ap x (flip <$> y <*> z) Alt as <*> z = Alt (map (<*> z) as) -- This assumes 'left distribution' instance Alternative (Alt f) where empty = Alt [] {-# INLINE empty #-} Alt [] <|> r = r l <|> Alt [] = l Alt as <|> Alt bs = Alt (as ++ bs) l <|> r = Alt [l, r] {-# INLINE (<|>) #-} instance Semigroup (Alt f a) where (<>) = (<|>) {-# INLINE (<>) #-} instance Monoid (Alt f a) where mempty = empty {-# INLINE mempty #-} mappend = (<|>) {-# INLINE mappend #-} mconcat as = fromList (as >>= toList) where toList (Alt xs) = xs toList x = [x] fromList [x] = x fromList xs = Alt xs {-# INLINE mconcat #-} -- | A version of 'lift' that can be used with just a 'Functor' for @f@. liftAlt :: f a -> Alt f a liftAlt x = Ap x (Pure id) {-# INLINE liftAlt #-} -- | Given a natural transformation from @f@ to @g@ this gives a monoidal natural transformation from @Alt f@ to @Alt g@. hoistAlt :: (forall a. f a -> g a) -> Alt f b -> Alt g b hoistAlt _ (Pure a) = Pure a hoistAlt f (Ap x y) = Ap (f x) (hoistAlt f y) hoistAlt f (Alt as) = Alt (map (hoistAlt f) as) #if defined(GHC_TYPEABLE) && __GLASGOW_HASKELL__ < 707 instance Typeable1 f => Typeable1 (Alt f) where typeOf1 t = mkTyConApp altTyCon [typeOf1 (f t)] where f :: Alt f a -> f a f = undefined altTyCon :: TyCon #if __GLASGOW_HASKELL__ < 704 altTyCon = mkTyCon "Control.Alternative.Free.Alt" #else altTyCon = mkTyCon3 "free" "Control.Alternative.Free" "Alt" #endif {-# NOINLINE altTyCon #-} #endif free-4.2/src/Control/Applicative/0000755000000000000000000000000012234641053015136 5ustar0000000000000000free-4.2/src/Control/Applicative/Free.hs0000644000000000000000000000471712234641053016364 0ustar0000000000000000{-# LANGUAGE CPP #-} {-# LANGUAGE Rank2Types #-} {-# LANGUAGE GADTs #-} #if __GLASGOW_HASKELL__ >= 707 {-# LANGUAGE DeriveDataTypeable #-} #endif {-# OPTIONS_GHC -Wall #-} ----------------------------------------------------------------------------- -- | -- Module : Control.Applicative.Free -- Copyright : (C) 2012 Edward Kmett -- License : BSD-style (see the file LICENSE) -- -- Maintainer : Edward Kmett -- Stability : provisional -- Portability : GADTs, Rank2Types -- -- 'Applicative' functors for free ---------------------------------------------------------------------------- module Control.Applicative.Free ( Ap(..) , runAp , liftAp , hoistAp , retractAp ) where import Control.Applicative import Data.Functor.Apply #ifdef GHC_TYPEABLE import Data.Typeable #endif -- | The free 'Applicative' for a 'Functor' @f@. data Ap f a where Pure :: a -> Ap f a Ap :: f a -> Ap f (a -> b) -> Ap f b #if __GLASGOW_HASKELL__ >= 707 deriving (Typeable) #endif -- | Given a natural transformation from @f@ to @g@, this gives a canonical monoidal natural transformation from @'Ap' f@ to @g@. runAp :: Applicative g => (forall x. f x -> g x) -> Ap f a -> g a runAp _ (Pure x) = pure x runAp u (Ap f x) = flip id <$> u f <*> runAp u x instance Functor (Ap f) where fmap f (Pure a) = Pure (f a) fmap f (Ap x y) = Ap x ((f .) <$> y) instance Apply (Ap f) where Pure f <.> y = fmap f y Ap x y <.> z = Ap x (flip <$> y <.> z) instance Applicative (Ap f) where pure = Pure Pure f <*> y = fmap f y Ap x y <*> z = Ap x (flip <$> y <*> z) -- | A version of 'lift' that can be used with just a 'Functor' for @f@. liftAp :: f a -> Ap f a liftAp x = Ap x (Pure id) {-# INLINE liftAp #-} -- | Given a natural transformation from @f@ to @g@ this gives a monoidal natural transformation from @Ap f@ to @Ap g@. hoistAp :: (forall a. f a -> g a) -> Ap f b -> Ap g b hoistAp _ (Pure a) = Pure a hoistAp f (Ap x y) = Ap (f x) (hoistAp f y) retractAp :: Applicative f => Ap f a -> f a retractAp (Pure a) = pure a retractAp (Ap x y) = x <**> retractAp y #if defined(GHC_TYPEABLE) && __GLASGOW_HASKELL__ < 707 instance Typeable1 f => Typeable1 (Ap f) where typeOf1 t = mkTyConApp apTyCon [typeOf1 (f t)] where f :: Ap f a -> f a f = undefined apTyCon :: TyCon #if __GLASGOW_HASKELL__ < 704 apTyCon = mkTyCon "Control.Applicative.Free.Ap" #else apTyCon = mkTyCon3 "free" "Control.Applicative.Free" "Ap" #endif {-# NOINLINE apTyCon #-} #endif free-4.2/src/Control/Comonad/0000755000000000000000000000000012234641053014255 5ustar0000000000000000free-4.2/src/Control/Comonad/Cofree.hs0000644000000000000000000002221212234641053016013 0ustar0000000000000000{-# LANGUAGE CPP #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE UndecidableInstances #-} {-# LANGUAGE MultiParamTypeClasses #-} #if __GLASGOW_HASKELL__ >= 707 {-# LANGUAGE DeriveDataTypeable #-} #endif ----------------------------------------------------------------------------- -- | -- Module : Control.Comonad.Cofree -- Copyright : (C) 2008-2012 Edward Kmett -- License : BSD-style (see the file LICENSE) -- -- Maintainer : Edward Kmett -- Stability : provisional -- Portability : MPTCs, fundeps -- -- Cofree comonads -- ---------------------------------------------------------------------------- module Control.Comonad.Cofree ( Cofree(..) , ComonadCofree(..) , section , coiter , unfold -- * Lenses into cofree comonads , _extract , _unwrap , telescoped ) where import Control.Applicative import Control.Comonad import Control.Comonad.Trans.Class import Control.Comonad.Cofree.Class import Control.Comonad.Env.Class import Control.Comonad.Store.Class as Class import Control.Comonad.Traced.Class import Control.Category import Data.Functor.Bind import Data.Functor.Extend import Data.Distributive import Data.Foldable import Data.Semigroup import Data.Traversable import Data.Semigroup.Foldable import Data.Semigroup.Traversable import Prelude hiding (id,(.)) #ifdef GHC_TYPEABLE import Data.Data #endif infixr 5 :< -- | The 'Cofree' 'Comonad' of a functor @f@. -- -- /Formally/ -- -- A 'Comonad' @v@ is a cofree 'Comonad' for @f@ if every comonad homomorphism -- another comonad @w@ to @v@ is equivalent to a natural transformation -- from @w@ to @f@. -- -- A 'cofree' functor is right adjoint to a forgetful functor. -- -- Cofree is a functor from the category of functors to the category of comonads -- that is right adjoint to the forgetful functor from the category of comonads -- to the category of functors that forgets how to 'extract' and -- 'duplicate', leaving you with only a 'Functor'. -- -- In practice, cofree comonads are quite useful for annotating syntax trees, -- or talking about streams. -- -- A number of common comonads arise directly as cofree comonads. -- -- For instance, -- -- * @'Cofree' 'Maybe'@ forms the a comonad for a non-empty list. -- -- * @'Cofree' ('Const' b)@ is a product. -- -- * @'Cofree' 'Identity'@ forms an infinite stream. -- -- * @'Cofree' ((->) b)'@ describes a Moore machine with states labeled with values of type a, and transitions on edges of type b. -- data Cofree f a = a :< f (Cofree f a) #if __GLASGOW_HASKELL__ >= 707 deriving (Typeable) #endif -- | Use coiteration to generate a cofree comonad from a seed. -- -- @'coiter' f = 'unfold' ('id' 'Control.Arrow.&&&' f)@ coiter :: Functor f => (a -> f a) -> a -> Cofree f a coiter psi a = a :< (coiter psi <$> psi a) -- | Unfold a cofree comonad from a seed. unfold :: Functor f => (b -> (a, f b)) -> b -> Cofree f a unfold f c = case f c of (x, d) -> x :< fmap (unfold f) d instance Functor f => ComonadCofree f (Cofree f) where unwrap (_ :< as) = as {-# INLINE unwrap #-} instance Distributive f => Distributive (Cofree f) where distribute w = fmap extract w :< fmap distribute (collect unwrap w) instance Functor f => Functor (Cofree f) where fmap f (a :< as) = f a :< fmap (fmap f) as b <$ (_ :< as) = b :< fmap (b <$) as instance Functor f => Extend (Cofree f) where extended = extend {-# INLINE extended #-} duplicated = duplicate {-# INLINE duplicated #-} instance Functor f => Comonad (Cofree f) where extend f w = f w :< fmap (extend f) (unwrap w) duplicate w = w :< fmap duplicate (unwrap w) extract (a :< _) = a {-# INLINE extract #-} -- | This is not a true 'Comonad' transformer, but this instance is convenient. instance ComonadTrans Cofree where lower (_ :< as) = fmap extract as {-# INLINE lower #-} instance Alternative f => Monad (Cofree f) where return x = x :< empty {-# INLINE return #-} (a :< m) >>= k = case k a of b :< n -> b :< (n <|> fmap (>>= k) m) -- | -- -- @'lower' . 'section' = 'id'@ section :: Comonad f => f a -> Cofree f a section as = extract as :< extend section as instance Apply f => Apply (Cofree f) where (f :< fs) <.> (a :< as) = f a :< ((<.>) <$> fs <.> as) {-# INLINE (<.>) #-} (f :< fs) <. (_ :< as) = f :< ((<. ) <$> fs <.> as) {-# INLINE (<.) #-} (_ :< fs) .> (a :< as) = a :< (( .>) <$> fs <.> as) {-# INLINE (.>) #-} instance ComonadApply f => ComonadApply (Cofree f) where (f :< fs) <@> (a :< as) = f a :< ((<@>) <$> fs <@> as) {-# INLINE (<@>) #-} (f :< fs) <@ (_ :< as) = f :< ((<@ ) <$> fs <@> as) {-# INLINE (<@) #-} (_ :< fs) @> (a :< as) = a :< (( @>) <$> fs <@> as) {-# INLINE (@>) #-} instance Applicative f => Applicative (Cofree f) where pure a = as where as = a :< pure as (f :< fs) <*> (a :< as) = f a :< ((<*>) <$> fs <*> as) {-# INLINE (<*>) #-} (f :< fs) <* (_ :< as) = f :< ((<* ) <$> fs <*> as) {-# INLINE (<*) #-} (_ :< fs) *> (a :< as) = a :< (( *>) <$> fs <*> as) {-# INLINE (*>) #-} instance (Show (f (Cofree f a)), Show a) => Show (Cofree f a) where showsPrec d (a :< as) = showParen (d > 5) $ showsPrec 6 a . showString " :< " . showsPrec 5 as instance (Read (f (Cofree f a)), Read a) => Read (Cofree f a) where readsPrec d r = readParen (d > 5) (\r' -> [(u :< v,w) | (u, s) <- readsPrec 6 r', (":<", t) <- lex s, (v, w) <- readsPrec 5 t]) r instance (Eq (f (Cofree f a)), Eq a) => Eq (Cofree f a) where a :< as == b :< bs = a == b && as == bs instance (Ord (f (Cofree f a)), Ord a) => Ord (Cofree f a) where compare (a :< as) (b :< bs) = case compare a b of LT -> LT EQ -> compare as bs GT -> GT instance Foldable f => Foldable (Cofree f) where foldMap f = go where go (a :< as) = f a `mappend` foldMap go as {-# INLINE foldMap #-} instance Foldable1 f => Foldable1 (Cofree f) where foldMap1 f = go where go (a :< as) = f a <> foldMap1 go as {-# INLINE foldMap1 #-} instance Traversable f => Traversable (Cofree f) where traverse f = go where go (a :< as) = (:<) <$> f a <*> traverse go as {-# INLINE traverse #-} instance Traversable1 f => Traversable1 (Cofree f) where traverse1 f = go where go (a :< as) = (:<) <$> f a <.> traverse1 go as {-# INLINE traverse1 #-} #if defined(GHC_TYPEABLE) && __GLASGOW_HASKELL__ < 707 instance (Typeable1 f) => Typeable1 (Cofree f) where typeOf1 dfa = mkTyConApp cofreeTyCon [typeOf1 (f dfa)] where f :: Cofree f a -> f a f = undefined instance (Typeable1 f, Typeable a) => Typeable (Cofree f a) where typeOf = typeOfDefault cofreeTyCon :: TyCon #if __GLASGOW_HASKELL__ < 704 cofreeTyCon = mkTyCon "Control.Comonad.Cofree.Cofree" #else cofreeTyCon = mkTyCon3 "free" "Control.Comonad.Cofree" "Cofree" #endif {-# NOINLINE cofreeTyCon #-} instance ( Typeable1 f , Data (f (Cofree f a)) , Data a ) => Data (Cofree f a) where gfoldl f z (a :< as) = z (:<) `f` a `f` as toConstr _ = cofreeConstr gunfold k z c = case constrIndex c of 1 -> k (k (z (:<))) _ -> error "gunfold" dataTypeOf _ = cofreeDataType dataCast1 f = gcast1 f cofreeConstr :: Constr cofreeConstr = mkConstr cofreeDataType ":<" [] Infix {-# NOINLINE cofreeConstr #-} cofreeDataType :: DataType cofreeDataType = mkDataType "Control.Comonad.Cofree.Cofree" [cofreeConstr] {-# NOINLINE cofreeDataType #-} #endif instance ComonadEnv e w => ComonadEnv e (Cofree w) where ask = ask . lower {-# INLINE ask #-} instance ComonadStore s w => ComonadStore s (Cofree w) where pos (_ :< as) = Class.pos as {-# INLINE pos #-} peek s (_ :< as) = extract (Class.peek s as) {-# INLINE peek #-} instance ComonadTraced m w => ComonadTraced m (Cofree w) where trace m = trace m . lower {-# INLINE trace #-} -- | This is a lens that can be used to read or write from the target of 'extract'. -- -- Using (^.) from the @lens@ package: -- -- @foo ^. '_extract' == 'extract' foo@ -- -- For more on lenses see the @lens@ package on hackage -- -- @'_extract' :: Lens' ('Cofree' g a) a@ _extract :: Functor f => (a -> f a) -> Cofree g a -> f (Cofree g a) _extract f (a :< as) = (:< as) <$> f a {-# INLINE _extract #-} -- | This is a lens that can be used to read or write to the tails of a 'Cofree' 'Comonad'. -- -- Using (^.) from the @lens@ package: -- -- @foo ^. '_unwrap' == 'unwrap' foo@ -- -- For more on lenses see the @lens@ package on hackage -- -- @'_unwrap' :: Lens' ('Cofree' g a) (g ('Cofree' g a))@ _unwrap :: Functor f => (g (Cofree g a) -> f (g (Cofree g a))) -> Cofree g a -> f (Cofree g a) _unwrap f (a :< as) = (a :<) <$> f as {-# INLINE _unwrap #-} -- | Construct a @Lens@ into a @'Cofree' f@ given a list of lenses into the base functor. -- -- For more on lenses see the 'lens' package on hackage. -- -- @telescoped :: 'Functor' g => [Lens' ('Cofree' g a) (g ('Cofree' g a))] -> Lens' ('Cofree' g a) a@ telescoped :: (Functor f, Functor g) => [(Cofree g a -> f (Cofree g a)) -> g (Cofree g a) -> f (g (Cofree g a))] -> (a -> f a) -> Cofree g a -> f (Cofree g a) telescoped = Prelude.foldr (\l r -> _unwrap . l . r) _extract {-# INLINE telescoped #-} free-4.2/src/Control/Comonad/Cofree/0000755000000000000000000000000012234641053015460 5ustar0000000000000000free-4.2/src/Control/Comonad/Cofree/Class.hs0000644000000000000000000000330212234641053017057 0ustar0000000000000000{-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE FunctionalDependencies #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE UndecidableInstances #-} ----------------------------------------------------------------------------- -- | -- Module : Control.Comonad.Cofree.Class -- Copyright : (C) 2008-2011 Edward Kmett -- License : BSD-style (see the file LICENSE) -- -- Maintainer : Edward Kmett -- Stability : experimental -- Portability : fundeps, MPTCs ---------------------------------------------------------------------------- module Control.Comonad.Cofree.Class ( ComonadCofree(..) ) where import Control.Applicative import Control.Comonad import Control.Comonad.Trans.Env import Control.Comonad.Trans.Store import Control.Comonad.Trans.Traced import Control.Comonad.Trans.Identity import Data.List.NonEmpty import Data.Semigroup -- | Allows you to peel a layer off a cofree comonad. class (Functor f, Comonad w) => ComonadCofree f w | w -> f where -- | Remove a layer. unwrap :: w a -> f (w a) instance ComonadCofree Maybe NonEmpty where unwrap (_ :| []) = Nothing unwrap (_ :| (a : as)) = Just (a :| as) instance ComonadCofree (Const b) ((,) b) where unwrap = Const . fst instance ComonadCofree f w => ComonadCofree f (IdentityT w) where unwrap = fmap IdentityT . unwrap . runIdentityT instance ComonadCofree f w => ComonadCofree f (EnvT e w) where unwrap (EnvT e wa) = EnvT e <$> unwrap wa instance ComonadCofree f w => ComonadCofree f (StoreT s w) where unwrap (StoreT wsa s) = flip StoreT s <$> unwrap wsa instance (ComonadCofree f w, Semigroup m, Monoid m) => ComonadCofree f (TracedT m w) where unwrap (TracedT wma) = TracedT <$> unwrap wma free-4.2/src/Control/Comonad/Trans/0000755000000000000000000000000012234641053015344 5ustar0000000000000000free-4.2/src/Control/Comonad/Trans/Cofree.hs0000644000000000000000000001416412234641053017111 0ustar0000000000000000{-# LANGUAGE CPP #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE UndecidableInstances #-} {-# LANGUAGE MultiParamTypeClasses #-} #if __GLASGOW_HASKELL__ >= 707 {-# LANGUAGE DeriveDataTypeable #-} #endif ----------------------------------------------------------------------------- -- | -- Module : Control.Comonad.Trans.Cofree -- Copyright : (C) 2008-2012 Edward Kmett -- License : BSD-style (see the file LICENSE) -- -- Maintainer : Edward Kmett -- Stability : provisional -- Portability : MPTCs, fundeps -- -- The cofree comonad transformer ---------------------------------------------------------------------------- module Control.Comonad.Trans.Cofree ( CofreeT(..) , CofreeF(..) , ComonadCofree(..) , headF , tailF , coiterT ) where import Control.Applicative import Control.Comonad import Control.Comonad.Trans.Class import Control.Comonad.Cofree.Class import Control.Category import Data.Bifunctor import Data.Bifoldable import Data.Bitraversable import Data.Foldable import Data.Semigroup import Data.Traversable import Prelude hiding (id,(.)) #if defined(GHC_TYPEABLE) || __GLASGOW_HASKELL__ >= 707 import Data.Data #endif infixr 5 :< -- | This is the base functor of the cofree comonad transformer. data CofreeF f a b = a :< f b deriving (Eq,Ord,Show,Read #if __GLASGOW_HASKELL__ >= 707 ,Typeable #endif ) -- | Extract the head of the base functor headF :: CofreeF f a b -> a headF (a :< _) = a -- | Extract the tails of the base functor tailF :: CofreeF f a b -> f b tailF (_ :< as) = as instance Functor f => Functor (CofreeF f a) where fmap f (a :< as) = a :< fmap f as instance Foldable f => Foldable (CofreeF f a) where foldMap f (_ :< as) = foldMap f as instance Traversable f => Traversable (CofreeF f a) where traverse f (a :< as) = (a :<) <$> traverse f as instance Functor f => Bifunctor (CofreeF f) where bimap f g (a :< as) = f a :< fmap g as instance Foldable f => Bifoldable (CofreeF f) where bifoldMap f g (a :< as) = f a `mappend` foldMap g as instance Traversable f => Bitraversable (CofreeF f) where bitraverse f g (a :< as) = (:<) <$> f a <*> traverse g as -- | This is a cofree comonad of some functor @f@, with a comonad @w@ threaded through it at each level. newtype CofreeT f w a = CofreeT { runCofreeT :: w (CofreeF f a (CofreeT f w a)) } instance (Functor f, Functor w) => Functor (CofreeT f w) where fmap f = CofreeT . fmap (bimap f (fmap f)) . runCofreeT instance (Functor f, Comonad w) => Comonad (CofreeT f w) where extract = headF . extract . runCofreeT extend f = CofreeT . extend (\w -> f (CofreeT w) :< (extend f <$> tailF (extract w))) . runCofreeT instance (Foldable f, Foldable w) => Foldable (CofreeT f w) where foldMap f = foldMap (bifoldMap f (foldMap f)) . runCofreeT instance (Traversable f, Traversable w) => Traversable (CofreeT f w) where traverse f = fmap CofreeT . traverse (bitraverse f (traverse f)) . runCofreeT instance Functor f => ComonadTrans (CofreeT f) where lower = fmap headF . runCofreeT instance (Functor f, Comonad w) => ComonadCofree f (CofreeT f w) where unwrap = tailF . extract . runCofreeT instance Show (w (CofreeF f a (CofreeT f w a))) => Show (CofreeT f w a) where showsPrec d w = showParen (d > 10) $ showString "CofreeT " . showsPrec 11 w instance Read (w (CofreeF f a (CofreeT f w a))) => Read (CofreeT f w a) where readsPrec d = readParen (d > 10) $ \r -> [(CofreeT w, t) | ("CofreeT", s) <- lex r, (w, t) <- readsPrec 11 s] instance Eq (w (CofreeF f a (CofreeT f w a))) => Eq (CofreeT f w a) where CofreeT a == CofreeT b = a == b instance Ord (w (CofreeF f a (CofreeT f w a))) => Ord (CofreeT f w a) where compare (CofreeT a) (CofreeT b) = compare a b -- | Unfold a @CofreeT@ comonad transformer from a coalgebra and an initial comonad. coiterT :: (Functor f, Comonad w) => (w a -> f (w a)) -> w a -> CofreeT f w a coiterT psi = CofreeT . (extend $ \w -> extract w :< fmap (coiterT psi) (psi w)) #if defined(GHC_TYPEABLE) && __GLASGOW_HASKELL__ < 707 instance Typeable1 f => Typeable2 (CofreeF f) where typeOf2 t = mkTyConApp cofreeFTyCon [typeOf1 (f t)] where f :: CofreeF f a b -> f a f = undefined instance (Typeable1 f, Typeable1 w) => Typeable1 (CofreeT f w) where typeOf1 t = mkTyConApp cofreeTTyCon [typeOf1 (f t), typeOf1 (w t)] where f :: CofreeT f w a -> f a f = undefined w :: CofreeT f w a -> w a w = undefined cofreeFTyCon, cofreeTTyCon :: TyCon #if __GLASGOW_HASKELL__ < 704 cofreeTTyCon = mkTyCon "Control.Comonad.Trans.Cofree.CofreeT" cofreeFTyCon = mkTyCon "Control.Comonad.Trans.Cofree.CofreeF" #else cofreeTTyCon = mkTyCon3 "free" "Control.Comonad.Trans.Cofree" "CofreeT" cofreeFTyCon = mkTyCon3 "free" "Control.Comonad.Trans.Cofree" "CofreeF" #endif {-# NOINLINE cofreeTTyCon #-} {-# NOINLINE cofreeFTyCon #-} instance ( Typeable1 f, Typeable a, Typeable b , Data a, Data (f b), Data b ) => Data (CofreeF f a b) where gfoldl f z (a :< as) = z (:<) `f` a `f` as toConstr _ = cofreeFConstr gunfold k z c = case constrIndex c of 1 -> k (k (z (:<))) _ -> error "gunfold" dataTypeOf _ = cofreeFDataType dataCast1 f = gcast1 f instance ( Typeable1 f, Typeable1 w, Typeable a , Data (w (CofreeF f a (CofreeT f w a))) , Data a ) => Data (CofreeT f w a) where gfoldl f z (CofreeT w) = z CofreeT `f` w toConstr _ = cofreeTConstr gunfold k z c = case constrIndex c of 1 -> k (z CofreeT) _ -> error "gunfold" dataTypeOf _ = cofreeTDataType dataCast1 f = gcast1 f cofreeFConstr, cofreeTConstr :: Constr cofreeFConstr = mkConstr cofreeFDataType ":<" [] Infix cofreeTConstr = mkConstr cofreeTDataType "CofreeT" [] Prefix {-# NOINLINE cofreeFConstr #-} {-# NOINLINE cofreeTConstr #-} cofreeFDataType, cofreeTDataType :: DataType cofreeFDataType = mkDataType "Control.Comonad.Trans.Cofree.CofreeF" [cofreeFConstr] cofreeTDataType = mkDataType "Control.Comonad.Trans.Cofree.CofreeT" [cofreeTConstr] {-# NOINLINE cofreeFDataType #-} {-# NOINLINE cofreeTDataType #-} #endif -- lowerF :: (Functor f, Comonad w) => CofreeT f w a -> f a -- lowerF = fmap extract . unwrap free-4.2/src/Control/Comonad/Trans/Coiter.hs0000644000000000000000000000744412234641053017136 0ustar0000000000000000{-# LANGUAGE CPP #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE UndecidableInstances #-} {-# LANGUAGE MultiParamTypeClasses #-} #if __GLASGOW_HASKELL__ >= 707 {-# LANGUAGE DeriveDataTypeable #-} #endif ----------------------------------------------------------------------------- -- | -- Module : Control.Comonad.Trans.Coiter -- Copyright : (C) 2008-2012 Edward Kmett -- License : BSD-style (see the file LICENSE) -- -- Maintainer : Edward Kmett -- Stability : provisional -- Portability : MPTCs, fundeps -- -- The iterative comonad generated by a comonad ---------------------------------------------------------------------------- module Control.Comonad.Trans.Coiter ( CoiterT(..) , ComonadCofree(..) , coiterT ) where import Control.Arrow import Control.Comonad import Control.Comonad.Trans.Class import Control.Comonad.Cofree.Class import Control.Category import Data.Bifunctor import Data.Bifoldable import Data.Bitraversable import Data.Foldable import Data.Functor.Identity import Data.Traversable import Prelude hiding (id,(.)) #if defined(GHC_TYPEABLE) || __GLASGOW_HASKELL__ >= 707 import Data.Data #endif -- | This is the (co?)iterative comonad generated by a comonad newtype CoiterT w a = CoiterT { runCoiterT :: w (a, CoiterT w a) } instance Functor w => Functor (CoiterT w) where fmap f = CoiterT . fmap (bimap f (fmap f)) . runCoiterT instance Comonad w => Comonad (CoiterT w) where extract = fst . extract . runCoiterT extend f = CoiterT . extend (\w -> (f (CoiterT w), extend f $ snd $ extract w)) . runCoiterT instance Foldable w => Foldable (CoiterT w) where foldMap f = foldMap (bifoldMap f (foldMap f)) . runCoiterT instance Traversable w => Traversable (CoiterT w) where traverse f = fmap CoiterT . traverse (bitraverse f (traverse f)) . runCoiterT instance ComonadTrans CoiterT where lower = fmap fst . runCoiterT instance Comonad w => ComonadCofree Identity (CoiterT w) where unwrap = Identity . snd . extract . runCoiterT instance Show (w (a, CoiterT w a)) => Show (CoiterT w a) where showsPrec d w = showParen (d > 10) $ showString "CoiterT " . showsPrec 11 w instance Read (w (a, CoiterT w a)) => Read (CoiterT w a) where readsPrec d = readParen (d > 10) $ \r -> [(CoiterT w, t) | ("CoiterT", s) <- lex r, (w, t) <- readsPrec 11 s] instance Eq (w (a, CoiterT w a)) => Eq (CoiterT w a) where CoiterT a == CoiterT b = a == b instance Ord (w (a, CoiterT w a)) => Ord (CoiterT w a) where compare (CoiterT a) (CoiterT b) = compare a b -- | Unfold a @CoiterT@ comonad transformer from a cokleisli arrow and an initial comonadic seed. coiterT :: Comonad w => (w a -> a) -> w a -> CoiterT w a coiterT psi = CoiterT . extend (extract &&& coiterT psi . extend psi) #if defined(GHC_TYPEABLE) && __GLASGOW_HASKELL__ < 707 instance Typeable1 w => Typeable1 (CoiterT w) where typeOf1 t = mkTyConApp coiterTTyCon [typeOf1 (w t)] where w :: CoiterT w a -> w a w = undefined coiterTTyCon :: TyCon #if __GLASGOW_HASKELL__ < 704 coiterTTyCon = mkTyCon "Control.Comonad.Trans.Coiter.CoiterT" #else coiterTTyCon = mkTyCon3 "free" "Control.Comonad.Trans.Coiter" "CoiterT" #endif {-# NOINLINE coiterTTyCon #-} instance ( Typeable1 w, Typeable a , Data (w (a, CoiterT w a)) , Data a ) => Data (CoiterT w a) where gfoldl f z (CoiterT w) = z CoiterT `f` w toConstr _ = coiterTConstr gunfold k z c = case constrIndex c of 1 -> k (z CoiterT) _ -> error "gunfold" dataTypeOf _ = coiterTDataType dataCast1 f = gcast1 f coiterTConstr :: Constr coiterTConstr = mkConstr coiterTDataType "CoiterT" [] Prefix {-# NOINLINE coiterTConstr #-} coiterTDataType :: DataType coiterTDataType = mkDataType "Control.Comonad.Trans.Coiter.CoiterT" [coiterTConstr] {-# NOINLINE coiterTDataType #-} #endif free-4.2/src/Control/Monad/0000755000000000000000000000000012234641053013733 5ustar0000000000000000free-4.2/src/Control/Monad/Free.hs0000644000000000000000000002465712234641053015166 0ustar0000000000000000{-# LANGUAGE CPP #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE UndecidableInstances #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE Rank2Types #-} #if __GLASGOW_HASKELL__ >= 707 {-# LANGUAGE DeriveDataTypeable #-} #endif ----------------------------------------------------------------------------- -- | -- Module : Control.Monad.Free -- Copyright : (C) 2008-2012 Edward Kmett -- License : BSD-style (see the file LICENSE) -- -- Maintainer : Edward Kmett -- Stability : provisional -- Portability : MPTCs, fundeps -- -- Monads for free ---------------------------------------------------------------------------- module Control.Monad.Free ( MonadFree(..) , Free(..) , retract , liftF , iter , iterM , hoistFree , _Pure, _Free ) where import Control.Applicative import Control.Monad (liftM, MonadPlus(..)) import Control.Monad.Fix import Control.Monad.Trans.Class import Control.Monad.Free.Class import Control.Monad.Reader.Class import Control.Monad.Writer.Class import Control.Monad.State.Class import Control.Monad.Error.Class import Control.Monad.Cont.Class import Data.Functor.Bind import Data.Foldable import Data.Profunctor import Data.Traversable import Data.Semigroup.Foldable import Data.Semigroup.Traversable #ifdef GHC_TYPEABLE import Data.Data #endif -- | The 'Free' 'Monad' for a 'Functor' @f@. -- -- /Formally/ -- -- A 'Monad' @n@ is a free 'Monad' for @f@ if every monad homomorphism -- from @n@ to another monad @m@ is equivalent to a natural transformation -- from @f@ to @m@. -- -- /Why Free?/ -- -- Every \"free\" functor is left adjoint to some \"forgetful\" functor. -- -- If we define a forgetful functor @U@ from the category of monads to the category of functors -- that just forgets the 'Monad', leaving only the 'Functor'. i.e. -- -- @U (M,'return','Control.Monad.join') = M@ -- -- then 'Free' is the left adjoint to @U@. -- -- Being 'Free' being left adjoint to @U@ means that there is an isomorphism between -- -- @'Free' f -> m@ in the category of monads and @f -> U m@ in the category of functors. -- -- Morphisms in the category of monads are 'Monad' homomorphisms (natural transformations that respect 'return' and 'Control.Monad.join'). -- -- Morphisms in the category of functors are 'Functor' homomorphisms (natural transformations). -- -- Given this isomorphism, every monad homomorphism from @'Free' f@ to @m@ is equivalent to a natural transformation from @f@ to @m@ -- -- Showing that this isomorphism holds is left as an exercise. -- -- In practice, you can just view a @'Free' f a@ as many layers of @f@ wrapped around values of type @a@, where -- @('>>=')@ performs substitution and grafts new layers of @f@ in for each of the free variables. -- -- This can be very useful for modeling domain specific languages, trees, or other constructs. -- -- This instance of 'MonadFree' is fairly naive about the encoding. For more efficient free monad implementation see "Control.Monad.Free.Church", in particular note the 'Control.Monad.Free.Church.improve' combinator. -- You may also want to take a look at the @kan-extensions@ package (). -- -- A number of common monads arise as free monads, -- -- * Given @data Empty a@, @'Free' Empty@ is isomorphic to the 'Data.Functor.Identity' monad. -- -- * @'Free' 'Maybe'@ can be used to model a partiality monad where each layer represents running the computation for a while longer. data Free f a = Pure a | Free (f (Free f a)) #if __GLASGOW_HASKELL__ >= 707 deriving (Typeable) #endif instance (Eq (f (Free f a)), Eq a) => Eq (Free f a) where Pure a == Pure b = a == b Free fa == Free fb = fa == fb _ == _ = False instance (Ord (f (Free f a)), Ord a) => Ord (Free f a) where Pure a `compare` Pure b = a `compare` b Pure _ `compare` Free _ = LT Free _ `compare` Pure _ = GT Free fa `compare` Free fb = fa `compare` fb instance (Show (f (Free f a)), Show a) => Show (Free f a) where showsPrec d (Pure a) = showParen (d > 10) $ showString "Pure " . showsPrec 11 a showsPrec d (Free m) = showParen (d > 10) $ showString "Free " . showsPrec 11 m instance (Read (f (Free f a)), Read a) => Read (Free f a) where readsPrec d r = readParen (d > 10) (\r' -> [ (Pure m, t) | ("Pure", s) <- lex r' , (m, t) <- readsPrec 11 s]) r ++ readParen (d > 10) (\r' -> [ (Free m, t) | ("Free", s) <- lex r' , (m, t) <- readsPrec 11 s]) r instance Functor f => Functor (Free f) where fmap f = go where go (Pure a) = Pure (f a) go (Free fa) = Free (go <$> fa) {-# INLINE fmap #-} instance Functor f => Apply (Free f) where Pure a <.> Pure b = Pure (a b) Pure a <.> Free fb = Free $ fmap a <$> fb Free fa <.> b = Free $ (<.> b) <$> fa instance Functor f => Applicative (Free f) where pure = Pure {-# INLINE pure #-} Pure a <*> Pure b = Pure $ a b Pure a <*> Free mb = Free $ fmap a <$> mb Free ma <*> b = Free $ (<*> b) <$> ma instance Functor f => Bind (Free f) where Pure a >>- f = f a Free m >>- f = Free ((>>- f) <$> m) instance Functor f => Monad (Free f) where return = Pure {-# INLINE return #-} Pure a >>= f = f a Free m >>= f = Free ((>>= f) <$> m) instance Functor f => MonadFix (Free f) where mfix f = a where a = f (impure a); impure (Pure x) = x; impure (Free _) = error "mfix (Free f): Free" -- | This violates the Alternative laws, handle with care. instance Alternative v => Alternative (Free v) where empty = Free empty {-# INLINE empty #-} a <|> b = Free (pure a <|> pure b) {-# INLINE (<|>) #-} -- | This violates the MonadPlus laws, handle with care. instance (Functor v, MonadPlus v) => MonadPlus (Free v) where mzero = Free mzero {-# INLINE mzero #-} a `mplus` b = Free (return a `mplus` return b) {-# INLINE mplus #-} -- | This is not a true monad transformer. It is only a monad transformer \"up to 'retract'\". instance MonadTrans Free where lift = Free . liftM Pure {-# INLINE lift #-} instance Foldable f => Foldable (Free f) where foldMap f = go where go (Pure a) = f a go (Free fa) = foldMap go fa {-# INLINE foldMap #-} instance Foldable1 f => Foldable1 (Free f) where foldMap1 f = go where go (Pure a) = f a go (Free fa) = foldMap1 go fa {-# INLINE foldMap1 #-} instance Traversable f => Traversable (Free f) where traverse f = go where go (Pure a) = Pure <$> f a go (Free fa) = Free <$> traverse go fa {-# INLINE traverse #-} instance Traversable1 f => Traversable1 (Free f) where traverse1 f = go where go (Pure a) = Pure <$> f a go (Free fa) = Free <$> traverse1 go fa {-# INLINE traverse1 #-} instance (Functor m, MonadWriter e m) => MonadWriter e (Free m) where tell = lift . tell {-# INLINE tell #-} listen = lift . listen . retract {-# INLINE listen #-} pass = lift . pass . retract {-# INLINE pass #-} instance (Functor m, MonadReader e m) => MonadReader e (Free m) where ask = lift ask {-# INLINE ask #-} local f = lift . local f . retract {-# INLINE local #-} instance (Functor m, MonadState s m) => MonadState s (Free m) where get = lift get {-# INLINE get #-} put s = lift (put s) {-# INLINE put #-} instance (Functor m, MonadError e m) => MonadError e (Free m) where throwError = lift . throwError {-# INLINE throwError #-} catchError as f = lift (catchError (retract as) (retract . f)) {-# INLINE catchError #-} instance (Functor m, MonadCont m) => MonadCont (Free m) where callCC f = lift (callCC (retract . f . liftM lift)) {-# INLINE callCC #-} instance Functor f => MonadFree f (Free f) where wrap = Free {-# INLINE wrap #-} -- | -- 'retract' is the left inverse of 'lift' and 'liftF' -- -- @ -- 'retract' . 'lift' = 'id' -- 'retract' . 'liftF' = 'id' -- @ retract :: Monad f => Free f a -> f a retract (Pure a) = return a retract (Free as) = as >>= retract -- | Tear down a 'Free' 'Monad' using iteration. iter :: Functor f => (f a -> a) -> Free f a -> a iter _ (Pure a) = a iter phi (Free m) = phi (iter phi <$> m) -- | Like iter for monadic values. iterM :: (Monad m, Functor f) => (f (m a) -> m a) -> Free f a -> m a iterM _ (Pure x) = return x iterM phi (Free f) = phi $ fmap (iterM phi) f -- | Lift a natural transformation from @f@ to @g@ into a natural transformation from @'FreeT' f@ to @'FreeT' g@. hoistFree :: Functor g => (forall a. f a -> g a) -> Free f b -> Free g b hoistFree _ (Pure a) = Pure a hoistFree f (Free as) = Free (hoistFree f <$> f as) -- | This is @Prism' (Free f a) a@ in disguise -- -- >>> preview _Pure (Pure 3) -- Just 3 -- -- >>> review _Pure 3 :: Free Maybe Int -- Pure 3 _Pure :: forall f m a p. (Choice p, Applicative m) => p a (m a) -> p (Free f a) (m (Free f a)) _Pure = dimap impure (either pure (fmap Pure)) . right' where impure (Pure x) = Right x impure x = Left x {-# INLINE impure #-} {-# INLINE _Pure #-} -- | This is @Prism' (Free f a) (f (Free f a))@ in disguise -- -- >>> preview _Free (review _Free (Just (Pure 3))) -- Just (Just (Pure 3)) -- -- >>> review _Free (Just (Pure 3)) -- Free (Just (Pure 3)) _Free :: forall f m a p. (Choice p, Applicative m) => p (f (Free f a)) (m (f (Free f a))) -> p (Free f a) (m (Free f a)) _Free = dimap unfree (either pure (fmap Free)) . right' where unfree (Free x) = Right x unfree x = Left x {-# INLINE unfree #-} {-# INLINE _Free #-} #if defined(GHC_TYPEABLE) && __GLASGOW_HASKELL__ < 707 instance Typeable1 f => Typeable1 (Free f) where typeOf1 t = mkTyConApp freeTyCon [typeOf1 (f t)] where f :: Free f a -> f a f = undefined freeTyCon :: TyCon #if __GLASGOW_HASKELL__ < 704 freeTyCon = mkTyCon "Control.Monad.Free.Free" #else freeTyCon = mkTyCon3 "free" "Control.Monad.Free" "Free" #endif {-# NOINLINE freeTyCon #-} instance ( Typeable1 f, Typeable a , Data a, Data (f (Free f a)) ) => Data (Free f a) where gfoldl f z (Pure a) = z Pure `f` a gfoldl f z (Free as) = z Free `f` as toConstr Pure{} = pureConstr toConstr Free{} = freeConstr gunfold k z c = case constrIndex c of 1 -> k (z Pure) 2 -> k (z Free) _ -> error "gunfold" dataTypeOf _ = freeDataType dataCast1 f = gcast1 f pureConstr, freeConstr :: Constr pureConstr = mkConstr freeDataType "Pure" [] Prefix freeConstr = mkConstr freeDataType "Free" [] Prefix {-# NOINLINE pureConstr #-} {-# NOINLINE freeConstr #-} freeDataType :: DataType freeDataType = mkDataType "Control.Monad.Free.FreeF" [pureConstr, freeConstr] {-# NOINLINE freeDataType #-} #endif free-4.2/src/Control/Monad/Free/0000755000000000000000000000000012234641053014614 5ustar0000000000000000free-4.2/src/Control/Monad/Free/Church.hs0000644000000000000000000001011012234641053016355 0ustar0000000000000000{-# LANGUAGE Rank2Types #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE UndecidableInstances #-} {-# LANGUAGE MultiParamTypeClasses #-} ----------------------------------------------------------------------------- -- | -- Module : Control.Monad.Free.Church -- Copyright : (C) 2011-2012 Edward Kmett -- License : BSD-style (see the file LICENSE) -- -- Maintainer : Edward Kmett -- Stability : provisional -- Portability : non-portable (rank-2 polymorphism) -- -- \"Free Monads for Less\" -- -- This is based on the \"Free Monads for Less\" series of articles: -- -- -- ---------------------------------------------------------------------------- module Control.Monad.Free.Church ( F(..) , improve , fromF , iterM , toF , retract , MonadFree(..) , liftF ) where import Control.Applicative import Control.Monad as Monad import Control.Monad.Free hiding (retract, iterM) import Control.Monad.Reader.Class import Control.Monad.Writer.Class import Control.Monad.Cont.Class import Control.Monad.Trans.Class import Control.Monad.State.Class import Data.Functor.Bind -- | The Church-encoded free monad for a functor @f@. -- -- It is /asymptotically/ more efficient to use ('>>=') for 'F' than it is to ('>>=') with 'Free'. -- -- newtype F f a = F { runF :: forall r. (a -> r) -> (f r -> r) -> r } -- | Like iter for monadic values. iterM :: (Monad m, Functor f) => (f (m a) -> m a) -> F f a -> m a iterM phi xs = runF xs return phi instance Functor (F f) where fmap f (F g) = F (\kp -> g (kp . f)) instance Apply (F f) where (<.>) = (<*>) instance Applicative (F f) where pure a = F (\kp _ -> kp a) F f <*> F g = F (\kp kf -> f (\a -> g (\b -> kp (a b)) kf) kf) instance Alternative f => Alternative (F f) where empty = F (\_ kf -> kf empty) F f <|> F g = F (\kp kf -> kf (pure (f kp kf) <|> pure (g kp kf))) instance Bind (F f) where (>>-) = (>>=) instance Monad (F f) where return a = F (\kp _ -> kp a) F m >>= f = F (\kp kf -> m (\a -> runF (f a) kp kf) kf) instance MonadPlus f => MonadPlus (F f) where mzero = F (\_ kf -> kf mzero) F f `mplus` F g = F (\kp kf -> kf (return (f kp kf) `mplus` return (g kp kf))) instance MonadTrans F where lift f = F (\kp kf -> kf (liftM kp f)) instance Functor f => MonadFree f (F f) where wrap f = F (\kp kf -> kf (fmap (\ (F m) -> m kp kf) f)) instance MonadState s m => MonadState s (F m) where get = lift get put = lift . put instance MonadReader e m => MonadReader e (F m) where ask = lift ask local f = lift . local f . retract instance MonadWriter w m => MonadWriter w (F m) where tell = lift . tell pass = lift . pass . retract listen = lift . listen . retract instance MonadCont m => MonadCont (F m) where callCC f = lift $ callCC (retract . f . fmap lift) -- | -- 'retract' is the left inverse of 'lift' and 'liftF' -- -- @ -- 'retract' . 'lift' = 'id' -- 'retract' . 'liftF' = 'id' -- @ retract :: Monad m => F m a -> m a retract (F m) = m return Monad.join {-# INLINE retract #-} -- | Convert to another free monad representation. fromF :: MonadFree f m => F f a -> m a fromF (F m) = m return wrap {-# INLINE fromF #-} -- | Generate a Church-encoded free monad from a 'Free' monad. toF :: Functor f => Free f a -> F f a toF xs = F (\kp kf -> go kp kf xs) where go kp _ (Pure a) = kp a go kp kf (Free fma) = kf (fmap (go kp kf) fma) -- | Improve the asymptotic performance of code that builds a free monad with only binds and returns by using 'F' behind the scenes. -- -- This is based on the \"Free Monads for Less\" series of articles by Edward Kmett: -- -- -- -- -- and \"Asymptotic Improvement of Computations over Free Monads\" by Janis Voightländer: -- -- improve :: Functor f => (forall m. MonadFree f m => m a) -> Free f a improve m = fromF m {-# INLINE improve #-} free-4.2/src/Control/Monad/Free/Class.hs0000644000000000000000000001232212234641053016215 0ustar0000000000000000{-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE FunctionalDependencies #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE UndecidableInstances #-} #if defined(__GLASGOW_HASKELL__) && __GLASGOW_HASKELL__ >= 704 {-# LANGUAGE DefaultSignatures #-} {-# LANGUAGE TypeFamilies #-} #endif ----------------------------------------------------------------------------- -- | -- Module : Control.Monad.Free.Class -- Copyright : (C) 2008-2011 Edward Kmett -- License : BSD-style (see the file LICENSE) -- -- Maintainer : Edward Kmett -- Stability : experimental -- Portability : non-portable (fundeps, MPTCs) -- -- Monads for free. ---------------------------------------------------------------------------- module Control.Monad.Free.Class ( MonadFree(..) , liftF , wrapT ) where import Control.Applicative import Control.Monad import Control.Monad.Trans.Class import Control.Monad.Trans.Reader import qualified Control.Monad.Trans.State.Strict as Strict import qualified Control.Monad.Trans.State.Lazy as Lazy import qualified Control.Monad.Trans.Writer.Strict as Strict import qualified Control.Monad.Trans.Writer.Lazy as Lazy import qualified Control.Monad.Trans.RWS.Strict as Strict import qualified Control.Monad.Trans.RWS.Lazy as Lazy import Control.Monad.Trans.Cont import Control.Monad.Trans.Maybe import Control.Monad.Trans.List import Control.Monad.Trans.Error import Control.Monad.Trans.Identity import Data.Monoid -- | -- Monads provide substitution ('fmap') and renormalization ('Control.Monad.join'): -- -- @m '>>=' f = 'Control.Monad.join' ('fmap' f m)@ -- -- A free 'Monad' is one that does no work during the normalization step beyond simply grafting the two monadic values together. -- -- @[]@ is not a free 'Monad' (in this sense) because @'Control.Monad.join' [[a]]@ smashes the lists flat. -- -- On the other hand, consider: -- -- @ -- data Tree a = Bin (Tree a) (Tree a) | Tip a -- @ -- -- @ -- instance 'Monad' Tree where -- 'return' = Tip -- Tip a '>>=' f = f a -- Bin l r '>>=' f = Bin (l '>>=' f) (r '>>=' f) -- @ -- -- This 'Monad' is the free 'Monad' of Pair: -- -- @ -- data Pair a = Pair a a -- @ -- -- And we could make an instance of 'MonadFree' for it directly: -- -- @ -- instance 'MonadFree' Pair Tree where -- 'wrap' (Pair l r) = Bin l r -- @ -- -- Or we could choose to program with @'Control.Monad.Free.Free' Pair@ instead of 'Tree' -- and thereby avoid having to define our own 'Monad' instance. -- -- Moreover, "Control.Monad.Free.Church" provides a 'MonadFree' -- instance that can improve the /asymptotic/ complexity of code that -- constructs free monads by effectively reassociating the use of -- ('>>='). You may also want to take a look at the @kan-extensions@ -- package (). -- -- See 'Control.Monad.Free.Free' for a more formal definition of the free 'Monad' -- for a 'Functor'. class Monad m => MonadFree f m | m -> f where -- | Add a layer. -- -- @ -- wrap (fmap f x) ≡ wrap (fmap return x) >>= f -- @ wrap :: f (m a) -> m a #if defined(__GLASGOW_HASKELL__) && __GLASGOW_HASKELL__ >= 704 default wrap :: (m ~ t n, MonadTrans t, MonadFree f n, Functor f) => f (m a) -> m a wrap = join . lift . wrap . fmap return #endif instance (Functor f, MonadFree f m) => MonadFree f (ReaderT e m) where wrap fm = ReaderT $ \e -> wrap $ flip runReaderT e <$> fm instance (Functor f, MonadFree f m) => MonadFree f (Lazy.StateT s m) where wrap fm = Lazy.StateT $ \s -> wrap $ flip Lazy.runStateT s <$> fm instance (Functor f, MonadFree f m) => MonadFree f (Strict.StateT s m) where wrap fm = Strict.StateT $ \s -> wrap $ flip Strict.runStateT s <$> fm instance (Functor f, MonadFree f m) => MonadFree f (ContT r m) where wrap t = ContT $ \h -> wrap (fmap (\p -> runContT p h) t) instance (Functor f, MonadFree f m, Monoid w) => MonadFree f (Lazy.WriterT w m) where wrap = Lazy.WriterT . wrap . fmap Lazy.runWriterT instance (Functor f, MonadFree f m, Monoid w) => MonadFree f (Strict.WriterT w m) where wrap = Strict.WriterT . wrap . fmap Strict.runWriterT instance (Functor f, MonadFree f m, Monoid w) => MonadFree f (Strict.RWST r w s m) where wrap fm = Strict.RWST $ \r s -> wrap $ fmap (\m -> Strict.runRWST m r s) fm instance (Functor f, MonadFree f m, Monoid w) => MonadFree f (Lazy.RWST r w s m) where wrap fm = Lazy.RWST $ \r s -> wrap $ fmap (\m -> Lazy.runRWST m r s) fm instance (Functor f, MonadFree f m) => MonadFree f (MaybeT m) where wrap = MaybeT . wrap . fmap runMaybeT instance (Functor f, MonadFree f m) => MonadFree f (IdentityT m) where wrap = IdentityT . wrap . fmap runIdentityT instance (Functor f, MonadFree f m) => MonadFree f (ListT m) where wrap = ListT . wrap . fmap runListT instance (Functor f, MonadFree f m, Error e) => MonadFree f (ErrorT e m) where wrap = ErrorT . wrap . fmap runErrorT -- | A version of lift that can be used with just a Functor for f. liftF :: (Functor f, MonadFree f m) => f a -> m a liftF = wrap . fmap return -- | A version of wrap for monad transformers over a free monad. -- -- /Note:/ that this is the default implementation for 'wrap' for -- @MonadFree f (t m)@. wrapT :: (Functor f, MonadFree f m, MonadTrans t, Monad (t m)) => f (t m a) -> t m a wrapT = join . lift . liftF free-4.2/src/Control/Monad/Trans/0000755000000000000000000000000012234641053015022 5ustar0000000000000000free-4.2/src/Control/Monad/Trans/Free.hs0000644000000000000000000001665712234641053016256 0ustar0000000000000000{-# LANGUAGE CPP #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE UndecidableInstances #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE Rank2Types #-} #if __GLASGOW_HASKELL__ >= 707 {-# LANGUAGE DeriveDataTypeable #-} #endif ----------------------------------------------------------------------------- -- | -- Module : Control.Monad.Trans.Free -- Copyright : (C) 2008-2012 Edward Kmett -- License : BSD-style (see the file LICENSE) -- -- Maintainer : Edward Kmett -- Stability : provisional -- Portability : MPTCs, fundeps -- -- The free monad transformer -- ---------------------------------------------------------------------------- module Control.Monad.Trans.Free ( FreeF(..) , FreeT(..) , MonadFree(..) , liftF , iterT , hoistFreeT , transFreeT ) where import Control.Applicative import Control.Monad (liftM, MonadPlus(..), ap) import Control.Monad.Trans.Class import Control.Monad.Free.Class import Control.Monad.IO.Class import Data.Monoid import Data.Foldable import Data.Traversable import Data.Bifunctor import Data.Bifoldable import Data.Bitraversable #ifdef GHC_TYPEABLE import Data.Data #endif -- | The base functor for a free monad. data FreeF f a b = Pure a | Free (f b) deriving (Eq,Ord,Show,Read #if __GLASGOW_HASKELL__ >= 707 ,Typeable #endif ) instance Functor f => Functor (FreeF f a) where fmap _ (Pure a) = Pure a fmap f (Free as) = Free (fmap f as) instance Foldable f => Foldable (FreeF f a) where foldMap f (Free as) = foldMap f as foldMap _ _ = mempty instance Traversable f => Traversable (FreeF f a) where traverse _ (Pure a) = pure (Pure a) traverse f (Free as) = Free <$> traverse f as instance Functor f => Bifunctor (FreeF f) where bimap f _ (Pure a) = Pure (f a) bimap _ g (Free as) = Free (fmap g as) instance Foldable f => Bifoldable (FreeF f) where bifoldMap f _ (Pure a) = f a bifoldMap _ g (Free as) = foldMap g as instance Traversable f => Bitraversable (FreeF f) where bitraverse f _ (Pure a) = Pure <$> f a bitraverse _ g (Free as) = Free <$> traverse g as transFreeF :: (forall x. f x -> g x) -> FreeF f a b -> FreeF g a b transFreeF _ (Pure a) = Pure a transFreeF t (Free as) = Free (t as) {-# INLINE transFreeF #-} -- | The \"free monad transformer\" for a functor @f@. newtype FreeT f m a = FreeT { runFreeT :: m (FreeF f a (FreeT f m a)) } instance Eq (m (FreeF f a (FreeT f m a))) => Eq (FreeT f m a) where FreeT m == FreeT n = m == n instance Ord (m (FreeF f a (FreeT f m a))) => Ord (FreeT f m a) where compare (FreeT m) (FreeT n) = compare m n instance Show (m (FreeF f a (FreeT f m a))) => Show (FreeT f m a) where showsPrec d (FreeT m) = showParen (d > 10) $ showString "FreeT " . showsPrec 11 m instance Read (m (FreeF f a (FreeT f m a))) => Read (FreeT f m a) where readsPrec d = readParen (d > 10) $ \r -> [ (FreeT m,t) | ("FreeT",s) <- lex r, (m,t) <- readsPrec 11 s] instance (Functor f, Monad m) => Functor (FreeT f m) where fmap f (FreeT m) = FreeT (liftM f' m) where f' (Pure a) = Pure (f a) f' (Free as) = Free (fmap (fmap f) as) instance (Functor f, Monad m) => Applicative (FreeT f m) where pure a = FreeT (return (Pure a)) {-# INLINE pure #-} (<*>) = ap {-# INLINE (<*>) #-} instance (Functor f, Monad m) => Monad (FreeT f m) where return a = FreeT (return (Pure a)) {-# INLINE return #-} FreeT m >>= f = FreeT $ m >>= \v -> case v of Pure a -> runFreeT (f a) Free w -> return (Free (fmap (>>= f) w)) instance MonadTrans (FreeT f) where lift = FreeT . liftM Pure {-# INLINE lift #-} instance (Functor f, MonadIO m) => MonadIO (FreeT f m) where liftIO = lift . liftIO {-# INLINE liftIO #-} instance (Functor f, MonadPlus m) => Alternative (FreeT f m) where empty = FreeT mzero FreeT ma <|> FreeT mb = FreeT (mplus ma mb) {-# INLINE (<|>) #-} instance (Functor f, MonadPlus m) => MonadPlus (FreeT f m) where mzero = FreeT mzero {-# INLINE mzero #-} mplus (FreeT ma) (FreeT mb) = FreeT (mplus ma mb) {-# INLINE mplus #-} instance (Functor f, Monad m) => MonadFree f (FreeT f m) where wrap = FreeT . return . Free {-# INLINE wrap #-} -- | Tear down a free monad transformer using iteration. iterT :: (Functor f, Monad m) => (f (m a) -> m a) -> FreeT f m a -> m a iterT f (FreeT m) = do val <- m case fmap (iterT f) val of Pure x -> return x Free y -> f y instance (Foldable m, Foldable f) => Foldable (FreeT f m) where foldMap f (FreeT m) = foldMap (bifoldMap f (foldMap f)) m instance (Monad m, Traversable m, Traversable f) => Traversable (FreeT f m) where traverse f (FreeT m) = FreeT <$> traverse (bitraverse f (traverse f)) m -- | Lift a monad homomorphism from @m@ to @n@ into a monad homomorphism from @'FreeT' f m@ to @'FreeT' f n@ -- -- @'hoistFreeT' :: ('Monad' m, 'Functor' f) => (m ~> n) -> 'FreeT' f m ~> 'FreeT' f n@ hoistFreeT :: (Monad m, Functor f) => (forall a. m a -> n a) -> FreeT f m b -> FreeT f n b hoistFreeT mh = FreeT . mh . liftM (fmap (hoistFreeT mh)) . runFreeT -- | Lift a natural transformation from @f@ to @g@ into a monad homomorphism from @'FreeT' f m@ to @'FreeT' g n@ transFreeT :: (Monad m, Functor g) => (forall a. f a -> g a) -> FreeT f m b -> FreeT g m b transFreeT nt = FreeT . liftM (fmap (transFreeT nt) . transFreeF nt) . runFreeT #if defined(GHC_TYPEABLE) && __GLASGOW_HASKELL__ < 707 instance Typeable1 f => Typeable2 (FreeF f) where typeOf2 t = mkTyConApp freeFTyCon [typeOf1 (f t)] where f :: FreeF f a b -> f a f = undefined instance (Typeable1 f, Typeable1 w) => Typeable1 (FreeT f w) where typeOf1 t = mkTyConApp freeTTyCon [typeOf1 (f t), typeOf1 (w t)] where f :: FreeT f w a -> f a f = undefined w :: FreeT f w a -> w a w = undefined freeFTyCon, freeTTyCon :: TyCon #if __GLASGOW_HASKELL__ < 704 freeTTyCon = mkTyCon "Control.Monad.Trans.Free.FreeT" freeFTyCon = mkTyCon "Control.Monad.Trans.Free.FreeF" #else freeTTyCon = mkTyCon3 "free" "Control.Monad.Trans.Free" "FreeT" freeFTyCon = mkTyCon3 "free" "Control.Monad.Trans.Free" "FreeF" #endif {-# NOINLINE freeTTyCon #-} {-# NOINLINE freeFTyCon #-} instance ( Typeable1 f, Typeable a, Typeable b , Data a, Data (f b), Data b ) => Data (FreeF f a b) where gfoldl f z (Pure a) = z Pure `f` a gfoldl f z (Free as) = z Free `f` as toConstr Pure{} = pureConstr toConstr Free{} = freeConstr gunfold k z c = case constrIndex c of 1 -> k (z Pure) 2 -> k (z Free) _ -> error "gunfold" dataTypeOf _ = freeFDataType dataCast1 f = gcast1 f instance ( Typeable1 f, Typeable1 w, Typeable a , Data (w (FreeF f a (FreeT f w a))) , Data a ) => Data (FreeT f w a) where gfoldl f z (FreeT w) = z FreeT `f` w toConstr _ = freeTConstr gunfold k z c = case constrIndex c of 1 -> k (z FreeT) _ -> error "gunfold" dataTypeOf _ = freeTDataType dataCast1 f = gcast1 f pureConstr, freeConstr, freeTConstr :: Constr pureConstr = mkConstr freeFDataType "Pure" [] Prefix freeConstr = mkConstr freeFDataType "Free" [] Prefix freeTConstr = mkConstr freeTDataType "FreeT" [] Prefix {-# NOINLINE pureConstr #-} {-# NOINLINE freeConstr #-} {-# NOINLINE freeTConstr #-} freeFDataType, freeTDataType :: DataType freeFDataType = mkDataType "Control.Monad.Trans.Free.FreeF" [pureConstr, freeConstr] freeTDataType = mkDataType "Control.Monad.Trans.Free.FreeT" [freeTConstr] {-# NOINLINE freeFDataType #-} {-# NOINLINE freeTDataType #-} #endif free-4.2/src/Control/Monad/Trans/Iter.hs0000644000000000000000000001744212234641053016271 0ustar0000000000000000{-# LANGUAGE CPP #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE UndecidableInstances #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE StandaloneDeriving #-} {-# LANGUAGE Rank2Types #-} {-# LANGUAGE DeriveDataTypeable #-} #ifndef MIN_VERSION_MTL #define MIN_VERSION_MTL(x,y,z) 1 #endif ----------------------------------------------------------------------------- -- | -- Module : Control.Monad.Trans.Iter -- Copyright : (C) 2013 Edward Kmett -- License : BSD-style (see the file LICENSE) -- -- Maintainer : Edward Kmett -- Stability : provisional -- Portability : MPTCs, fundeps -- -- Based on -- -- Unlike 'Free', this is a true monad transformer. ---------------------------------------------------------------------------- module Control.Monad.Trans.Iter ( MonadFree(..) , IterF(..) , IterT(..) , delay , retract , iter , hoistIterT ) where import Control.Applicative import Control.Monad (ap, liftM, MonadPlus(..)) import Control.Monad.Fix import Control.Monad.Trans.Class import Control.Monad.Free.Class import Control.Monad.State.Class import Control.Monad.Reader.Class import Data.Bifoldable import Data.Bifunctor import Data.Bitraversable import Data.Functor.Bind import Data.Functor.Identity import Data.Foldable import Data.Monoid import Data.Traversable import Data.Semigroup.Foldable import Data.Semigroup.Traversable import Data.Typeable #ifdef GHC_TYPEABLE import Data.Data #endif data IterF a b = Pure a | Iter b deriving (Eq,Ord,Show,Read,Typeable) instance Functor (IterF a) where fmap _ (Pure a) = Pure a fmap f (Iter b) = Iter (f b) instance Foldable (IterF a) where foldMap f (Iter b) = f b foldMap _ _ = mempty instance Traversable (IterF a) where traverse _ (Pure a) = pure (Pure a) traverse f (Iter b) = Iter <$> f b instance Bifunctor IterF where bimap f _ (Pure a) = Pure (f a) bimap _ g (Iter b) = Iter (g b) instance Bifoldable IterF where bifoldMap f _ (Pure a) = f a bifoldMap _ g (Iter b) = g b instance Bitraversable IterF where bitraverse f _ (Pure a) = Pure <$> f a bitraverse _ g (Iter b) = Iter <$> g b iterF :: (a -> r) -> (b -> r) -> IterF a b -> r iterF f _ (Pure a) = f a iterF _ g (Iter b) = g b {-# INLINE iterF #-} -- | The monad supporting iteration based over a base monad @m@. -- -- @ -- 'IterT' ~ 'FreeT' 'Identity' -- @ data IterT m a = IterT { runIterT :: m (IterF a (IterT m a)) } #if __GLASGOW_HASKELL__ >= 707 deriving (Typeable) #endif instance Eq (m (IterF a (IterT m a))) => Eq (IterT m a) where IterT m == IterT n = m == n instance Ord (m (IterF a (IterT m a))) => Ord (IterT m a) where compare (IterT m) (IterT n) = compare m n instance Show (m (IterF a (IterT m a))) => Show (IterT m a) where showsPrec d (IterT m) = showParen (d > 10) $ showString "IterT " . showsPrec 11 m instance Read (m (IterF a (IterT m a))) => Read (IterT m a) where readsPrec d = readParen (d > 10) $ \r -> [ (IterT m,t) | ("IterT",s) <- lex r, (m,t) <- readsPrec 11 s] instance Monad m => Functor (IterT m) where fmap f = IterT . liftM (bimap f (fmap f)) . runIterT {-# INLINE fmap #-} instance Monad m => Applicative (IterT m) where pure = IterT . return . Pure {-# INLINE pure #-} (<*>) = ap {-# INLINE (<*>) #-} instance Monad m => Monad (IterT m) where return = IterT . return . Pure {-# INLINE return #-} IterT m >>= k = IterT $ m >>= iterF (runIterT . k) (return . Iter . (>>= k)) {-# INLINE (>>=) #-} fail = IterT . fail {-# INLINE fail #-} instance Monad m => Apply (IterT m) where (<.>) = ap {-# INLINE (<.>) #-} instance Monad m => Bind (IterT m) where (>>-) = (>>=) {-# INLINE (>>-) #-} instance MonadFix m => MonadFix (IterT m) where mfix f = IterT $ mfix (runIterT . f . unPure) where unPure (Pure x) = x unPure (Iter _) = error "mfix (IterT m): Iter" {-# INLINE mfix #-} instance MonadPlus m => Alternative (IterT m) where empty = IterT mzero {-# INLINE empty #-} IterT a <|> IterT b = IterT (mplus a b) {-# INLINE (<|>) #-} instance MonadPlus m => MonadPlus (IterT m) where mzero = IterT mzero {-# INLINE mzero #-} IterT a `mplus` IterT b = IterT (mplus a b) {-# INLINE mplus #-} -- | This is not a true monad transformer. It is only a monad transformer \"up to 'retract'\". instance MonadTrans IterT where lift = IterT . liftM Pure {-# INLINE lift #-} instance Foldable m => Foldable (IterT m) where foldMap f = foldMap (iterF f (foldMap f)) . runIterT {-# INLINE foldMap #-} instance Foldable1 m => Foldable1 (IterT m) where foldMap1 f = foldMap1 (iterF f (foldMap1 f)) . runIterT {-# INLINE foldMap1 #-} instance (Monad m, Traversable m) => Traversable (IterT m) where traverse f (IterT m) = IterT <$> traverse (bitraverse f (traverse f)) m {-# INLINE traverse #-} instance (Monad m, Traversable1 m) => Traversable1 (IterT m) where traverse1 f (IterT m) = IterT <$> traverse1 go m where go (Pure a) = Pure <$> f a go (Iter a) = Iter <$> traverse1 f a {-# INLINE traverse1 #-} {- instance MonadWriter e m => MonadWriter e (IterT m) where tell = lift . tell {-# INLINE tell #-} listen = lift . listen . retract {-# INLINE listen #-} pass = lift . pass . retract {-# INLINE pass #-} -} instance (Functor m, MonadReader e m) => MonadReader e (IterT m) where ask = lift ask {-# INLINE ask #-} local f = hoistIterT (local f) {-# INLINE local #-} instance (Functor m, MonadState s m) => MonadState s (IterT m) where get = lift get {-# INLINE get #-} put s = lift (put s) {-# INLINE put #-} #if MIN_VERSION_mtl(2,1,1) state f = lift (state f) {-# INLINE state #-} #endif {- instance (Functor m, MonadError e m) => MonadError e (Free m) where throwError = lift . throwError {-# INLINE throwError #-} catchError as f = lift (catchError (retract as) (retract . f)) {-# INLINE catchError #-} instance (Functor m, MonadCont m) => MonadCont (Free m) where callCC f = lift (callCC (retract . f . liftM lift)) {-# INLINE callCC #-} -} instance Monad m => MonadFree Identity (IterT m) where wrap = IterT . return . Iter . runIdentity {-# INLINE wrap #-} delay :: (Monad f, MonadFree f m) => m a -> m a delay = wrap . return {-# INLINE delay #-} -- | -- 'retract' is the left inverse of 'lift' -- -- @ -- 'retract' . 'lift' = 'id' -- @ retract :: Monad m => IterT m a -> m a retract m = runIterT m >>= iterF return retract -- | Tear down a 'Free' 'Monad' using iteration. iter :: Monad m => (m a -> a) -> IterT m a -> a iter phi (IterT m) = phi (iterF id (iter phi) `liftM` m) -- | Lift a monad homomorphism from @m@ to @n@ into a Monad homomorphism from @'IterT' m@ to @'IterT' n@. hoistIterT :: Monad n => (forall a. m a -> n a) -> IterT m b -> IterT n b hoistIterT f (IterT as) = IterT (fmap (hoistIterT f) `liftM` f as) #if defined(GHC_TYPEABLE) && __GLASGOW_HASKELL__ < 707 instance Typeable1 m => Typeable1 (IterT m) where typeOf1 t = mkTyConApp freeTyCon [typeOf1 (f t)] where f :: IterT m a -> m a f = undefined freeTyCon :: TyCon #if __GLASGOW_HASKELL__ < 704 freeTyCon = mkTyCon "Control.Monad.Iter.IterT" #else freeTyCon = mkTyCon3 "free" "Control.Monad.Iter" "IterT" #endif {-# NOINLINE freeTyCon #-} instance ( Typeable1 m, Typeable a , Data (m (IterF a (IterT m a))) , Data a ) => Data (IterT m a) where gfoldl f z (IterT as) = z IterT `f` as toConstr IterT{} = iterConstr gunfold k z c = case constrIndex c of 1 -> k (z IterT) _ -> error "gunfold" dataTypeOf _ = iterDataType dataCast1 f = gcast1 f iterConstr :: Constr iterConstr = mkConstr iterDataType "IterT" [] Prefix {-# NOINLINE iterConstr #-} iterDataType :: DataType iterDataType = mkDataType "Control.Monad.Iter.IterT" [iterConstr] {-# NOINLINE iterDataType #-} #endif free-4.2/src/Control/MonadPlus/0000755000000000000000000000000012234641053014577 5ustar0000000000000000free-4.2/src/Control/MonadPlus/Free.hs0000644000000000000000000002155312234641053016022 0ustar0000000000000000{-# LANGUAGE CPP #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE UndecidableInstances #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE Rank2Types #-} #if __GLASGOW_HASKELL__ >= 707 {-# LANGUAGE DeriveDataTypeable #-} #endif ----------------------------------------------------------------------------- -- | -- Module : Control.MonadPlus.Free -- Copyright : (C) 2008-2012 Edward Kmett -- License : BSD-style (see the file LICENSE) -- -- Maintainer : Edward Kmett -- Stability : provisional -- Portability : MPTCs, fundeps -- -- left-distributive MonadPlus for free. ---------------------------------------------------------------------------- module Control.MonadPlus.Free ( MonadFree(..) , Free(..) , retract , liftF , iter , iterM , hoistFree ) where import Control.Applicative import Control.Monad (liftM, MonadPlus(..)) import Control.Monad.Trans.Class import Control.Monad.Free.Class import Control.Monad.Reader.Class import Control.Monad.Writer.Class import Control.Monad.State.Class import Control.Monad.Error.Class import Control.Monad.Cont.Class import Data.Functor.Bind import Data.Foldable import Data.Traversable import Data.Semigroup #ifdef GHC_TYPEABLE import Data.Data #endif -- | The 'Free' 'MonadPlus' for a 'Functor' @f@. -- -- /Formally/ -- -- A 'MonadPlus' @n@ is a free 'MonadPlus' for @f@ if every monadplus homomorphism -- from @n@ to another MonadPlus @m@ is equivalent to a natural transformation -- from @f@ to @m@. -- -- We model this internally as if left-distribution holds. -- -- <> data Free f a = Pure a | Free (f (Free f a)) | Plus [Free f a] #if __GLASGOW_HASKELL__ >= 707 deriving (Typeable) #endif instance (Eq (f (Free f a)), Eq a) => Eq (Free f a) where Pure a == Pure b = a == b Free fa == Free fb = fa == fb Plus as == Plus bs = as == bs _ == _ = False instance (Ord (f (Free f a)), Ord a) => Ord (Free f a) where Pure a `compare` Pure b = a `compare` b Pure _ `compare` Free _ = LT Pure _ `compare` Plus _ = LT Free _ `compare` Pure _ = GT Free fa `compare` Free fb = fa `compare` fb Free _ `compare` Plus _ = LT Plus _ `compare` Pure _ = GT Plus _ `compare` Free _ = GT Plus as `compare` Plus bs = as `compare` bs instance (Show (f (Free f a)), Show a) => Show (Free f a) where showsPrec d (Pure a) = showParen (d > 10) $ showString "Pure " . showsPrec 11 a showsPrec d (Free m) = showParen (d > 10) $ showString "Free " . showsPrec 11 m showsPrec d (Plus as) = showParen (d > 10) $ showString "Plus " . showsPrec 11 as instance (Read (f (Free f a)), Read a) => Read (Free f a) where readsPrec d r = readParen (d > 10) (\r' -> [ (Pure m, t) | ("Pure", s) <- lex r' , (m, t) <- readsPrec 11 s]) r ++ readParen (d > 10) (\r' -> [ (Free m, t) | ("Free", s) <- lex r' , (m, t) <- readsPrec 11 s]) r ++ readParen (d > 10) (\r' -> [ (Plus as, t) | ("Plus", s) <- lex r' , (as, t) <- readsPrec 11 s]) r instance Functor f => Functor (Free f) where fmap f = go where go (Pure a) = Pure (f a) go (Free fa) = Free (go <$> fa) go (Plus as) = Plus (map go as) {-# INLINE fmap #-} instance Functor f => Apply (Free f) where Pure f <.> Pure b = Pure (f b) Pure f <.> Plus bs = Plus $ fmap f <$> bs Pure f <.> Free fb = Free $ fmap f <$> fb Free ff <.> b = Free $ (<.> b) <$> ff Plus fs <.> b = Plus $ (<.> b) <$> fs -- left distribution ??? instance Functor f => Applicative (Free f) where pure = Pure {-# INLINE pure #-} Pure f <*> Pure b = Pure (f b) Pure f <*> Free mb = Free $ fmap f <$> mb Pure f <*> Plus bs = Plus $ fmap f <$> bs Free ff <*> b = Free $ (<*> b) <$> ff Plus fs <*> b = Plus $ (<*> b) <$> fs -- left distribution instance Functor f => Bind (Free f) where Pure a >>- f = f a Free m >>- f = Free ((>>- f) <$> m) Plus m >>- f = Plus ((>>- f) <$> m) instance Functor f => Monad (Free f) where return = Pure {-# INLINE return #-} Pure a >>= f = f a Free m >>= f = Free ((>>= f) <$> m) Plus m >>= f = Plus (map (>>= f) m) -- left distribution law instance Functor f => Alternative (Free f) where empty = Plus [] {-# INLINE empty #-} Plus [] <|> r = r l <|> Plus [] = l Plus as <|> Plus bs = Plus (as ++ bs) a <|> b = Plus [a, b] {-# INLINE (<|>) #-} instance Functor f => MonadPlus (Free f) where mzero = empty {-# INLINE mzero #-} mplus = (<|>) {-# INLINE mplus #-} instance Functor f => Semigroup (Free f a) where (<>) = (<|>) {-# INLINE (<>) #-} instance Functor f => Monoid (Free f a) where mempty = empty {-# INLINE mempty #-} mappend = (<|>) {-# INLINE mappend #-} mconcat as = from (as >>= to) where to (Plus xs) = xs to x = [x] from [x] = x from xs = Plus xs {-# INLINE mconcat #-} -- | This is not a true monad transformer. It is only a monad transformer \"up to 'retract'\". instance MonadTrans Free where lift = Free . liftM Pure {-# INLINE lift #-} instance Foldable f => Foldable (Free f) where foldMap f = go where go (Pure a) = f a go (Free fa) = foldMap go fa go (Plus as) = foldMap go as {-# INLINE foldMap #-} instance Traversable f => Traversable (Free f) where traverse f = go where go (Pure a) = Pure <$> f a go (Free fa) = Free <$> traverse go fa go (Plus as) = Plus <$> traverse go as {-# INLINE traverse #-} instance (Functor m, MonadPlus m, MonadWriter e m) => MonadWriter e (Free m) where tell = lift . tell {-# INLINE tell #-} listen = lift . listen . retract {-# INLINE listen #-} pass = lift . pass . retract {-# INLINE pass #-} instance (Functor m, MonadPlus m, MonadReader e m) => MonadReader e (Free m) where ask = lift ask {-# INLINE ask #-} local f = lift . local f . retract {-# INLINE local #-} instance (Functor m, MonadState s m) => MonadState s (Free m) where get = lift get {-# INLINE get #-} put s = lift (put s) {-# INLINE put #-} instance (Functor m, MonadPlus m, MonadError e m) => MonadError e (Free m) where throwError = lift . throwError {-# INLINE throwError #-} catchError as f = lift (catchError (retract as) (retract . f)) {-# INLINE catchError #-} instance (Functor m, MonadPlus m, MonadCont m) => MonadCont (Free m) where callCC f = lift (callCC (retract . f . liftM lift)) {-# INLINE callCC #-} instance Functor f => MonadFree f (Free f) where wrap = Free {-# INLINE wrap #-} -- | -- 'retract' is the left inverse of 'lift' and 'liftF' -- -- @ -- 'retract' . 'lift' = 'id' -- 'retract' . 'liftF' = 'id' -- @ retract :: MonadPlus f => Free f a -> f a retract (Pure a) = return a retract (Free as) = as >>= retract retract (Plus as) = Prelude.foldr (mplus . retract) mzero as -- | Tear down a 'Free' 'Monad' using iteration. iter :: Functor f => (f a -> a) -> ([a] -> a) -> Free f a -> a iter phi psi = go where go (Pure a) = a go (Free as) = phi (go <$> as) go (Plus as) = psi (go <$> as) {-# INLINE iter #-} -- | Like iter for monadic values. iterM :: (Monad m, Functor f) => (f (m a) -> m a) -> ([m a] -> m a) -> Free f a -> m a iterM phi psi = go where go (Pure a) = return a go (Free as) = phi (go <$> as) go (Plus as) = psi (go <$> as) -- | Lift a natural transformation from @f@ to @g@ into a natural transformation from @'FreeT' f@ to @'FreeT' g@. hoistFree :: Functor g => (forall a. f a -> g a) -> Free f b -> Free g b hoistFree f = go where go (Pure a) = Pure a go (Free as) = Free (go <$> f as) go (Plus as) = Plus (map go as) #if defined(GHC_TYPEABLE) && __GLASGOW_HASKELL__ < 707 instance Typeable1 f => Typeable1 (Free f) where typeOf1 t = mkTyConApp freeTyCon [typeOf1 (f t)] where f :: Free f a -> f a f = undefined freeTyCon :: TyCon #if __GLASGOW_HASKELL__ < 704 freeTyCon = mkTyCon "Control.MonadPlus.Free.Free" #else freeTyCon = mkTyCon3 "free" "Control.MonadPlus.Free" "Free" #endif {-# NOINLINE freeTyCon #-} instance ( Typeable1 f, Typeable a , Data a, Data (f (Free f a)) ) => Data (Free f a) where gfoldl f z (Pure a) = z Pure `f` a gfoldl f z (Free as) = z Free `f` as gfoldl f z (Plus as) = z Plus `f` as toConstr Pure{} = pureConstr toConstr Free{} = freeConstr toConstr Plus{} = plusConstr gunfold k z c = case constrIndex c of 1 -> k (z Pure) 2 -> k (z Free) 3 -> k (z Plus) _ -> error "gunfold" dataTypeOf _ = freeDataType dataCast1 f = gcast1 f pureConstr, freeConstr, plusConstr :: Constr pureConstr = mkConstr freeDataType "Pure" [] Prefix freeConstr = mkConstr freeDataType "Free" [] Prefix plusConstr = mkConstr freeDataType "Plus" [] Prefix {-# NOINLINE pureConstr #-} {-# NOINLINE freeConstr #-} freeDataType :: DataType freeDataType = mkDataType "Control.MonadPlus.Free.Free" [pureConstr, freeConstr, plusConstr] {-# NOINLINE freeDataType #-} #endif