cv-combinators-0.1: Functional Combinators for Computer Vision

Portabilitytested on GHC only
Stabilityexperimental
MaintainerNoam Lewis <jones.noamle@gmail.com>

AI.CV.Processor

Description

Framework for expressing monadic actions that require initialization and finalizers. This module provides a *functional* interface for defining and chaining a series of processors.

Motivating example: bindings to C libraries that use functions such as: f(foo *src, foo *dst), where the pointer dst must be pre-allocated. In this case we normally do:

foo *dst = allocateFoo(); ... while (something) { f(src, dst); ... } releaseFoo(dst);

You can use the runUntil function below to emulate that loop.

Processor is an instance of Category, Functor, Applicative and Arrow.

Synopsis

Documentation

data Processor m a b whereSource

The type of Processors

The semantic model is:

 [[ Processor m o a b ]] = a -> b

The idea is that the monad m is usually IO, and that a and b are usually pointers. It is meant for functions that require a pre-allocated output pointer to operate.

  • a, b = the input and output types of the processor (think a -> b)
  • m = monad in which the processor operates
  • x = type of internal state

The arguments to the constructor are:

  1. Processing function: Takes input and internal state, and returns new internal state.
  2. Allocator for internal state (this is run only once): Takes (usually the first) input, and returns initial internal state.
  3. Convertor from state x to output b: Takes internal state and returns the output.
  4. Releaser for internal state (finalizer, run once): Run after processor is done being used, to release the internal state.

Constructors

Processor :: Monad m => (a -> x -> m x) -> (a -> m x) -> (x -> m b) -> (x -> m ()) -> Processor m a b 

Instances

Monad m => Arrow (Processor m)

A few tricks by Saizan from #haskell to perhaps use here: first f = (,) $ (arr fst >>> f) * arr snd arr f = f $ id f *** g = (arr fst >>> f) &&& (arr snd >>> g)

Monad m => Category (Processor m) 
Monad m => Functor (Processor m a) 
Monad m => Applicative (Processor m a) 

processor :: Monad m => (a -> x -> m x) -> (a -> m x) -> (x -> m b) -> (x -> m ()) -> Processor m a bSource

chain :: Monad m => Processor m a b' -> Processor m b' b -> Processor m a bSource

Chains two processors serially, so one feeds the next.

parallel :: Monad m => Processor m a b -> Processor m c d -> Processor m (a, c) (b, d)Source

A processor that represents two sub-processors in parallel (although the current implementation runs them sequentially, but that may change in the future)

forkJoin :: Monad m => Processor m a b -> Processor m a b' -> Processor m a (b, b')Source

Constructs a processor that: given two processors, gives source as input to both processors and runs them independently, and after both have have finished, outputs their combined outputs.

Semantic meaning, using Arrow's (&&&) operator: [[ forkJoin ]] = &&& Or, considering the Monad instance of functions (which are the semantic meanings of a processor): [[ forkJoin ]] = liftM2 (,) Alternative implementation to consider: f &&& g = (,) & f * g

empty :: Monad m => Processor m a aSource

The identity processor: output = input. Semantically, [[ empty ]] = id

split :: Functor f => f a -> f (a, a)Source

Splits (duplicates) the output of a functor, or on this case a processor.

(--<) :: (Functor (cat a), Category cat) => cat a a1 -> cat (a1, a1) c -> cat a cSource

'f --< g' means: split f and feed it into g. Useful for feeding parallelized (***'d) processors. For example, a --< (b &&& c)

run :: Monad m => Processor m a b -> a -> m bSource

Runs the processor once: allocates, processes, converts to output, and deallocates.

runUntil :: Monad m => Processor m a b -> a -> (b -> m Bool) -> m bSource

Keeps running the processing function in a loop until a predicate on the output is true. Useful for processors whose main function is after the allocation and before deallocation.

runWith :: Monad m => (m b -> m b') -> Processor m a b -> a -> m b'Source

Runs the processor once, but passes the processing + conversion action to the given function.