free-3.3.0.2: Monads for free

Portabilitynon-portable (rank-2 polymorphism)
Stabilityprovisional
MaintainerEdward Kmett <ekmett@gmail.com>
Safe HaskellNone

Control.Monad.Free.Church

Description

"Free Monads for Less"

This is based on the "Free Monads for Less" series of articles:

http://comonad.com/reader/2011/free-monads-for-less/ http://comonad.com/reader/2011/free-monads-for-less-2/

Synopsis

Documentation

newtype F f a Source

The Church-encoded free monad for a functor f.

It is asymptotically more efficient to use (>>=) for F than it is to (>>=) with Free.

http://comonad.com/reader/2011/free-monads-for-less-2/

Constructors

F 

Fields

runF :: forall r. (a -> r) -> (f r -> r) -> r
 

Instances

MonadTrans F 
(Monad (F m), MonadReader e m) => MonadReader e (F m) 
(Monad (F m), MonadState s m) => MonadState s (F m) 
(Monoid w, Monad (F m), MonadWriter w m) => MonadWriter w (F m) 
(Monad (F f), Functor f) => MonadFree f (F f) 
Monad (F f) 
Functor (F f) 
(Monad (F f), MonadPlus f) => MonadPlus (F f) 
Functor (F f) => Applicative (F f) 
(Applicative (F f), Alternative f) => Alternative (F f) 
(Monad (F m), MonadCont m) => MonadCont (F m) 
Functor (F f) => Apply (F f) 
Apply (F f) => Bind (F f) 

improve :: Functor f => (forall m. MonadFree f m => m a) -> Free f aSource

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:

http://comonad.com/reader/2011/free-monads-for-less/ http://comonad.com/reader/2011/free-monads-for-less-2/

and "Asymptotic Improvement of Computations over Free Monads" by Janis Voightländer:

http://www.iai.uni-bonn.de/~jv/mpc08.pdf

fromF :: MonadFree f m => F f a -> m aSource

Convert to another free monad representation.

toF :: Functor f => Free f a -> F f aSource

Generate a Church-encoded free monad from a Free monad.

liftF :: Functor f => f a -> F f aSource

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

retract :: Monad m => F m a -> m aSource

retract is the left inverse of lift and liftF

 retract . lift = id
 retract . liftF = id