pipes-2.1.0: Compositional pipelines

Safe HaskellSafe
LanguageHaskell2010

Control.Monad.Trans.Free

Contents

Description

People commonly misconstrue Free as defining a monad transformer with liftF behaving like lift, however that approach violates the monad transformer laws. Another common mistake is to include the base monad as a term in the functor, which also gives rise to an incorrect monad transformer.

To solve this, this module provides FreeT, which properly generalizes the free monad to a free monad transformer which is correct by construction.

The FreeT type commonly arises in coroutine and iteratee libraries that wish to provide a monad transformer that correctly obeys the monad transformer laws.

Synopsis

Free monad transformer

This differs substantially from the non-monad-transformer version because of the requirement to nest the constructors within the base monad.

To deconstruct a free monad transformer, use runFreeT to unwrap it and bind the result in the base monad. You can then pattern match against the bound value to obtain the next constructor:

do x <- runFreeT f
   case x of
       Return r -> ...
       Wrap   w -> ...

Because of this, you cannot create free monad transformers using the raw constructors from FreeF. Instead you use the smart constructors return (from Control.Monad) and wrap.

data FreeF f r x Source #

The signature for Free

Constructors

Return r 
Wrap (f x) 

data FreeT f m r Source #

A free monad transformer alternates nesting the base monad m and the base functor f.

  • f - The functor that generates the free monad transformer
  • m - The base monad
  • r - The type of the return value

Constructors

FreeT 

Fields

Instances

MonadTrans (FreeT f) Source # 

Methods

lift :: Monad m => m a -> FreeT f m a #

(Functor f, Monad m) => Monad (FreeT f m) Source # 

Methods

(>>=) :: FreeT f m a -> (a -> FreeT f m b) -> FreeT f m b #

(>>) :: FreeT f m a -> FreeT f m b -> FreeT f m b #

return :: a -> FreeT f m a #

fail :: String -> FreeT f m a #

(Functor f, Monad m) => Functor (FreeT f m) Source # 

Methods

fmap :: (a -> b) -> FreeT f m a -> FreeT f m b #

(<$) :: a -> FreeT f m b -> FreeT f m a #

(Functor f, Monad m) => Applicative (FreeT f m) Source # 

Methods

pure :: a -> FreeT f m a #

(<*>) :: FreeT f m (a -> b) -> FreeT f m a -> FreeT f m b #

(*>) :: FreeT f m a -> FreeT f m b -> FreeT f m b #

(<*) :: FreeT f m a -> FreeT f m b -> FreeT f m a #

wrap :: Monad m => f (FreeT f m r) -> FreeT f m r Source #

Smart constructor for Wrap

liftF :: (Functor f, Monad m) => f r -> FreeT f m r Source #

Equivalent to liftF from Control.Monad.Free

Free monad

The Free type is isomorphic to the following simple implementation:

data Free f r = Return r | Wrap (f (Free f r))

... except that if you want to pattern match against those constructors, you must first use runFree to unwrap the value first.

case (runFreeT f) of
    Return r -> ...
    Wrap   w -> ...

Similarly, you use the smart constructors return and wrap to build a value of type Free.

type Free f = FreeT f Identity Source #

FreeT reduces to Free when specialized to the Identity monad.

runFree :: Free f r -> FreeF f r (Free f r) Source #

Observation function that exposes the next FreeF constructor