Contstuff
The contstuff library implements a number of monad transformers and monads, which make heavy use of continuation passing style (CPS). This makes them both fast and flexible. Please note that this is neither a CPS tutorial nor a monad transformer tutorial. You should understand these concepts, before attempting to use contstuff.
Basics[edit]
ContT[edit]
The ContT monad transformer is the simplest of all CPS-based monads:
newtype ContT r m a
It essentially gives you access to the current continuation, which means that it lets you label certain points of execution and reuse these points later in interesting ways. With ContT you get an elegant encoding of computations, which support:
- abortion (premature termination),
- resumption (start a computation at a certain spot),
- branches (aka goto),
- result accumulation,
- etc.
All these features are effects of ContT. If you don't use them, then ContT behaves like the identity monad. A computation of type ContT r m a
is a CPS computation with an intermediate result of type a
and a final result of type r
. The r
type can be polymorphic most of the time. You only need to specify it, if you use some of the CPS effects like abort
.
To run a ContT computation you can use runContT
or the convenience function evalContT
:
runContT :: (a -> m r) -> ContT r m a -> m r
evalContT :: Applicative m => ContT r m r -> m r
The runContT
function takes a final continuation transforming the last intermediate result into a final result. The evalContT
function simply passes pure
as the final continuation.
Abortion[edit]
Let's have a look at a small example:
testComp1 :: ContT () IO ()
testComp1 =
forever $ do
txt <- io getLine
case txt of
"info" -> io $ putStrLn "This is a test computation."
"quit" -> abort ()
_ -> return ()
This example demonstrates the most basic feature of ContT. First of all, ContT is a monad transformer, so you can for example lift IO actions to a CPS computation. The io
function is a handy tool, which corresponds to liftIO
from other transformer libraries and to inBase
from monadLib, but is restricted to the IO monad. You can also use the more generic base
function, which promotes a base monad computation to ContT.
Each ContT subcomputation receives a continuation, which is a function, to which the subcomputation is supposed to pass the result. However, the subcomputation may choose not to call the continuation at all, in which case the entire computation finishes with a final result. The abort
function does that.
Resumption and branches[edit]
You can capture the current continuation using the common callCC
function. If you just need branches, there are two handy functions for this:
labelCC :: a -> ContT r m (a, Label (ContT r m) a)
goto :: Label (ContT r m) a -> a -> ContT r m ()
These slightly complicated looking functions are actually very simple to use:
testComp2 :: ContT r IO ()
testComp2 = do
(i, again) <- labelCC 0
io (print i)
when (i < 10) $ goto again (i+1)
io (putStrLn $ "Final result: " ++ show i)
The labelCC
function establishes a label to jump to by capturing its own continuation. It returns both its argument and a label. The goto
function takes a label and a new argument. The effect is jumping to the corresponding label, but returning the new argument. So when labelCC
is reached the i
variable becomes 0. Later goto
jumps back to the same point, but gives i
a new value 1, as if labelCC
were originally called with 1 as the argument.
Labels are first class values in contstuff. This means you can carry them around. They are only limited in that they can't be carried outside of a ContT computation.
Lifting[edit]
As noted earlier there are three lifting functions, which you can use to access monads in lower layers of the transformer stack:
lift :: (Transformer t, Monad m) => m a -> t m a
base :: LiftBase m => Base m a -> m a
io :: (LiftBase m, Base m ~ IO) => Base m a -> m a
The lift
function promotes a computation of the underlying monad. The base
function promotes a computation of the base monad. It is a generalization of liftIO
from other monad transformer libraries. Finally there is io
, which is simply an alias for base
, but restricted to IO.
Accumulating results[edit]
ContT does not require the underlying functor to be a monad. Whenever the underlying functor is an Alternative
functor, there is support for accumulating results using the (<|>)
combinator. In other words, if m
is an Alternative
, then ContT r m
is, too. Here is an example:
testComp3 :: Num a => ContT r [] (a, a)
testComp3 = do
x <- pure 10 <|> pure 20
y <- pure (x+1) <|> pure (x-1)
return (x, y)
The contstuff library implements a convenience function listA
, which turns a list into an Alternative
computation:
listA :: (Alternative f) => [a] -> f a
Using this you can simplify testComp3
to:
testComp3' :: Num a => ContT r [] (a, a)
testComp3' = do
x <- listA [10, 20]
y <- listA [x+1, x-1]
return (x, y)
You can collapse branches using abort
:
testComp4 :: Num a => ContT (a, a) [] (a, a)
testComp4 = do
x <- listA [10, 20]
when (x == 10) (abort (10, 10))
y <- listA [x+1, x-1]
return (x, y)
State[edit]
The contstuff library also comes with a monad transformer for stateful computations. These computations carry state of a certain type and can access it at any time. It's called StateT, just like in other transformer libraries, but this one has very different semantics and also takes an additional parameter:
newtype StateT r s m a
It is basically a generalization of ContT. In fact you can use all the features of ContT in a StateT computation, too, including abortion, labels, accumulation, etc.
The r
parameter is the type of the final result. In actual computations this parameter can be left polymorphic most of the time, unless you use abortion.
Accessing the state[edit]
There are many functions to access the implicit state. These don't belong to StateT directly, but instead to a type class called Stateful, of which StateT is an instance. The associated type StateOf m
is the type of the state of the monad m
:
-- Where 'm' is a Stateful monad, 'StateOf m' is the type of its state.
get :: (Stateful m) => m (StateOf m)
put :: (Stateful m) => StateOf m -> m ()
putLazy :: (Stateful m) => StateOf m -> m ()
-- Convenience functions.
getField :: (Functor m, Stateful m) => (StateOf m -> a) -> m a
modify :: (Monad m, Stateful m) => (StateOf m -> StateOf m) -> m ()
modifyLazy :: (Monad m, Stateful m) => (StateOf m -> StateOf m) -> m ()
modifyField :: (Monad m, Stateful m) =>
(StateOf m -> a) -> (a -> StateOf m) -> m ()
modifyFieldLazy :: (Monad m, Stateful m) =>
(StateOf m -> a) -> (a -> StateOf m) -> m ()
As the names suggest StateT is strict by default. When setting a new state using put
, the state is evaluated. If you want to avoid that use putLazy
instead.
Running[edit]
To run a stateful computation you can use the runStateT
function, which takes a final continuation, an initial state and a stateful computation as arguments. There are two convenience functions evalStateT
runStateT :: s -> (s -> a -> m r) -> StateT r s m a -> m r
evalStateT :: (Applicative m) => s -> StateT r s m r -> m r
execStateT :: (Applicative m) => s -> StateT s s m a -> m s
In most cases you will just use evalStateT
or execStateT
.
Exceptions[edit]
Contstuff provides an EitherT monad transformer:
newtype EitherT r e m a
This monad transformer is a generalization of ContT in that it supports two continuations. The second one can be accessed indirectly by the various exception handling functions.
Raising and catching[edit]
There are a number of functions to handle exceptions, which belong to a class HasExceptions
with an associated type Exception m
. EitherT is an instance of this class.
-- Where 'm' is a monad supporting exceptions, 'Exception m' is the
-- type of the exceptions.
raise :: (HasExceptions m) => Exception m -> m a
try :: (HasExceptions m) => m a -> m (Either (Exception m) a)
-- Convenience functions.
catch :: (HasExceptions m, Monad m) => m a -> (Exception m -> m a) -> m a
handle :: (HasExceptions m, Monad m) => (Exception m -> m a) -> m a -> m a
finally :: (HasExceptions m, Monad m) => m a -> m b -> m a
bracket :: (HasExceptions m, Monad m) =>
m res -> (res -> m b) -> (res -> m a) -> m a
bracket_ :: (HasExceptions m, Monad m) => m a -> m b -> m c -> m c
Please note that bracket
and bracket_
have slightly different semantics than the corresponding functions from Control.Exception
. If an exception is raised in both the middle computation and the final computation, then the middle one is significant.
Running[edit]
To run an EitherT computation you can use the runEitherT
function, which expects the two final continuations and an EitherT computation. There is also a convenience function evalEitherT
, which just returns an Either value:
runEitherT :: (a -> m r) -> (e -> m r) -> EitherT r e m a -> m r
evalEitherT :: (Applicative m) =>
EitherT (Either e a) e m a -> m (Either e a)
Choice/nondeterminism[edit]
The ChoiceT monad transformer is basically a list monad transformer and a proper one at that. It is also very fast, because choice is implemented as a CPS-based left fold function:
newtype ChoiceT r i m a
The parameters r
and i
are the types of the final and the intermediate results respectively. In actual computations, unless you use abortion, these can be left polymorphic most of the time. Also practically they are almost always the same. Don't worry about them.
Running[edit]
You can run a ChoiceT computation by using the slightly scary runChoiceT
function:
runChoiceT ::
(i -> a -> (i -> m r) -> m r) -> i -> (i -> m r)
-> ChoiceT r i m a -> m r
This function takes a folding function, a base element, a final continuation (the folding function uses CPS) and a ChoiceT computation. Of course in practice you mostly just want a list of results or the first result or something like that. Luckily there are two convenience functions to do just that:
findFirst :: (Alternative f, Applicative m) =>
ChoiceT (f a) (f a) m a -> m (f a)
findAll :: (Alternative f, Applicative m) =>
ChoiceT (f a) (f a) m a -> m (f a)
Even these look scary, but they really aren't. In most cases f
is just []
or Maybe
. But there are more convenience functions:
maybeChoiceT :: Applicative m =>
ChoiceT (Maybe a) (Maybe a) m a -> m (Maybe a)
listChoiceT :: Applicative m => ChoiceT [a] [a] m a -> m [a]
The maybeChoiceT
function is just a special case of findFirst
. The listChoiceT
in contrast does not behave like findAll
. It returns the results in reversed order and is much faster than findAll
.
Convenience functions[edit]
Often you just want to encode a list of choices. For this you can use the listA
function discussed earlier:
listA :: (Alternative f) => [a] -> f a
There is an alternative function, which works only for ChoiceT, but is much faster than listA
, called just choice
:
choice :: [a] -> ChoiceT r i m a