hdph-0.0.1: Haskell distributed parallel Haskell

Safe HaskellNone

Control.Parallel.HdpH

Contents

Synopsis

Documentation

HdpH (Haskell distributed parallel Haskell) is a Haskell DSL for shared- and distributed-memory parallelism, implemented entirely in Haskell (as supported by the GHC). HdpH is described in the following paper:

P. Maier, P. W. Trinder. Implementing a High-level Distributed-Memory Parallel Haskell in Haskell. IFL 2011.

HdpH executes programs written in a monadic embedded DSL for shared- and distributed-memory parallelism. HdpH operates a distributed runtime system, scheduling tasks either explicitly (controled by the DSL) or implicitly (by work stealing). The runtime system distinguishes between nodes and schedulers. A node is an OS process running HdpH (that is, a GHC-compiled executable built on top of the HdpH library), whereas a scheduler is a Haskell IO thread executing HdpH expressions (that is, Par monad computation). As a rule of thumb, a node should correspond to a machine in a network, and a scheduler should correspond to a core in a machine.

The semantics of HdpH was developed with fault tolerance in mind (though this version of HdpH is not yet fault tolerant). In particular, HdpH allows the replication computations, and the racing of computations against each other. The price to pay for these features is that HdpH cannot enforce determinism.

Par monad

Par is the monad for parallel computations in HdpH. It is a continuation monad, similar to the one described in paper A monad for deterministic parallelism by S. Marlow, R. Newton, S. Peyton Jones (Haskell 2011).

type Par = ParM RTSSource

Par is type constructor of kind *->* and an instance of classes Functor and Monad. Par is defined in terms of a parametric continuation monad ParM by plugging in RTS, the state monad of the runtime system. Since neither ParM nor RTS are exported, Par can be considered abstract.

runParIO_ :: RTSConf -> Par () -> IO ()Source

Eliminates the Par monad by executing the given parallel computation p, including setting up and initialising a distributed runtime system according to the configuration parameter conf. This function lives in the IO monad because p may be impure, for instance, p may exhibit non-determinism. Caveat: Though the computation p will only be started on a single root node, runParIO_ must be executed on every node of the distributed runtime system du to the SPMD nature of HdpH. Note that the configuration parameter conf applies to all nodes uniformly; at present there is no support for heterogeneous configurations.

runParIO :: RTSConf -> Par a -> IO (Maybe a)Source

Convenience: variant of runParIO_ which does return a result. Caveat: The result is only returned on the root node; all other nodes return Nothing.

Operations in the Par monad

These operations form the HdpH DSL, a low-level API of for parallel programming across shared- and distributed-memory architectures. For a more high-level API see module Control.Parallel.HdpH.Strategies.

done :: Par aSource

Terminates the current thread.

myNode :: Par NodeIdSource

Returns the node this operation is currently executed on.

allNodes :: Par [NodeId]Source

Returns a list of all nodes currently forming the distributed runtime system.

io :: IO a -> Par aSource

Lifts an IO action into the Par monad.

eval :: a -> Par aSource

Evaluates its argument to weak head normal form.

force :: NFData a => a -> Par aSource

Evaluates its argument to normal form (as defined by NFData instance).

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

Creates a new thread, to be executed on the current node.

spark :: Closure (Par ()) -> Par ()Source

Creates a spark, to be available for work stealing. The spark may be converted into a thread and executed locally, or it may be stolen by another node and executed there.

pushTo :: Closure (Par ()) -> NodeId -> Par ()Source

Pushes a computation to the given node, where it is eagerly converted into a thread and executed.

new :: Par (IVar a)Source

Creates a new empty IVar.

put :: IVar a -> a -> Par ()Source

Writes to given IVar (without forcing the value written).

get :: IVar a -> Par aSource

Reads from given IVar; blocks if the IVar is empty.

tryGet :: IVar a -> Par (Maybe a)Source

Reads from given IVar; does not block but returns Nothing if IVar empty.

probe :: IVar a -> Par BoolSource

Tests whether given IVar is empty or full; does not block.

glob :: IVar (Closure a) -> Par (GIVar (Closure a))Source

Globalises given IVar, returning a globally unique handle; this operation is restricted to IVars of Closure type.

rput :: GIVar (Closure a) -> Closure a -> Par ()Source

Writes to (possibly remote) IVar denoted by given global handle; this operation is restricted to write valueso of Closure type.

Locations

data NodeId Source

A NodeId identifies a node (that is, an OS process running HdpH). A NodeId should be thought of as an abstract identifier which instantiates the classes Eq, Ord, Show, NFData and Serialize.

Local and global IVars

data IVar a Source

An IVar is a write-once one place buffer. IVars are abstract; they can be accessed and manipulated only by the operations put, get, tryGet, probe and glob.

data GIVar a Source

A GIVar (short for global IVar) is a globally unique handle referring to an IVar. Unlike IVars, GIVars can be compared and serialised. They can also be written to remotely by the operation rput.

Instances

Eq (GIVar a) 
Ord (GIVar a) 
Show (GIVar a) 
Serialize (GIVar a) 
NFData (GIVar a) 

at :: GIVar a -> NodeIdSource

Returns the node hosting the IVar referred to by the given GIVar. This function being pure implies that IVars cannot migrate between nodes.

Explicit Closures

Runtime system configuration

This module's Static declaration

declareStatic :: StaticDeclSource

Static declaration of Static deserialisers used in explicit Closures created or imported by this module. This Static declaration must be imported by every main module using HdpH. The imported Static declaration must be combined with the main module's own Static declaration and registered; failure to do so may abort the program at runtime.