free-4.2: Monads for free

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

Control.Monad.Trans.Iter

Description

Based on Capretta's Iterative Monad Transformer

Unlike Free, this is a true monad transformer.

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

Methods

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

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 (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 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 IterF a b Source

Constructors

Pure a 
Iter b 

Instances

Typeable2 IterF 
Bitraversable IterF 
Bifunctor IterF 
Bifoldable IterF 
Functor (IterF a) 
Foldable (IterF a) 
Traversable (IterF a) 
(Eq a, Eq b) => Eq (IterF a b) 
(Ord a, Ord b) => Ord (IterF a b) 
(Read a, Read b) => Read (IterF a b) 
(Show a, Show b) => Show (IterF a b) 

data IterT m a Source

The monad supporting iteration based over a base monad m.

 IterT ~ FreeT Identity

Constructors

IterT 

Fields

runIterT :: m (IterF a (IterT m a))
 

Instances

MonadTrans IterT

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

Monad m => MonadFree Identity (IterT m) 
(Functor m, MonadState s m) => MonadState s (IterT m) 
(Functor m, MonadReader e m) => MonadReader e (IterT m) 
Monad m => Monad (IterT m) 
Monad m => Functor (IterT m) 
Typeable1 m => Typeable1 (IterT m) 
MonadFix m => MonadFix (IterT m) 
MonadPlus m => MonadPlus (IterT m) 
Monad m => Applicative (IterT m) 
Foldable m => Foldable (IterT m) 
(Monad m, Traversable m) => Traversable (IterT m) 
MonadPlus m => Alternative (IterT m) 
(Monad m, Traversable1 m) => Traversable1 (IterT m) 
Foldable1 m => Foldable1 (IterT m) 
Monad m => Apply (IterT m) 
Monad m => Bind (IterT m) 
Eq (m (IterF a (IterT m a))) => Eq (IterT m a) 
(Typeable1 m, Typeable a, Data (m (IterF a (IterT m a))), Data a) => Data (IterT m a) 
Ord (m (IterF a (IterT m a))) => Ord (IterT m a) 
Read (m (IterF a (IterT m a))) => Read (IterT m a) 
Show (m (IterF a (IterT m a))) => Show (IterT m a) 

delay :: (Monad f, MonadFree f m) => m a -> m aSource

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

retract is the left inverse of lift

 retract . lift = id

iter :: Monad m => (m a -> a) -> IterT m a -> aSource

Tear down a Free Monad using iteration.

hoistIterT :: Monad n => (forall a. m a -> n a) -> IterT m b -> IterT n bSource

Lift a monad homomorphism from m to n into a Monad homomorphism from IterT m to IterT n.