| Portability | portable |
|---|---|
| Stability | experimental |
| Maintainer | dustin.deweese@gmail.com |
| Safe Haskell | Safe-Infered |
Control.Monad.Catana
Contents
Description
- Computation type:
- Computations that both consume and produce elements lazily with support for advanced control flow using continuations, recursion, and parallel and serial composition.
- Binding Strategy:
- Binding a function to a monadic value produces a continuation which is represented as a
Stepthat eitherWaits for input orYields a value, and returns the nextStep. - Useful for:
- Lazily processing a list with complex control structures.
- Zero and plus:
- mzero consumes all input with producing any output, mplus combines output of two Catana's in parallel
- Example type:
-
Catanai o b a
The Catana monad represents computations that are both catamorphisms and anamorphisms; they both consume and produce values. In addition, the Catana monad represents the computation in continuation-passing style, and implements callCC.
- data Catana i o b a = Catana {
- step :: (a -> Step i o b) -> Step i o b
- consume :: Catana i o a i
- top :: Catana i o a i
- push :: i -> Catana i o a ()
- produce :: o -> Catana i o a ()
- stop :: b -> Catana i o b a
- execCatana :: Catana i o a a -> [i] -> [o]
- runCatana :: Catana i o a a -> [i] -> (Maybe a, [o])
- parallelB :: Catana i o a a -> Catana i o b b -> Catana i o c (a, b)
- parallelE :: Catana i o a a -> Catana i o b b -> Catana i o c (Either a b)
- serial :: Catana io o a a -> Catana i io b b -> Catana i o c (Either a b)
The Catana monad
consume :: Catana i o a iSource
Consumes an element from the input list, returning it If there is no more input, the chain of continuations ends immediately; no more computations will be processed
execCatana :: Catana i o a a -> [i] -> [o]Source
Converts a Catana monad into a function over lists
runCatana :: Catana i o a a -> [i] -> (Maybe a, [o])Source
Evaluates a Catana monad over a list returning the result and output
parallelB :: Catana i o a a -> Catana i o b b -> Catana i o c (a, b)Source
Combine two monads to run in parallel, consuming the same input
parallelE :: Catana i o a a -> Catana i o b b -> Catana i o c (Either a b)Source
Combine two monads to run in parallel, consuming the same input, stopping when either of them finish.
serial :: Catana io o a a -> Catana i io b b -> Catana i o c (Either a b)Source
Combine two monads to run in serial, the first consuming the output of the second
Example 1: Basic usage of the Catana monad
An example of complex control structure using Catana:
catanaExample1 =
forever $ do
z <- callCC $ \exit -> do
(x, y) <- (,) <$> consume <*> consume
produce (x + y)
produce (x * y)
if x > 1
then exit 0
else do
produce (x - y)
produce (x / y)
return 1
produce z
Catana monads can be converted into a function over lists using execCatana.
>>>execCatana catanaExample1 [1..4][3.0,2.0,-1.0,0.5,1.0,7.0,12.0,0.0]
Example 2: An Example using serial and parallel data flow
An example using serial and parallel data flow:
catanaExample2 = sq `serial` (ev `parallelB` od)
where od = forever $ do
x <- consume
when (odd x) .
produce $ x * 2
ev = forever $ do
x <- consume
when (even x) .
produce $ x + 3
sq = forever $ do
x <- consume
produce x
produce $ x ^ 2
>>>let l = 1 : execCatana catanaExample2 l>>>take 10 l[1,2,4,5,25,7,49,10,100,50]
Example 3: An Example using recursion
An example using recursion:
fibTest :: Catana Int Int b a
fibTest = do
rec fib <- return $ \x ->
if x <= 1
then produce x >> return x
else do f1 <- fib (x-1)
f2 <- fib (x-2)
produce (f1+f2)
return (f1+f2)
forever $ consume >>= fib
>>>execCatana fibTest [3,5,7][1,0,1,1,2,1,0,1,1,2,1,0,1,3,1,0,1,1,2,5,1,0,1,1,2,1,0,1,3,1,0,1,1,2,5,1,0,1,1,2,1,0,1,3,8,1,0,1,1,2,1,0,1,3,1,0,1,1,2,5,13]