free-4.12.4: Monads for free

Copyright(C) 2008-2014 Edward Kmett
LicenseBSD-style (see the file LICENSE)
MaintainerEdward Kmett <ekmett@gmail.com>
Stabilityprovisional
Portabilitynon-portable (rank-2 polymorphism, MTPCs)
Safe HaskellSafe
LanguageHaskell2010

Control.Monad.Trans.Free.Church

Contents

Description

Church-encoded free monad transformer.

Synopsis

The free monad transformer

newtype FT f m a

The "free monad transformer" for a functor f

Constructors

FT 

Fields

runFT :: forall r. (a -> m r) -> (forall x. (x -> m r) -> f x -> m r) -> m r
 

Instances

(Functor f, MonadError e m) => MonadError e (FT f m) 
MonadReader r m => MonadReader r (FT f m) 
MonadState s m => MonadState s (FT f m) 
(Functor f, MonadWriter w m) => MonadWriter w (FT f m) 
MonadFree f (FT f m) 
MonadTrans (FT f) 
Monad (FT f m) 
Functor (FT f m) 
Applicative (FT f m) 
(Foldable f, Foldable m, Monad m) => Foldable (FT f m) 
(Monad m, Traversable m, Traversable f) => Traversable (FT f m) 
Alternative m => Alternative (FT f m) 
MonadPlus m => MonadPlus (FT f m) 
MonadThrow m => MonadThrow (FT f m) 
(Functor f, MonadCatch m) => MonadCatch (FT f m) 
MonadIO m => MonadIO (FT f m) 
MonadCont m => MonadCont (FT f m) 
Apply (FT f m) 
Bind (FT f m) 
(Functor f, Monad m, Eq (FreeT f m a)) => Eq (FT f m a) 
(Functor f, Monad m, Ord (FreeT f m a)) => Ord (FT f m a) 

The free monad

type F f = FT f Identity

The "free monad" for a functor f.

free :: (forall r. (a -> r) -> (f r -> r) -> r) -> F f a

Wrap a Church-encoding of a "free monad" as the free monad for a functor.

runF :: Functor f => F f a -> forall r. (a -> r) -> (f r -> r) -> r

Unwrap the Free monad to obtain it's Church-encoded representation.

Operations

improveT :: (Functor f, Monad m) => (forall t. MonadFree f (t m) => t m a) -> FreeT f m a

Improve the asymptotic performance of code that builds a free monad transformer with only binds and returns by using FT behind the scenes.

Similar to improve.

toFT :: Monad m => FreeT f m a -> FT f m a

Generate a Church-encoded free monad transformer from a FreeT monad transformer.

fromFT :: (Monad m, Functor f) => FT f m a -> FreeT f m a

Convert to a FreeT free monad representation.

iterT :: (Functor f, Monad m) => (f (m a) -> m a) -> FT f m a -> m a

Tear down a free monad transformer using iteration.

iterTM :: (Functor f, Monad m, MonadTrans t, Monad (t m)) => (f (t m a) -> t m a) -> FT f m a -> t m a

Tear down a free monad transformer using iteration over a transformer.

hoistFT :: (Monad m, Monad n) => (forall a. m a -> n a) -> FT f m b -> FT f n b

Lift a monad homomorphism from m to n into a monad homomorphism from FT f m to FT f n

hoistFT :: (Monad m, Monad n, Functor f) => (m ~> n) -> FT f m ~> FT f n

transFT :: (forall a. f a -> g a) -> FT f m b -> FT g m b

Lift a natural transformation from f to g into a monad homomorphism from FT f m to FT g n

joinFT :: (Monad m, Traversable f) => FT f m a -> m (F f a)

Pull out and join m layers of FreeT f m a.

cutoff :: (Functor f, Monad m) => Integer -> FT f m a -> FT f m (Maybe a)

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.

Operations of free monad

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

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 :: (Functor f, MonadFree f m) => F f a -> m a

Convert to another free monad representation.

toF :: Free f a -> F f a

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

retract :: Monad f => F f a -> f a

retract is the left inverse of liftF

retract . liftF = id

retractT :: (MonadTrans t, Monad (t m), Monad m) => FT (t m) m a -> t m a

Tear down a free monad transformer using iteration over a transformer.

iter :: Functor f => (f a -> a) -> F f a -> a

Tear down an F Monad using iteration.

iterM :: (Functor f, Monad m) => (f (m a) -> m a) -> F f a -> m a

Like iter for monadic values.

Free Monads With Class

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

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

Add a layer.

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

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 (F f) 
Monad m => MonadFree Identity (IterT m) 
(Functor f, MonadFree f m) => MonadFree f (ExceptT e 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) 
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) 

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

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