free-3.4.2: Monads for free

PortabilityMPTCs, fundeps
Stabilityprovisional
MaintainerEdward Kmett <ekmett@gmail.com>
Safe HaskellNone

Control.MonadPlus.Free

Description

left-distributive MonadPlus for free.

Synopsis

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 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, 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.

Methods

wrap :: f (m a) -> m aSource

Add a layer.

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) 

data Free f a Source

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.

Constructors

Pure a 
Free (f (Free f a)) 
Plus [Free f a] 

Instances

MonadTrans Free

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

(Functor m, MonadPlus m, MonadError e m) => MonadError e (Free m) 
(Functor m, MonadPlus m, MonadReader e m) => MonadReader e (Free m) 
(Functor m, MonadState s m) => MonadState s (Free m) 
(Functor m, MonadPlus 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 => MonadPlus (Free f) 
Functor f => Applicative (Free f) 
Foldable f => Foldable (Free f) 
Traversable f => Traversable (Free f) 
Functor f => Alternative (Free f) 
(Functor m, MonadPlus m, MonadCont m) => MonadCont (Free m) 
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) 
Functor f => Monoid (Free f a) 
Functor f => Semigroup (Free f a) 

retract :: MonadPlus f => Free f a -> f aSource

retract is the left inverse of lift and liftF

 retract . lift = id
 retract . liftF = id

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

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

iter :: Functor f => (f a -> a) -> ([a] -> a) -> Free f a -> aSource

Tear down a Free Monad using iteration.

iterM :: (Monad m, Functor f) => (f (m a) -> m a) -> ([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 FreeT f to FreeT g.