Difference between revisions of "Contstuff"

From HaskellWiki
Jump to navigation Jump to search
m (→‎Introduction: Fixed wiki markup typo.)
(Added a lot of stuff.)
Line 3: Line 3:
 
The [http://hackage.haskell.org/package/contstuff 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''.
 
The [http://hackage.haskell.org/package/contstuff 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''.
   
== ContT ==
+
== Basics ==
  +
=== ContT ===
   
 
The <hask>ContT</hask> monad transformer is the simplest of all CPS-based monads. 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:
 
The <hask>ContT</hask> monad transformer is the simplest of all CPS-based monads. 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:
Line 13: Line 14:
 
* etc.
 
* etc.
   
All these features are effects of <hask>ContT</hask>. If you don't use them, then <hask>ContT</hask> behaves like the identity monad. A computation of type <hask>ContT r m a</hask> is a CPS computation with an intermediate result of type <hask>a</hask> and a final result of type <hask>r</hask>. The <hask>r</hask> type can be polymorphic most of the time. You only need to specify it, if you use some of the CPS effects like <hask>abort</hask>. Let's have a look at a small example:
+
All these features are effects of <hask>ContT</hask>. If you don't use them, then <hask>ContT</hask> behaves like the identity monad. A computation of type <hask>ContT r m a</hask> is a CPS computation with an intermediate result of type <hask>a</hask> and a final result of type <hask>r</hask>. The <hask>r</hask> type can be polymorphic most of the time. You only need to specify it, if you use some of the CPS effects like <hask>abort</hask>.
  +
 
To run a <hask>ContT</hask> computation you can use <hask>runContT</hask> or the convenience function <hask>evalContT</hask>:
  +
  +
<haskell>
  +
runContT :: (a -> m r) -> ContT r m a -> m r
  +
evalContT :: Applicative m => ContT r m r -> m r
  +
</haskell>
  +
 
The <hask>runContT</hask> function takes a final continuation transforming the last intermediate result into a final result. The <hask>evalContT</hask> function simply passes <hask>pure</hask> as the final continuation.
  +
  +
=== Abortion ===
  +
  +
Let's have a look at a small example:
   
 
<haskell>
 
<haskell>
Line 30: Line 44:
 
Each <hask>ContT</hask> 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 <hask>abort</hask> function does that.
 
Each <hask>ContT</hask> 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 <hask>abort</hask> function does that.
   
  +
=== Resumption and branches ===
To run a <hask>ContT</hask> computation you can use <hask>runContT</hask> or the convenience function <hask>evalContT</hask>:
 
  +
  +
You can capture the current continuation using the common <hask>callCC</hask> function. If you just need branches, there are two handy functions for this:
   
 
<haskell>
 
<haskell>
runContT :: (a -> m r) -> ContT r m a -> m r
+
labelCC :: a -> ContT r m (a, Label (ContT r m) a)
evalContT :: Applicative m => ContT r m r -> m r
+
goto :: Label (ContT r m) a -> a -> ContT r m b
 
</haskell>
 
</haskell>
   
  +
These slightly complicated looking functions are actually very simple to use:
The <hask>runContT</hask> function takes a final continuation transforming the last intermediate result into a final result. The <hask>evalContT</hask> function simply passes <hask>pure</hask> as the final continuation.
 
  +
  +
<haskell>
  +
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)
  +
</haskell>
  +
  +
The <hask>labelCC</hask> function establishes a label to jump to by capturing its own continuation. It returns both its argument and a label. The <hask>goto</hask> function takes a label and a new argument. The effect is jumping to the corresponding label, but returning the new argument. So when <hask>labelCC</hask> is reached the <hask>i</hask> variable becomes 0. Later <hask>goto</hask> jumps back to the same point, but gives <hask>i</hask> a new value 1, as if <hask>labelCC</hask> 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 <hask>ContT</hask> computation.
  +
  +
=== Lifting ===
  +
  +
As noted earlier there are three lifting functions, which you can use to access monads in lower layers of the transformer stack:
  +
  +
<haskell>
  +
lift :: (Transformer t, Monad m) => m a -> t m a
  +
base :: (LiftBase m a) => Base m a -> m a
  +
io :: (Base m a ~ IO a, LiftBase m a) => Base m a -> m a
  +
</haskell>
  +
  +
The <hask>lift</hask> function promotes a computation of the underlying monad. The <hask>base</hask> function promotes a computation of the base monad. It is a generalization of <hask>liftIO</hask> from other monad transformer libraries. Finally there is <hask>io</hask>, which is simply an alias for <hask>base</hask>, but restricted to <hask>IO</hask>.
  +
  +
=== Accumulating results ===
  +
  +
<hask>ContT</hask> does not require the underlying functor to be a monad. Whenever the underlying functor is an <hask>Alternative</hask> functor, there is support for accumulating results using the <hask>(<|>)</hask> combinator. In other words, if <hask>m</hask> is an <hask>Alternative</hask>, then <hask>ContT r m</hask> is, too. Here is an example:
  +
  +
<haskell>
  +
testComp3 :: Num a => ContT r [] (a, a)
  +
testComp3 = do
  +
x <- pure 10 <|> pure 20
  +
y <- pure (x+1) <|> pure (x-1)
  +
return (x, y)
  +
</haskell>
  +
  +
The ''contstuff'' library implements a convenience function <hask>listA</hask>, which turns a list into an <hask>Alternative</hask> computation:
  +
  +
<haskell>
  +
listA :: (Alternative f) => [a] -> f a
  +
</haskell>
  +
  +
Using this you can simplify <hask>testComp3</hask> to:
  +
  +
<haskell>
  +
testComp3' :: Num a => ContT r [] (a, a)
  +
testComp3' = do
  +
x <- listA [10, 20]
  +
y <- listA [x+1, x-1]
  +
return (x, y)
  +
</haskell>
  +
  +
You can collapse branches using <hask>abort</hask>:
  +
  +
<haskell>
  +
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)
  +
</haskell>

Revision as of 23:49, 20 September 2010

Introduction

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

ContT

The ContT monad transformer is the simplest of all CPS-based monads. 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

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

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 b

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

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 a) => Base m a -> m a
io   :: (Base m a ~ IO a, LiftBase m a) => 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

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)