Copyright | (C) 2008-2014 Edward Kmett |
---|---|
License | BSD-style (see the file LICENSE) |
Maintainer | Edward Kmett <ekmett@gmail.com> |
Stability | provisional |
Portability | non-portable (rank-2 polymorphism, MTPCs) |
Safe Haskell | Safe |
Language | Haskell2010 |
Church-encoded free monad transformer.
Synopsis
-
newtype
FT
f m a =
FT
{
- runFT :: forall r. (a -> m r) -> ( forall x. (x -> m r) -> f x -> m r) -> m r
- type F f = FT f Identity
- free :: ( forall r. (a -> r) -> (f r -> r) -> r) -> F f a
- runF :: Functor f => F f a -> forall r. (a -> r) -> (f r -> r) -> r
- improveT :: ( Functor f, Monad m) => ( forall t. MonadFree f (t m) => t m a) -> FreeT f m a
- toFT :: Monad m => FreeT f m a -> FT f m a
- fromFT :: ( Monad m, Functor f) => FT f m a -> FreeT f m a
- iterT :: ( Functor f, Monad m) => (f (m a) -> m a) -> FT f m a -> m a
- iterTM :: ( Functor f, Monad m, MonadTrans t, Monad (t m)) => (f (t m a) -> t m a) -> FT f m a -> t m a
- hoistFT :: ( Monad m, Monad n) => ( forall a. m a -> n a) -> FT f m b -> FT f n b
- transFT :: ( forall a. f a -> g a) -> FT f m b -> FT g m b
- joinFT :: ( Monad m, Traversable f) => FT f m a -> m ( F f a)
- cutoff :: ( Functor f, Monad m) => Integer -> FT f m a -> FT f m ( Maybe a)
- improve :: Functor f => ( forall m. MonadFree f m => m a) -> Free f a
- fromF :: ( Functor f, MonadFree f m) => F f a -> m a
- toF :: Free f a -> F f a
- retract :: Monad f => F f a -> f a
- retractT :: ( MonadTrans t, Monad (t m), Monad m) => FT (t m) m a -> t m a
- iter :: Functor f => (f a -> a) -> F f a -> a
- iterM :: ( Functor f, Monad m) => (f (m a) -> m a) -> F f a -> m a
-
class
Monad
m =>
MonadFree
f m | m -> f
where
- wrap :: f (m a) -> m a
- liftF :: ( Functor f, MonadFree f m) => f a -> m a
The free monad transformer
The "free monad transformer" for a functor
f
Instances
The free monad
free :: ( forall r. (a -> r) -> (f r -> r) -> r) -> F f a Source #
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 Source #
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 Source #
toFT :: Monad m => FreeT f m a -> FT f m a Source #
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 Source #
Convert to a
FreeT
free monad representation.
iterT :: ( Functor f, Monad m) => (f (m a) -> m a) -> FT f m a -> m a Source #
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 Source #
Tear down a free monad transformer using iteration over a transformer.
joinFT :: ( Monad m, Traversable f) => FT f m a -> m ( F f a) Source #
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) Source #
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 Source #
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:
fromF :: ( Functor f, MonadFree f m) => F f a -> m a Source #
Convert to another free monad representation.
retractT :: ( MonadTrans t, Monad (t m), Monad m) => FT (t m) m a -> t m a Source #
Tear down a free monad transformer using iteration over a transformer.
iterM :: ( Functor f, Monad m) => (f (m a) -> m a) -> F f a -> m a Source #
Like
iter
for monadic values.
Free Monads With Class
class Monad m => MonadFree f m | m -> f where Source #
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
smashes the lists flat.
join
[[a]]
On the other hand, consider:
data Tree a = Bin (Tree a) (Tree a) | Tip a
instanceMonad
Tree wherereturn
= 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:
instanceMonadFree
Pair Tree wherewrap
(Pair l r) = Bin l r
Or we could choose to program with
instead of
Free
Pair
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
.
Nothing