free-5.1.3: Monads for free

Copyright(C) 2008-2015 Edward Kmett
LicenseBSD-style (see the file LICENSE)
MaintainerEdward Kmett <ekmett@gmail.com>
Stabilityprovisional
PortabilityMPTCs, fundeps
Safe HaskellSafe
LanguageHaskell2010

Control.Monad.Free

Description

Monads for free

Synopsis

Documentation

class Monad m => MonadFree f m | m -> f where Source #

Monads provide substitution (fmap) and renormalization (join):

m >>= f = 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 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 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 (http://hackage.haskell.org/package/kan-extensions).

See Free for a more formal definition of the free Monad for a Functor.

Minimal complete definition

Nothing

Methods

wrap :: f (m a) -> m a Source #

Add a layer.

wrap (fmap f x) ≡ wrap (fmap return x) >>= f

wrap :: (m ~ t n, MonadTrans t, MonadFree f n, Functor f) => f (m a) -> m a Source #

Add a layer.

wrap (fmap f x) ≡ wrap (fmap return x) >>= f
Instances
(Functor f, MonadFree f m) => MonadFree f (ListT m) Source # 
Instance details

Defined in Control.Monad.Free.Class

Methods

wrap :: f (ListT m a) -> ListT m a Source #

(Functor f, MonadFree f m) => MonadFree f (MaybeT m) Source # 
Instance details

Defined in Control.Monad.Free.Class

Methods

wrap :: f (MaybeT m a) -> MaybeT m a Source #

Applicative f => MonadFree f (Free f) Source # 
Instance details

Defined in Control.Monad.Free.Ap

Methods

wrap :: f (Free f a) -> Free f a Source #

Functor f => MonadFree f (Free f) Source # 
Instance details

Defined in Control.Monad.Free

Methods

wrap :: f (Free f a) -> Free f a Source #

Functor f => MonadFree f (F f) Source # 
Instance details

Defined in Control.Monad.Free.Church

Methods

wrap :: f (F f a) -> F f a Source #

Monad m => MonadFree Identity (IterT m) Source # 
Instance details

Defined in Control.Monad.Trans.Iter

Methods

wrap :: Identity (IterT m a) -> IterT m a Source #

(Functor f, MonadFree f m) => MonadFree f (ExceptT e m) Source # 
Instance details

Defined in Control.Monad.Free.Class

Methods

wrap :: f (ExceptT e m a) -> ExceptT e m a Source #

(Functor f, MonadFree f m, Error e) => MonadFree f (ErrorT e m) Source # 
Instance details

Defined in Control.Monad.Free.Class

Methods

wrap :: f (ErrorT e m a) -> ErrorT e m a Source #

(Functor f, MonadFree f m) => MonadFree f (IdentityT m) Source # 
Instance details

Defined in Control.Monad.Free.Class

Methods

wrap :: f (IdentityT m a) -> IdentityT m a Source #

(Functor f, MonadFree f m, Monoid w) => MonadFree f (WriterT w m) Source # 
Instance details

Defined in Control.Monad.Free.Class

Methods

wrap :: f (WriterT w m a) -> WriterT w m a Source #

(Functor f, MonadFree f m, Monoid w) => MonadFree f (WriterT w m) Source # 
Instance details

Defined in Control.Monad.Free.Class

Methods

wrap :: f (WriterT w m a) -> WriterT w m a Source #

(Functor f, MonadFree f m) => MonadFree f (StateT s m) Source # 
Instance details

Defined in Control.Monad.Free.Class

Methods

wrap :: f (StateT s m a) -> StateT s m a Source #

(Functor f, MonadFree f m) => MonadFree f (StateT s m) Source # 
Instance details

Defined in Control.Monad.Free.Class

Methods

wrap :: f (StateT s m a) -> StateT s m a Source #

(Applicative f, Applicative m, Monad m) => MonadFree f (FreeT f m) Source # 
Instance details

Defined in Control.Monad.Trans.Free.Ap

Methods

wrap :: f (FreeT f m a) -> FreeT f m a Source #

(Functor f, Monad m) => MonadFree f (FreeT f m) Source # 
Instance details

Defined in Control.Monad.Trans.Free

Methods

wrap :: f (FreeT f m a) -> FreeT f m a Source #

MonadFree f (FT f m) Source # 
Instance details

Defined in Control.Monad.Trans.Free.Church

Methods

wrap :: f (FT f m a) -> FT f m a Source #

(Functor f, MonadFree f m) => MonadFree f (ContT r m) Source # 
Instance details

Defined in Control.Monad.Free.Class

Methods

wrap :: f (ContT r m a) -> ContT r m a Source #

(Functor f, MonadFree f m) => MonadFree f (ReaderT e m) Source # 
Instance details

Defined in Control.Monad.Free.Class

Methods

wrap :: f (ReaderT e m a) -> ReaderT e m a Source #

(Functor f, MonadFree f m, Monoid w) => MonadFree f (RWST r w s m) Source # 
Instance details

Defined in Control.Monad.Free.Class

Methods

wrap :: f (RWST r w s m a) -> RWST r w s m a Source #

(Functor f, MonadFree f m, Monoid w) => MonadFree f (RWST r w s m) Source # 
Instance details

Defined in Control.Monad.Free.Class

Methods

wrap :: f (RWST r w s m a) -> RWST r w s m a Source #

data Free f a Source #

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,join) = M

then Free is the left adjoint to U.

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 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 improve combinator. You may also want to take a look at the kan-extensions package (http://hackage.haskell.org/package/kan-extensions).

A number of common monads arise as free monads,

  • Given data Empty a, Free Empty is isomorphic to the Identity monad.
  • Free Maybe can be used to model a partiality monad where each layer represents running the computation for a while longer.

Constructors

Pure a 
Free (f (Free f a)) 
Instances
MonadTrans Free Source #

This is not a true monad transformer. It is only a monad transformer "up to retract".

Instance details

Defined in Control.Monad.Free

Methods

lift :: Monad m => m a -> Free m a #

(Functor m, MonadWriter e m) => MonadWriter e (Free m) Source # 
Instance details

Defined in Control.Monad.Free

Methods

writer :: (a, e) -> Free m a #

tell :: e -> Free m () #

listen :: Free m a -> Free m (a, e) #

pass :: Free m (a, e -> e) -> Free m a #

(Functor m, MonadState s m) => MonadState s (Free m) Source # 
Instance details

Defined in Control.Monad.Free

Methods

get :: Free m s #

put :: s -> Free m () #

state :: (s -> (a, s)) -> Free m a #

(Functor m, MonadReader e m) => MonadReader e (Free m) Source # 
Instance details

Defined in Control.Monad.Free

Methods

ask :: Free m e #

local :: (e -> e) -> Free m a -> Free m a #

reader :: (e -> a) -> Free m a #

(Functor m, MonadError e m) => MonadError e (Free m) Source # 
Instance details

Defined in Control.Monad.Free

Methods

throwError :: e -> Free m a #

catchError :: Free m a -> (e -> Free m a) -> Free m a #

Functor f => MonadFree f (Free f) Source # 
Instance details

Defined in Control.Monad.Free

Methods

wrap :: f (Free f a) -> Free f a Source #

Functor f => Monad (Free f) Source # 
Instance details

Defined in Control.Monad.Free

Methods

(>>=) :: Free f a -> (a -> Free f b) -> Free f b #

(>>) :: Free f a -> Free f b -> Free f b #

return :: a -> Free f a #

fail :: String -> Free f a #

Functor f => Functor (Free f) Source # 
Instance details

Defined in Control.Monad.Free

Methods

fmap :: (a -> b) -> Free f a -> Free f b #

(<$) :: a -> Free f b -> Free f a #

Functor f => MonadFix (Free f) Source # 
Instance details

Defined in Control.Monad.Free

Methods

mfix :: (a -> Free f a) -> Free f a #

Functor f => Applicative (Free f) Source # 
Instance details

Defined in Control.Monad.Free

Methods

pure :: a -> Free f a #

(<*>) :: Free f (a -> b) -> Free f a -> Free f b #

liftA2 :: (a -> b -> c) -> Free f a -> Free f b -> Free f c #

(*>) :: Free f a -> Free f b -> Free f b #

(<*) :: Free f a -> Free f b -> Free f a #

Foldable f => Foldable (Free f) Source # 
Instance details

Defined in Control.Monad.Free

Methods

fold :: Monoid m => Free f m -> m #

foldMap :: Monoid m => (a -> m) -> Free f a -> m #

foldr :: (a -> b -> b) -> b -> Free f a -> b #

foldr' :: (a -> b -> b) -> b -> Free f a -> b #

foldl :: (b -> a -> b) -> b -> Free f a -> b #

foldl' :: (b -> a -> b) -> b -> Free f a -> b #

foldr1 :: (a -> a -> a) -> Free f a -> a #

foldl1 :: (a -> a -> a) -> Free f a -> a #

toList :: Free f a -> [a] #

null :: Free f a -> Bool #

length :: Free f a -> Int #

elem :: Eq a => a -> Free f a -> Bool #

maximum :: Ord a => Free f a -> a #

minimum :: Ord a => Free f a -> a #

sum :: Num a => Free f a -> a #

product :: Num a => Free f a -> a #

Traversable f => Traversable (Free f) Source # 
Instance details

Defined in Control.Monad.Free

Methods

traverse :: Applicative f0 => (a -> f0 b) -> Free f a -> f0 (Free f b) #

sequenceA :: Applicative f0 => Free f (f0 a) -> f0 (Free f a) #

mapM :: Monad m => (a -> m b) -> Free f a -> m (Free f b) #

sequence :: Monad m => Free f (m a) -> m (Free f a) #

Eq1 f => Eq1 (Free f) Source # 
Instance details

Defined in Control.Monad.Free

Methods

liftEq :: (a -> b -> Bool) -> Free f a -> Free f b -> Bool #

Ord1 f => Ord1 (Free f) Source # 
Instance details

Defined in Control.Monad.Free

Methods

liftCompare :: (a -> b -> Ordering) -> Free f a -> Free f b -> Ordering #

Read1 f => Read1 (Free f) Source # 
Instance details

Defined in Control.Monad.Free

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Free f a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Free f a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Free f a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Free f a] #

Show1 f => Show1 (Free f) Source # 
Instance details

Defined in Control.Monad.Free

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Free f a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Free f a] -> ShowS #

Alternative v => Alternative (Free v) Source #

This violates the Alternative laws, handle with care.

Instance details

Defined in Control.Monad.Free

Methods

empty :: Free v a #

(<|>) :: Free v a -> Free v a -> Free v a #

some :: Free v a -> Free v [a] #

many :: Free v a -> Free v [a] #

(Functor v, MonadPlus v) => MonadPlus (Free v) Source #

This violates the MonadPlus laws, handle with care.

Instance details

Defined in Control.Monad.Free

Methods

mzero :: Free v a #

mplus :: Free v a -> Free v a -> Free v a #

(Functor m, MonadCont m) => MonadCont (Free m) Source # 
Instance details

Defined in Control.Monad.Free

Methods

callCC :: ((a -> Free m b) -> Free m a) -> Free m a #

Traversable1 f => Traversable1 (Free f) Source # 
Instance details

Defined in Control.Monad.Free

Methods

traverse1 :: Apply f0 => (a -> f0 b) -> Free f a -> f0 (Free f b) #

sequence1 :: Apply f0 => Free f (f0 b) -> f0 (Free f b) #

Foldable1 f => Foldable1 (Free f) Source # 
Instance details

Defined in Control.Monad.Free

Methods

fold1 :: Semigroup m => Free f m -> m #

foldMap1 :: Semigroup m => (a -> m) -> Free f a -> m #

toNonEmpty :: Free f a -> NonEmpty a #

Functor f => Apply (Free f) Source # 
Instance details

Defined in Control.Monad.Free

Methods

(<.>) :: Free f (a -> b) -> Free f a -> Free f b #

(.>) :: Free f a -> Free f b -> Free f b #

(<.) :: Free f a -> Free f b -> Free f a #

liftF2 :: (a -> b -> c) -> Free f a -> Free f b -> Free f c #

Functor f => Bind (Free f) Source # 
Instance details

Defined in Control.Monad.Free

Methods

(>>-) :: Free f a -> (a -> Free f b) -> Free f b #

join :: Free f (Free f a) -> Free f a #

Functor f => Generic1 (Free f :: Type -> Type) Source # 
Instance details

Defined in Control.Monad.Free

Associated Types

type Rep1 (Free f) :: k -> Type #

Methods

from1 :: Free f a -> Rep1 (Free f) a #

to1 :: Rep1 (Free f) a -> Free f a #

(Eq1 f, Eq a) => Eq (Free f a) Source # 
Instance details

Defined in Control.Monad.Free

Methods

(==) :: Free f a -> Free f a -> Bool #

(/=) :: Free f a -> Free f a -> Bool #

(Typeable f, Data (f (Free f a)), Data a) => Data (Free f a) Source # 
Instance details

Defined in Control.Monad.Free

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Free f a -> c (Free f a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Free f a) #

toConstr :: Free f a -> Constr #

dataTypeOf :: Free f a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Free f a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Free f a)) #

gmapT :: (forall b. Data b => b -> b) -> Free f a -> Free f a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Free f a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Free f a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Free f a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Free f a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Free f a -> m (Free f a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Free f a -> m (Free f a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Free f a -> m (Free f a) #

(Ord1 f, Ord a) => Ord (Free f a) Source # 
Instance details

Defined in Control.Monad.Free

Methods

compare :: Free f a -> Free f a -> Ordering #

(<) :: Free f a -> Free f a -> Bool #

(<=) :: Free f a -> Free f a -> Bool #

(>) :: Free f a -> Free f a -> Bool #

(>=) :: Free f a -> Free f a -> Bool #

max :: Free f a -> Free f a -> Free f a #

min :: Free f a -> Free f a -> Free f a #

(Read1 f, Read a) => Read (Free f a) Source # 
Instance details

Defined in Control.Monad.Free

Methods

readsPrec :: Int -> ReadS (Free f a) #

readList :: ReadS [Free f a] #

readPrec :: ReadPrec (Free f a) #

readListPrec :: ReadPrec [Free f a] #

(Show1 f, Show a) => Show (Free f a) Source # 
Instance details

Defined in Control.Monad.Free

Methods

showsPrec :: Int -> Free f a -> ShowS #

show :: Free f a -> String #

showList :: [Free f a] -> ShowS #

Generic (Free f a) Source # 
Instance details

Defined in Control.Monad.Free

Associated Types

type Rep (Free f a) :: Type -> Type #

Methods

from :: Free f a -> Rep (Free f a) x #

to :: Rep (Free f a) x -> Free f a #

type Rep1 (Free f :: Type -> Type) Source # 
Instance details

Defined in Control.Monad.Free

type Rep1 (Free f :: Type -> Type) = D1 (MetaData "Free" "Control.Monad.Free" "free-5.1.3-ImEEo1rc5VgJtcDOQOOyvw" False) (C1 (MetaCons "Pure" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1) :+: C1 (MetaCons "Free" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (f :.: Rec1 (Free f))))
type Rep (Free f a) Source # 
Instance details

Defined in Control.Monad.Free

type Rep (Free f a) = D1 (MetaData "Free" "Control.Monad.Free" "free-5.1.3-ImEEo1rc5VgJtcDOQOOyvw" False) (C1 (MetaCons "Pure" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)) :+: C1 (MetaCons "Free" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (f (Free f a)))))

retract :: Monad f => Free f a -> f a Source #

retract is the left inverse of lift and liftF

retract . lift = id
retract . liftF = id

liftF :: (Functor f, MonadFree f m) => f a -> m a Source #

A version of lift that can be used with just a Functor for f.

iter :: Functor f => (f a -> a) -> Free f a -> a Source #

Tear down a Free Monad using iteration.

iterA :: (Applicative p, Functor f) => (f (p a) -> p a) -> Free f a -> p a Source #

Like iter for applicative values.

iterM :: (Monad m, Functor f) => (f (m a) -> m a) -> Free f a -> m a Source #

Like iter for monadic values.

hoistFree :: Functor g => (forall a. f a -> g a) -> Free f b -> Free g b Source #

Lift a natural transformation from f to g into a natural transformation from Free f to Free g.

foldFree :: Monad m => (forall x. f x -> m x) -> Free f a -> m a Source #

The very definition of a free monad is that given a natural transformation you get a monad homomorphism.

toFreeT :: (Functor f, Monad m) => Free f a -> FreeT f m a Source #

Convert a Free monad from Control.Monad.Free to a FreeT monad from Control.Monad.Trans.Free.

cutoff :: Functor f => Integer -> Free f a -> Free f (Maybe a) Source #

Cuts off a tree of computations at a given depth. If the depth is 0 or less, no computation nor monadic effects will take place.

Some examples (n ≥ 0):

cutoff 0     _        == return Nothing
cutoff (n+1) . return == return . Just
cutoff (n+1) . lift   ==   lift . liftM Just
cutoff (n+1) . wrap   ==  wrap . fmap (cutoff n)

Calling 'retract . cutoff n' is always terminating, provided each of the steps in the iteration is terminating.

unfold :: Functor f => (b -> Either a (f b)) -> b -> Free f a Source #

Unfold a free monad from a seed.

unfoldM :: (Traversable f, Applicative m, Monad m) => (b -> m (Either a (f b))) -> b -> m (Free f a) Source #

Unfold a free monad from a seed, monadically.

_Pure :: forall f m a p. (Choice p, Applicative m) => p a (m a) -> p (Free f a) (m (Free f a)) Source #

This is Prism' (Free f a) a in disguise

>>> preview _Pure (Pure 3)
Just 3
>>> review _Pure 3 :: Free Maybe Int
Pure 3

_Free :: forall f g m a p. (Choice p, Applicative m) => p (f (Free f a)) (m (g (Free g a))) -> p (Free f a) (m (Free g a)) Source #

This is Prism (Free f a) (Free g a) (f (Free f a)) (g (Free g a)) in disguise

>>> preview _Free (review _Free (Just (Pure 3)))
Just (Just (Pure 3))
>>> review _Free (Just (Pure 3))
Free (Just (Pure 3))