fraxl-0.1.0.0: Cached and parallel data fetching.

Safe HaskellSafe
LanguageHaskell2010

Control.Monad.Trans.Fraxl.Free

Contents

Synopsis

The base functor

data FreeF f m a where Source

The base functor for a free monad.

Constructors

Pure :: a -> FreeF f m a 
Free :: f b -> FastTCQueue (Kleisli (FreeT f m)) b a -> FreeF f m a 

Instances

The free monad transformer

newtype FreeT f m a Source

The "free monad transformer" for an applicative functor f

Constructors

FreeT 

Fields

runFreeT :: m (FreeF f m a)
 

The free monad

type Free f = FreeT f Identity Source

The "free monad" for an applicative functor f.

Operations

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

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

iterT :: (Applicative f, Monad m) => (f (m a) -> m a) -> FreeT f m a -> m a Source

Tear down a free monad transformer using iteration.

iterTM :: (Applicative f, Monad m, MonadTrans t, Monad (t m)) => (f (t m a) -> t m a) -> FreeT f m a -> t m a Source

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

hoistFreeT :: (Monad m, Applicative f) => (forall a. m a -> n a) -> FreeT f m b -> FreeT f n b Source

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

hoistFreeT :: (Monad m, Functor f) => (m ~> n) -> FreeT f m ~> FreeT f n

transFreeT :: (Applicative f, Monad m) => (forall a. f a -> g a) -> FreeT f m b -> FreeT g m b Source

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

joinFreeT :: forall m f a. (Monad m, Traversable f, Applicative f) => FreeT f m a -> m (Free f a) Source

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

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

Tear down a free monad transformer using Monad instance for t m.

Operations of free monad

retract :: Monad f => Free f a -> f a Source

retract is the left inverse of liftF

retract . liftF = id

iter :: Applicative f => (f a -> a) -> Free f a -> a Source

Tear down a Free Monad using iteration.

iterM :: (Applicative f, Monad m) => (f (m a) -> m a) -> Free f a -> m a Source

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 (MaybeT m) 
(Functor f, MonadFree f m) => MonadFree f (ListT m) 
(Functor f, MonadFree f m) => MonadFree f (IdentityT m) 
(Applicative f, Monad m) => MonadFree f (FreeT f 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 (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, 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) => MonadFree f (ContT r 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)