lvish-1.1.1.2: Parallel scheduler, LVar data structures, and infrastructure to build more.

Safe HaskellNone

Control.LVish

Contents

Description

The lvish package provides a parallel programming model based on monotonically growing data structures.

This module provides the core scheduler and basic control flow operations. But to do anything useful you will need to import, along with this module, one of the data structure modules (Data.LVar.*).

Here is a self-contained example. This program writes the same value to an LVar called num twice. It deterministically prints 4 instead of raising an error, as it would if num were a traditional IVar rather than an LVar. (You will need to compile using the -XDataKinds extension.)

 
 import Control.LVish  -- Generic scheduler; works with any lattice.
 import Data.LVar.IVar -- The particular lattice in question.
 
 p :: Par Det s Int
 p = do
   num <- new
   fork $ put num 4
   fork $ put num 4
   get num
 
 main = do
   print $ runPar $ p

Synopsis

CRITICAL OBLIGATIONS for the user: valid Eq and total Ord

We would like to tell you that if you're programming with Safe Haskell (-XSafe), that this library provides a formal guarantee that anything executed with runPar is guaranteed-deterministic. Unfortunately, as of this release there is still one back-door that hasn't yet been closed.

If an adversarial user defines invalid Eq instances (claiming objects are equal when they're not), or if they define a compare function that is not a pure, total function, and then they store those types within LVars, then nondeterminism may leak out of a parallel runPar computation.

In future releases, we will strive to require alternate, safe versions of Eq and Ord that are derived automatically by our library and by the GHC compiler.

Par computations and their parameters

data Par Source

The type of parallel computations. A computation Par d s a may or may not be deterministic based on the setting of the d parameter (of kind Determinism). The s parameter is for preventing the escape of LVars from Par computations (just like the ST monad).

Implementation note: This is a wrapper around the internal Par type, only with more type parameters.

Instances

Monad (Par $a $b) 
Functor (Par $a $b) 
Applicative (Par $a $b) 
MonadIO (Par d s) 

data Determinism Source

This datatype is promoted to type-level (DataKinds extension) and used to indicate whether a Par computation is guaranteed-deterministic, or only quasi-deterministic (i.e., might throw NonDeterminismExn).

Constructors

Det 
QuasiDet 

Instances

liftQD :: Par Det s a -> Par QuasiDet s aSource

It is always safe to lift a deterministic computation to a quasi-deterministic one.

data LVishException Source

All LVars share a common notion of exceptions. The two common forms of exception currently are conflicting-put and put-after-freeze. There are also errors that correspond to particular invariants for particular LVars.

Constructors

ConflictingPutExn String 
PutAfterFreezeExn String 
LVarSpecificExn String 

Instances

Basic control flow

fork :: Par d s () -> Par d s ()Source

Execute a computation in parallel.

yield :: Par d s ()Source

Cooperatively schedule other threads.

runPar :: (forall s. Par Det s a) -> aSource

If a computation is guaranteed-deterministic, then Par becomes a dischargeable effect. This function will create new worker threads and do the work in parallel, returning the final result.

(For now there is no sharing of workers with repeated invocations; so keep in mind that runPar is an expensive operation. [2013.09.27])

runParIO :: (forall s. Par d s a) -> IO aSource

If the input computation is quasi-deterministic (QuasiDet), then this may throw a LVishException nondeterministically on the thread that calls it, but if it returns without exception then it always returns the same answer.

If the input computation is deterministic (Det), then runParIO will return the same result as runPar. However, runParIO is still possibly useful for avoiding an extra unsafePerformIO required inside the implementation of runPar.

In the future, full nondeterminism may be allowed as a third setting beyond Det and QuasiDet.

Various loop constructs

parForL :: (Int, Int) -> (Int -> Par d s ()) -> Par d s ()Source

Deprecated: These will be removed in a future release in favor of a more general approach to loops.

Left-biased parallel for loop. As worker threads beyond the first are added, this hews closer to the sequential iteration order than an unbiased parallel loop.

Takes a range as inclusive-start, exclusive-end.

parForSimple :: (Int, Int) -> (Int -> Par d s ()) -> Par d s ()Source

Deprecated: These will be removed in a future release in favor of a more general approach to loops.

The least-sophisticated form of parallel loop. Fork iterations one at a time.

parForTree :: (Int, Int) -> (Int -> Par d s ()) -> Par d s ()Source

Deprecated: These will be removed in a future release in favor of a more general approach to loops.

Divide the iteration space recursively, but ultimately run every iteration in parallel. That is, the loop body is permitted to block on other iterations.

parForTiled :: Maybe HandlerPool -> Int -> (Int, Int) -> (Int -> Par d s ()) -> Par d s ()Source

Deprecated: These will be removed in a future release in favor of a more general approach to loops.

Split the work into a number of tiles, and fork it in a tree topology.

for_ :: Monad m => (Int, Int) -> (Int -> m ()) -> m ()Source

A simple for loop for numeric ranges (not requiring deforestation optimizations like forM). Inclusive start, exclusive end.

Logical control flow operators

asyncAnd :: Maybe HandlerPool -> Par d s Bool -> Par d s Bool -> (Bool -> Par d s ()) -> Par d s ()Source

A parallel And operation that can return early---whenever a False appears on either branch.

asyncOr :: Maybe HandlerPool -> Par d s Bool -> Par d s Bool -> (Bool -> Par d s ()) -> Par d s ()Source

Analagous operation for Or.

andMap :: Maybe HandlerPool -> (a -> Par d s Bool) -> [a] -> Par d s BoolSource

orMap :: Maybe HandlerPool -> (a -> Par d s Bool) -> [a] -> Par d s BoolSource

Synchronizing with handler pools

data HandlerPool Source

A HandlerPool contains a way to count outstanding parallel computations that are affiliated with the pool. It detects the condition where all such threads have completed.

newPool :: Par d s HandlerPoolSource

Create a new pool that can be used to synchronize on the completion of all parallel computations associated with the pool.

withNewPool :: (HandlerPool -> Par d s a) -> Par d s (a, HandlerPool)Source

Execute a Par computation in the context of a fresh handler pool.

withNewPool_ :: (HandlerPool -> Par d s ()) -> Par d s HandlerPoolSource

Execute a Par computation in the context of a fresh handler pool, while ignoring the result of the computation.

quiesce :: HandlerPool -> Par d s ()Source

Block until a handler pool is quiescent, i.e., until all associated parallel computations have completed.

forkHP :: Maybe HandlerPool -> Par d s () -> Par d s ()Source

A version of fork that also allows the forked computation to be tracked in a HandlerPool, that enables the programmer to synchronize on the completion of the child computation. But be careful; this does not automatically wait for all downstream forked computations (transitively).

Reexport IVar operations for a full, standard Par Monad API

Debug facilities and internal bits

logDbgLn :: Int -> String -> Par d s ()Source

Log a line of debugging output. This is only used when *compiled* in debugging mode. It atomically adds a string onto an in-memory log.

The provided Int, is the debug level associated with the message, 1-5. One is the least verbose, and five is the most. When debugging, the user can control the debug level by setting the env var DEBUG, e.g. DEBUG=5.

runParLogged :: (forall s. Par d s a) -> IO ([String], a)Source

Useful for debugging. Returns debugging logs, in realtime order, in addition to the final result.

runParDetailedSource

Arguments

:: DbgCfg

Debugging configuration

-> Int

How many worker threads to use.

-> (forall s. Par d s a)

The computation to run.

-> IO ([String], Either SomeException a) 

A variant with full control over the relevant knobs.

Returns a list of flushed debug messages at the end (if in-memory logging was enabled, otherwise the list is empty).

This version of runPar catches ALL exceptions that occur within the runPar, and returns them via an Either. The reason for this is that even if an error occurs, it is still useful to observe the log messages that lead to the failure.

data OutDest Source

A destination for log messages

Constructors

OutputEvents

Output via GHC's traceEvent runtime events.

OutputTo Handle

Printed human-readable output to a handle.

OutputInMemory

Accumulate output in memory and flush when appropriate.

data DbgCfg Source

Constructors

DbgCfg 

Fields

dbgRange :: Maybe (Int, Int)

Inclusive range of debug messages to accept (i.e. filter on priority level). If Nothing, use the default level, which is (0,N) where N is controlled by the DEBUG environment variable.

dbgDests :: [OutDest]

Destinations for debug log messages.

dbgScheduling :: Bool

In additional to logging debug messages, control thread interleaving at these points when this is True.

data LVar s all delt Source

The generic representation of LVars used by the scheduler. The end-user can't actually do anything with these and should not try to.