Catana-0.2: A monad for complex manipulation of a stream.

Portabilityportable
Stabilityexperimental
Maintainerdustin.deweese@gmail.com
Safe HaskellSafe-Infered

Control.Monad.Catana

Contents

Description

Computation type:
Computations that both consume and produce elements lazily with support for advanced control flow using continuations
Binding Strategy:
Binding a function to a monadic value produces a continuation which passes the unconsumed input and the combined output function in turn to the next continuation.
Useful for:
Lazily processing a list with complex control structures.
Zero and plus:
None.
Example type:
Catana i 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.

Synopsis

The Catana monad

data Catana i o b a Source

Constructors

Catana 

Fields

runCatana :: (a -> Step i o b) -> Step i o b
 

Instances

Monad (Catana i o b) 
Functor (Catana i o b) 
Applicative (Catana i o b) 
MonadCont (Catana i o b) 

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

top :: Catana i o a iSource

Returns the next input without consuming it

push :: i -> Catana i o a ()Source

Pushes x into the input

produce :: o -> Catana i o a ()Source

Produces x in the output

stop :: b -> Catana i o b aSource

Stops computation, ending the continuation chain

evalCatana :: Catana i o a a -> [i] -> [o]Source

Converts a Catana monad into a function over lists

evalCatana' :: 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: 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 evalCatana.

 evalCatana catanaExample1 [1..4]
 -- result: [3.0,2.0,-1.0,0.5,1.0,7.0,12.0,0.0] 

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 : evalCatana catanaExample2 l
 take 10 l
 -- result: [1,2,4,5,25,7,49,10,100,50]