| Safe Haskell | Safe-Infered | 
|---|
Control.Monad.Par.Class
Description
This module establishes a class hierarchy that captures the interface(s) for valid Par monads. In particular, the functionality is split into layers: e.g. Futures vs. full IVars vs. Chans (Streams).
Not all Par monad schedulers must provide all functionality.
For more documentation of the programming model, see
-  The Control.Monad.Par module in the monad-parpackage. * The wikitutorial (<http:www.haskell.orghaskellwiki/Par_Monad:_A_Parallelism_Tutorial>) * The original paper (http://www.cs.indiana.edu/~rrnewton/papers/haskell2011_monad-par.pdf) * Tutorial slides (http://community.haskell.org/~simonmar/slides/CUFP.pdf) * Other slides: http://www.cs.ox.ac.uk/ralf.hinze/WG2.8/28/slides/simon.pdf, http://www.cs.indiana.edu/~rrnewton/talks/2011_HaskellSymposium_ParMonad.pdf
Futures
class Monad m => ParFuture future m | m -> future whereSource
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)Source
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)Source
Like spawn, but the result is only head-strict, not fully-strict.
spawnP :: NFData a => a -> m (future a)Source
Spawn a pure (rather than monadic) computation. Fully-strict.
spawnP = spawn . return
IVars
class ParFuture ivar m => ParIVar ivar m | m -> ivar whereSource
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.
Methods
Forks a computation to happen in parallel.  The forked
 computation may exchange values with other computations using
 IVars.
creates a new IVar
put :: NFData a => ivar a -> a -> m ()Source
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 ()Source
like put, but only head-strict rather than fully-strict.  
newFull :: NFData a => a -> m (ivar a)Source
creates a new IVar that contains a value
newFull_ :: a -> m (ivar a)Source
creates a new IVar that contains a value (head-strict only)
class NFData a
A class of types that can be fully evaluated.
Instances
| NFData Bool | |
| NFData Char | |
| NFData Double | |
| NFData Float | |
| NFData Int | |
| NFData Int8 | |
| NFData Int16 | |
| NFData Int32 | |
| NFData Int64 | |
| NFData Integer | |
| NFData Word | |
| NFData Word8 | |
| NFData Word16 | |
| NFData Word32 | |
| NFData Word64 | |
| NFData () | |
| NFData Version | |
| NFData a => NFData [a] | |
| (Integral a, NFData a) => NFData (Ratio a) | |
| NFData (Fixed a) | |
| (RealFloat a, NFData a) => NFData (Complex a) | |
| NFData a => NFData (Maybe a) | |
| NFData (a -> b) | This instance is for convenience and consistency with  | 
| (NFData a, NFData b) => NFData (Either a b) | |
| (NFData a, NFData b) => NFData (a, b) | |
| (Ix a, NFData a, NFData b) => NFData (Array a b) | |
| (NFData a, NFData b, NFData c) => NFData (a, b, c) | |
| (NFData a, NFData b, NFData c, NFData d) => NFData (a, b, c, d) | |
| (NFData a1, NFData a2, NFData a3, NFData a4, NFData a5) => NFData (a1, a2, a3, a4, a5) | |
| (NFData a1, NFData a2, NFData a3, NFData a4, NFData a5, NFData a6) => NFData (a1, a2, a3, a4, a5, a6) | |
| (NFData a1, NFData a2, NFData a3, NFData a4, NFData a5, NFData a6, NFData a7) => NFData (a1, a2, a3, a4, a5, a6, a7) | |
| (NFData a1, NFData a2, NFData a3, NFData a4, NFData a5, NFData a6, NFData a7, NFData a8) => NFData (a1, a2, a3, a4, a5, a6, a7, a8) | |
| (NFData a1, NFData a2, NFData a3, NFData a4, NFData a5, NFData a6, NFData a7, NFData a8, NFData a9) => NFData (a1, a2, a3, a4, a5, a6, a7, a8, a9) |