| Portability | MPTCs, fundeps | 
|---|---|
| Stability | provisional | 
| Maintainer | Edward Kmett <ekmett@gmail.com> | 
| Safe Haskell | None | 
Control.MonadPlus.Free
Description
left-distributive MonadPlus for free.
- class Monad m => MonadFree f m | m -> f where- wrap :: f (m a) -> m a
 
- data Free f a
- retract :: MonadPlus f => Free f a -> f a
- liftF :: (Functor f, MonadFree f m) => f a -> m a
- iter :: Functor f => (f a -> a) -> ([a] -> a) -> Free f a -> a
- iterM :: (Monad m, Functor f) => (f (m a) -> m a) -> ([m a] -> m a) -> Free f a -> m a
- hoistFree :: Functor g => (forall a. f a -> g a) -> Free f b -> Free g b
Documentation
class Monad m => MonadFree f m | m -> f whereSource
Monads provide substitution (fmap) and renormalization (join):
m>>=f =join.fmapf 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]]
On the other hand, consider:
data Tree a = Bin (Tree a) (Tree a) | Tip a
instanceMonadTree 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:
instanceMonadFreePair Tree wherewrap(Pair l r) = Bin l r
Or we could choose to program with Free PairTree
 and thereby avoid having to define our own Monad instance.
Moreover, the kan-extensions package provides MonadFree instances that can
 improve the asymptotic complexity of code that constructors free monads by
 effectively reassociating the use of (>>=).
See Free for a more formal definition of the free Monad
 for a Functor.
Instances
| (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) | |
| (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 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 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.
Instances
liftF :: (Functor f, MonadFree f m) => f a -> m aSource
A version of lift that can be used with just a Functor for f.