meta-par-0.3: Provides the monad-par interface, but based on modular scheduler "mix-ins".

Safe HaskellNone

Control.Monad.Par.Meta

Contents

Synopsis

Core Meta-Par types

data Par a Source

The Meta-Par monad with its full suite of instances. Note that the MonadIO instance, while essential for building new Resources, is unsafe in client code when combined with runMetaPar. This type should therefore be exposed to client code as a newtype that omits the MonadIO instance.

data IVar a Source

An IVar is a write-once, read-many structure for communication between Par threads.

Operations

class Monad m => ParFuture future m | m -> future where

ParFuture captures the class of Par monads which support futures. This level of functionality subsumes par/pseq and is similar to the Control.Parallel.Strategies.Eval monad.

A minimal implementation consists of spawn_ and get. However, for monads that are also a member of ParIVar it is typical to simply define spawn in terms of fork, new, and put.

Methods

spawn :: NFData a => m a -> m (future a)

Create a potentially-parallel computation, and return a future (or promise) that can be used to query the result of the forked computataion.

  spawn p = do
    r <- new
    fork (p >>= put r)
    return r

spawn_ :: m a -> m (future a)

Like spawn, but the result is only head-strict, not fully-strict.

get :: future a -> m a

spawnP :: NFData a => a -> m (future a)

Spawn a pure (rather than monadic) computation. Fully-strict.

  spawnP = spawn . return

class ParFuture ivar m => ParIVar ivar m | m -> ivar where

ParIVar builds on futures by adding full anyone-writes, anyone-reads IVars. These are more expressive but may not be supported by all distributed schedulers.

A minimal implementation consists of fork, put_, and new.

Methods

fork :: m () -> m ()

Forks a computation to happen in parallel. The forked computation may exchange values with other computations using IVars.

new :: m (ivar a)

creates a new IVar

put :: NFData a => ivar a -> a -> m ()

put a value into a IVar. Multiple puts to the same IVar are not allowed, and result in a runtime error.

put fully evaluates its argument, which therefore must be an instance of NFData. The idea is that this forces the work to happen when we expect it, rather than being passed to the consumer of the IVar and performed later, which often results in less parallelism than expected.

Sometimes partial strictness is more appropriate: see put_.

put_ :: ivar a -> a -> m ()

like put, but only head-strict rather than fully-strict.

newFull :: NFData a => a -> m (ivar a)

creates a new IVar that contains a value

newFull_ :: a -> m (ivar a)

creates a new IVar that contains a value (head-strict only)

Entrypoints

runMetaPar :: Resource -> Par a -> aSource

Run a Par computation, and return its result as a pure value. If the choice of Resource introduces non-determinism, use runMetaParIO instead, as non-deterministic computations are not referentially-transparent.

runMetaParIO :: Resource -> Par a -> IO aSource

Run a Par computation in the IO monad, allowing non-deterministic Meta-Par variants to be safely executed.

Implementation API

data Sched Source

Constructors

Sched 

Fields

no :: !Int

Capability number

tids :: HotVar (Set ThreadId)

The ThreadIds of all worker threads on this capability

workpool :: WSDeque (Par ())

The local WSDeque for this worker. The worker may push and pop from the left of its own workpool, but workers on other threads may only steal from the right.

rng :: HotVar GenIO

A GenIO for random work stealing.

mortals :: HotVar Int

A counter of how many extra workers are working on this capability. This situation arises during nested calls to runMetaPar, and the worker loop kills workers as necessary to keep this value at 1.

consecutiveFailures :: IORef Int

Tracks the number of consecutive times this worker has invoked a WorkSearch and received Nothing. This is used to implement backoff in Backoff.

ivarUID :: HotVar Int

A per-thread source of unique identifiers for IVars. Multiply this value by getNumCapabilities and add no for uniqueness.

schedWs :: WorkSearch

The WorkSearch of this worker's associated Resource.

type GlobalState = Vector (Maybe Sched)Source

A GlobalState structure tracks the state of all Meta-Par workers in a program in a Vector indexed by capability number.

Execution Resources

data Resource Source

A Resource provides an abstraction of heterogeneous execution resources, and may be combined using Monoid operations. Composition of resources is left-biased; for example, if resource1 always returns work from its WorkSearch, the composed resource resource1 mappend resource2 will never request work from resource2.

Constructors

Resource 

newtype Startup Source

The Startup component of a Resource is a callback that implements initialization behavior. For example, the SMP Startup calls spawnWorkerOnCPU a number of times. The arguments to Startup are the combined Resource of the current scheduler and a thread-safe reference to the GlobalState.

Constructors

St 

newtype WorkSearch Source

The WorkSearch component of a Resource is a callback that responds to requests for work from Meta-Par workers. The arguments to WorkSearch are the Sched for the current thread and a thread-safe reference to the GlobalState.

Constructors

WS 

Fields

runWS :: Sched -> HotVar GlobalState -> IO (Maybe (Par ()))
 

Utilities

forkWithExceptionsSource

Arguments

:: (IO () -> IO ThreadId)

The basic forkOn implementation

-> String

A name for the child thread in error messages

-> IO () -> IO ThreadId 

Produces a variant of forkOn that allows exceptions from child threads to propagate up to the parent thread.

spawnWorkerOnCPUSource

Arguments

:: WorkSearch

The WorkSearch called by the new worker

-> Int

Capability

-> IO ThreadId 

Spawn a Meta-Par worker that will stay on a given capability.

Note: this does not check whether workers already exist on the capability, and should be called appropriately. In particular, it is the caller's responsibility to manage things like the mortal count of the given capability.