edenskel-2.1.0.0: Semi-explicit parallel programming skeleton library

Copyright(c) Philipps Universitaet Marburg 2009-2014
LicenseBSD-style (see the file LICENSE)
Maintainereden@mathematik.uni-marburg.de
Stabilitybeta
Portabilitynot portable
Safe HaskellNone
LanguageHaskell98

Control.Parallel.Eden.Workpool

Contents

Description

This Haskell module defines workpool skeletons for dynamic task distribution for the parallel functional language Eden.

Depends on GHC. Using standard GHC, you will get a threaded simulation of Eden. Use the forked GHC-Eden compiler from http://www.mathematik.uni-marburg.de/~eden for a parallel build.

Eden Group ( http://www.mathematik.uni-marburg.de/~eden )

Synopsis

Workpool skeletons with a single master

Simple workpool skeletons

The workpool skeletons use the non-deterministic merge function to achieve dynamic load balancing.

workpool Source

Arguments

:: (Trans t, Trans r) 
=> Int

number of child processes (workers)

-> Int

prefetch of tasks (for workers)

-> (t -> r)

worker function (mapped to tasks)

-> [t] 
-> [r]

what to do

Simple workpool (result list in non-deterministic order)

Notice: Result list in non-deterministic order.

workpoolSorted Source

Arguments

:: (Trans t, Trans r) 
=> Int

number of child processes (workers)

-> Int

prefetch of tasks (for workers)

-> (t -> r)

worker function (mapped to tasks)

-> [t]

tasks

-> [r]

results

Sorted workpool: Efficient implementation using a the distribution lookup list.

Notice: Results in the order of the tasks.

workpoolSortedNonBlock Source

Arguments

:: (Trans t, Trans r) 
=> Int

number of child processes (workers)

-> Int

prefetch of tasks (for workers)

-> (t -> r)

worker function (mapped to tasks)

-> [t] 
-> [r]

what to do

Non-blocking sorted workpool (results in the order of the tasks). Result list is structurally defined up to the position where tasks are distributed, independent of the received worker results. This version needs still performance testing. This version takes places for instantiation.

Notice: Results in the order of the tasks.

workpoolReduce Source

Arguments

:: (Trans t, Trans r, Trans r') 
=> Int

number of child processes (workers)

-> Int

prefetch of tasks (for workers)

-> (r' -> r -> r)

reduce function

-> r

neutral for reduce function

-> (t -> r')

worker function (mapped to tasks)

-> [t]

tasks

-> [r]

results (one from each worker)

Simple workpool with additional reduce function for worker outputs. This version takes places for instantiation.

Notice: Result list in non-deterministic order.

Simple workpool skeletons - versions using explicit placement

The workpool skeletons use the non-deterministic merge function to achieve dynamic load balancing.

workpoolAt Source

Arguments

:: (Trans t, Trans r) 
=> Places 
-> Int

number of child processes (workers)

-> Int

prefetch of tasks (for workers)

-> (t -> r)

worker function (mapped to tasks)

-> [t] 
-> [r]

what to do

Simple workpool (result list in non-deterministic order) This version takes places for instantiation.

Notice: Result list in non-deterministic order.

workpoolSortedAt Source

Arguments

:: (Trans t, Trans r) 
=> Places 
-> Int

number of child processes (workers)

-> Int

prefetch of tasks (for workers)

-> (t -> r)

worker function

-> [t]

tasks

-> [r]

results

Sorted workpool (results in the order of the tasks). This version takes places for instantiation.

workpoolSortedNonBlockAt Source

Arguments

:: (Trans t, Trans r) 
=> Places 
-> Int

number of child processes (workers)

-> Int

prefetch of tasks (for workers)

-> (t -> r)

worker function (mapped to tasks)

-> [t] 
-> [r]

what to do

Non-blocking sorted workpool. Result list is structurally defined up to the position where tasks are distributed, independent of the received worker results. This version needs still performance testing.

Notice: Results in the order of the tasks.

workpoolReduceAt Source

Arguments

:: (Trans t, Trans r, Trans r') 
=> Places 
-> Int

number of child processes (workers)

-> Int

prefetch of tasks (for workers)

-> (r' -> r -> r)

reduce function

-> r

neutral for reduce function

-> (t -> r')

worker function (mapped to tasks)

-> [t]

tasks

-> [r]

results (one from each worker)

Simple workpool with additional reduce function for worker outputs. This version takes places for instantiation.

Notice: Result list in non-deterministic order.

workpoolAuxAt Source

Arguments

:: (Trans t, Trans r) 
=> Places 
-> Int

number of child processes (workers)

-> Int

prefetch of tasks (for workers)

-> (t -> r)

worker function (tasks to results mapping)

-> [t]

tasks

-> ([Int], [[Int]], [[r]])

(input distribution (input i is in sub-list distribs!i), task positions (element i of result-sub-list j was in the input list at (poss!j)!i ), result streams of workers)

Workpool version with one result stream for each worker and meta information about the task distribution. This meta-skeleton can be used to define workpool-skeletons which can reestablish the result list order.

Notice: Result list in non-deterministic order.

Hierarchical workpool skeleton

These skeletons can be nested with an arbitrary number of submaster levels to unload the top master.

wpNested Source

Arguments

:: (Trans t, Trans r) 
=> [Int]

branching degrees: the i-th element defines the branching degree of for the i-th level of the WP-hierarchy. Use a singleton list for a flat MW-Skeleton.

-> [Int]

Prefetches for the sub-master/worker levels

-> (t -> r)

worker function

-> [t]

initial tasks

-> [r]

results

Hierachical WP-Skeleton. The worker function is mapped to the worker input stream (list type). A worker produces a result. The workers are located on the leaves of a WP-hierarchy, in the intermediate levels are submasters which unload the master by streaming result streams of their child processes into a single result stream.

Notice: Result list in non-deterministic order.

Hierarchical workpool skeleton with dynamic task creation

The worker function is extended such that dynamic creation of new tasks is possible. New tasks are added to the end of the task list, thus tasks are traversed breath first (not strictly because of the skeletons' nondeterminism). Furthermore, these skeletons can be nested with an arbitrary number of submaster levels to unload the top master.

wpDynNested Source

Arguments

:: (Trans t, Trans r) 
=> [Int]

branching degrees: the i-th element defines the branching degree of for the i-th level of the MW-hierarchy. Use a singleton list for a flat MW-Skeleton.

-> [Int]

Prefetches for the sub-master/worker levels

-> (t -> (r, [t]))

worker function - produces a tuple of result and new tasks for the processed task

-> [t]

initial tasks

-> [r]

results

Hierachical WP-Skeleton with dynamic task creation. The worker function is mapped to the worker input stream (list type). A worker produces a tuple of result and dynamicly created tasks for each processed task. The workers are located on the leaves of a WP-hierarchy, in the intermediate levels are submasters which unload the master by streamlining 'result/newtask' streams of their child processes into a single result/newtask stream. Furthermore, the submasters retain locally half of the tasks which are dynamically created by the workers in their subtree.

Notice: Result list in non-deterministic order.

wpDNI Source

Arguments

:: (Trans t, Trans r) 
=> Int

number of processes (submasters and workers)

-> Int

nesting depth

-> Int

branching degree of the first submaster level (further submaster levels are branched binary)

-> Int

task prefetch for the workers

-> (t -> (r, [t]))

worker function - produces a tuple of result and tasks for the processed task

-> [t]

initial tasks

-> [r]

results

Simple interface for wpDynNested. Parameters are the number of child processes, the first level branching degree, the nesting depth (use 1 for a single master), and the task prefetch amount for the worker level. All processes that are not needed for the submasters are used for the workers. If the number of submasters in the last level and the number of remaining child processes are prime to each other, then the next larger divisor is chosen for the number of workers.

Notice: Result list in non-deterministic order.

Distributed workpool skeletons with state and dynamic task creation

distribWPAt Source

Arguments

:: (Trans onT, Trans t, Trans r, Trans s, NFData r') 
=> Places

where to put workers

-> ((t, s) -> (Maybe (r', s), [t]))

worker function

-> (Maybe ofT -> Maybe onT -> [t])

input transformation (e.g. (fetch . fromJust . snd) for online input of type [RD[t]])

-> ([Maybe (r', s)] -> s -> r)

result transformation (prior to release results in the workers)

-> ([t] -> [t] -> s -> [t])

taskpool transform attach function

-> ([t] -> s -> ([t], Maybe (t, s)))

taskpool transform detach function (local request)

-> ([t] -> s -> ([t], [t]))

taskpool transform split function (remote request)

-> (s -> s -> Bool)

state comparison (checks if new state is better than old state)

-> s

initial state (offline input)

-> [ofT]

offline input (if non empty, outer list defines the number of workers, else the shorter list does)

-> [onT]

dynamic input (if non empty, outer list defines the number of workers, else the shorter list does)

-> [r]

results of workers

A distributed workpool skeleton that uses task generation and a global state (s) with a total order. Split and Detatch policy must give tasks away (may not produce empty lists), unless all tasks are pruned!

Deprecated skeletons

masterWorker :: (Trans a, Trans b) => Int -> Int -> (a -> b) -> [a] -> [b] Source

Deprecated: better use workpoolSortedNonBlock instead

Deprecated, same as workpoolSortedNonBlock

mwNested :: forall t r. (Trans t, Trans r) => [Int] -> [Int] -> (t -> r) -> [t] -> [r] Source

Deprecated: better use wpNested instead

Deprecated, same as wpNested

mwDynNested :: forall t r. (Trans t, Trans r) => [Int] -> [Int] -> (t -> (r, [t])) -> [t] -> [r] Source

Deprecated: better use wpDynNested instead

Deprecated, same as wpDynNested

mwDNI :: (Trans t, Trans r) => Int -> Int -> Int -> Int -> (t -> (r, [t])) -> [t] -> [r] Source

Deprecated: better use wpDNI instead

Deprecated, same as wpDNI