Safe Haskell | None |
---|
- data Par a
- data IVar a
- class Monad m => ParFuture future m | m -> future where
- class ParFuture ivar m => ParIVar ivar m | m -> ivar where
- runMetaPar :: Resource -> Par a -> a
- runMetaParIO :: Resource -> Par a -> IO a
- data Sched = Sched {}
- type GlobalState = Vector (Maybe Sched)
- data Resource = Resource {}
- newtype Startup = St {
- runSt :: WorkSearch -> HotVar GlobalState -> IO ()
- newtype WorkSearch = WS {}
- forkWithExceptions :: (IO () -> IO ThreadId) -> String -> IO () -> IO ThreadId
- spawnWorkerOnCPU :: WorkSearch -> Int -> IO ThreadId
Core Meta-Par types
The Meta-Par monad with its full suite of instances. Note that
the MonadIO
instance, while essential for building new
Resource
s, 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.
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
.
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.
fork :: m () -> m ()
Forks a computation to happen in parallel. The forked
computation may exchange values with other computations using
IVar
s.
new :: m (ivar a)
creates a new IVar
put :: NFData a => ivar a -> a -> m ()
put a value into a IVar
. Multiple put
s 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
Implementation API
Sched | |
|
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
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
will never
request work from mappend
resource2resource2
.
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
.
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
.
Utilities
:: (IO () -> IO ThreadId) | The basic |
-> 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.
:: WorkSearch | The |
-> 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.