Portability | MPTCs, fundeps |
---|---|
Stability | provisional |
Maintainer | Edward Kmett <ekmett@gmail.com> |
Safe Haskell | None |
Monads for free
- class Monad m => MonadFree f m | m -> f where
- wrap :: f (m a) -> m a
- data Free f a
- retract :: Monad f => Free f a -> f a
- liftF :: (Functor f, MonadFree f m) => f a -> m a
- iter :: Functor f => (f a -> a) -> Free f a -> a
- iterM :: (Monad m, Functor f) => (f (m a) -> m a) -> Free f a -> m a
- hoistFree :: Functor g => (forall a. f a -> g a) -> Free f b -> Free g b
- _Pure :: forall f m a p. (Choice p, Applicative m) => p a (m a) -> p (Free f a) (m (Free f a))
- _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))
Documentation
class Monad m => MonadFree f m | m -> f whereSource
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
smashes the lists flat.
join
[[a]]
On the other hand, consider:
data Tree a = Bin (Tree a) (Tree a) | Tip a
instanceMonad
Tree wherereturn
= 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:
instanceMonadFree
Pair Tree wherewrap
(Pair l r) = Bin l r
Or we could choose to program with
instead of Free
PairTree
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
.
(Functor f, MonadFree f m) => MonadFree f (ListT m) | |
(Functor f, MonadFree f m) => MonadFree f (IdentityT m) | |
(Functor f, MonadFree f m) => MonadFree f (MaybeT m) | |
Functor f => MonadFree f (Free f) | |
Functor f => MonadFree f (Free f) | |
Functor f => MonadFree f (F f) | |
Monad m => MonadFree Identity (IterT m) | |
(Functor f, MonadFree f m, Error e) => MonadFree f (ErrorT e m) | |
(Functor f, MonadFree f m, Monoid w) => MonadFree f (WriterT w m) | |
(Functor f, MonadFree f m, Monoid w) => MonadFree f (WriterT w m) | |
(Functor f, MonadFree f m) => MonadFree f (ContT r m) | |
(Functor f, MonadFree f m) => MonadFree f (StateT s m) | |
(Functor f, MonadFree f m) => MonadFree f (StateT s m) | |
(Functor f, MonadFree f m) => MonadFree f (ReaderT e m) | |
(Functor f, Monad m) => MonadFree f (FreeT f m) | |
Functor f => MonadFree f (FT f m) | |
(Functor f, MonadFree f m, Monoid w) => MonadFree f (RWST r w s m) | |
(Functor f, MonadFree f m, Monoid w) => MonadFree f (RWST r w s m) |
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
.
Being Free
being left adjoint to U
means that there is an isomorphism between
in the category of monads and Free
f -> mf -> 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
to Free
fm
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
as many layers of Free
f af
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,
MonadTrans Free | This is not a true monad transformer. It is only a monad transformer "up to |
(Functor m, MonadError e m) => MonadError e (Free m) | |
(Functor m, MonadReader e m) => MonadReader e (Free m) | |
(Functor m, MonadState s m) => MonadState s (Free m) | |
(Functor m, MonadWriter e m) => MonadWriter e (Free m) | |
Functor f => MonadFree f (Free f) | |
Functor f => Monad (Free f) | |
Functor f => Functor (Free f) | |
Typeable1 f => Typeable1 (Free f) | |
Functor f => MonadFix (Free f) | |
(Functor v, MonadPlus v) => MonadPlus (Free v) | This violates the MonadPlus laws, handle with care. |
Functor f => Applicative (Free f) | |
Foldable f => Foldable (Free f) | |
Traversable f => Traversable (Free f) | |
Alternative v => Alternative (Free v) | This violates the Alternative laws, handle with care. |
(Functor m, MonadCont m) => MonadCont (Free m) | |
Traversable1 f => Traversable1 (Free f) | |
Foldable1 f => Foldable1 (Free f) | |
Functor f => Apply (Free f) | |
Functor f => Bind (Free f) | |
(Eq (f (Free f a)), Eq a) => Eq (Free f a) | |
(Typeable1 f, Typeable a, Data a, Data (f (Free f a))) => Data (Free f a) | |
(Ord (f (Free f a)), Ord a) => Ord (Free f a) | |
(Read (f (Free f a)), Read a) => Read (Free f a) | |
(Show (f (Free f a)), Show a) => Show (Free f a) |
liftF :: (Functor f, MonadFree f m) => f a -> m aSource
A version of lift that can be used with just a Functor for f.
iterM :: (Monad m, Functor f) => (f (m a) -> m a) -> Free f a -> m aSource
Like iter for monadic values.
hoistFree :: Functor g => (forall a. f a -> g a) -> Free f b -> Free g bSource
Lift a natural transformation from f
to g
into a natural transformation from
to FreeT
f
.
FreeT
g
_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 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))Source
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))