orc-1.2.1.1: Orchestration-style co-ordination EDSL

StabilityPortability : concurrency
MaintainerJohn Launchbury <john@galois.com>

Orc.Monad

Description

Primitive combinators for the Orc EDSL in Haskell.

Synopsis

Documentation

data Orc a Source

A monad for many-valued concurrency, external actions and managed resources. An expression of type Orc a may perform many actions and return many results of type a. The MonadPlus instance does not obey the Right-Zero law (p >> stop /= stop).

stop :: Orc aSource

Finish the local thread of operations, so that anything sequenced afterwards is not executed. It satisfies the following law: stop >>= k == stop

eagerly :: Orc a -> Orc (Orc a)Source

Immediately fires up a thread for p, and then returns a handle to the first result of that thread which is also of type Orc a. An invocation to eagerly is non-blocking, while an invocation of the resulting handle is blocking. eagerly satisfies the following laws:

Par-eagerly:

 eagerly p >>= (\x -> k x <|> h)
 == (eagerly p >>= k) <|> h

Eagerly-swap:

 do y <- eagerly p
    x <- eagerly q
    k x y
 == do x <- eagerly q
       y <- eagerly p
       k x y

Eagerly-IO:

 eagerly (liftIO m) >> p == (liftIO m >> stop) <|> p

val :: Orc a -> Orc aSource

An alternate mechanism for eagerly, it fires up a thread for p and returns a lazy thunk that contains the single (trimmed) result of the computation. Be careful to use this function with public when these lazy values need to be fully evaluated before proceeding further. For example, the following code succeeds immediately:

 do x <- val p
    return x

Whereas this code waits until p has generated one result before returning:

 do x <- val p
    publish p

(<+>) :: Orc a -> Orc a -> Orc aSource

Biased choice operator (pronounced and-then) that performs the action (and returns all the results) of p first, and then once done performs the action of q.

runOrc :: Orc a -> IO ()Source

Runs an Orc computation, discarding the (many) results of the computation. See collect on a mechanism for collecting the results of a computation into a list, which may then be passed to another IO thread.