GHC/Data Parallel Haskell

From HaskellWiki
< GHC
Revision as of 05:46, 20 March 2007 by Chak (talk | contribs) (→‎Download)
Jump to navigation Jump to search

Data Parallel Haskell

Data Parallel Haskell is the codename for an extension to the Glasgow Haskell Compiler and its libraries to support nested data parallelism with a focus to utilise multi-core CPUs. Nested data parallelism extends the programming model of flat data parallelism, as known from parallel Fortran dialects, to irregular parallel computations (such as divide-and-conquer algorithms) and irregular data structures (such as sparse matrices and tree structures). An introduction to nested data parallelism in Haskell, including some examples, can be found in the paper Nepal -- Nested Data-Parallelism in Haskell.

Overview

The design, some implementation details, and first results of Data Parallel Haskell are described in the paper Data Parallel Haskell: a status report. The same topic is covered in the slides for the two talks Nested data parallelism in Haskell and Compiling nested data parallelism by program transformation.

Download

As we are still missing some components in the implementation of Data Parallel Haskell, you need to choose between the following two options:

Convenience without the speed
Nice surface syntax for parallel arrays and array comprehensions (very similar to that for Haskell lists) is available in all GHC releases of the 6.6 series. However, there are a number of bugs in version 6.6, so we recommend to use the development version of GHC, for the moment, and 6.6.1 as soon as it is released. To use parallel arrays, specify the option -fparr and import GHC.PArr. This is nice to implement and test parallel algorithms, but the code will be executed purely sequentially with limited performance. Further details are at convenience without the speed.
Speed without the convenience
Parallel high-performance arrays that use aggressive fusion and transparently utilise multicore and SMP architectures are available in the library package ndp. In contrast to the previous option, there is no special syntactic sugar for array types and array comprehensions, and only flat and segmented arrays of basic types and pairs are available. The library is only available in source form and needs to be compiled in a GHC build tree. However, this is pretty easy to do. The details are at speed without the convenience.

We are currently working to integrate these two components to finally provide convenience and speed in one.

Disclaimer: Data Parallel Haskell is very much work in progress. Some components are already usable, and we explain here how to use them. However, please be aware that APIs are still in flux and functionality may change during development.

Further information

For further reading, refer to this collection of background papers, and pointers to other people's work. If you are really curious and like to know implementation details and the internals of the Data Parallel Haskell project, it is all on the GHC developer wiki on the pages covering data parallelism and associated types.

Implementation of nested data parallelism in two stages

As Data Parallel Haskell is not fully implemented at this stage, use of the existing components requires some knowledge of the structure of the implementation, which essentially consists of two parts:

  1. A concurrent, high-performance library of strict, segmented arrays. In contrast to Haskell 98 arrays, these arrays are strict in that when one element of an array is evaluated, all of them are - we also call this a parallel evaluation semantics. Moreover, all operations come in two flavours: one for plain, flat arrays and one for segmented arrays, which are a particular representation of arrays with one level of nesting. For example, a sum of a segmented array of numbers computes one sum for each segment. The library has a purely functional interface, but internally uses monadic low-level array operations, array fusion, and a many standard GHC optimisations to produce highly optimised code. Finally, the library uses GHC's SMP concurrency to parallelise array processing on hardware with multiple processing elements.
  2. A vectorising program transformation (in the compiler) that maps nested array code (of arbitrary nesting depth) to code using segmented arrays. Nested parallel arrays are as convenient to use as finite, eagerly evaluated nested lists. Code vectorisation transforms a nested parallel array program such that it operates on the segmented arrays described before. The resulting code would be tedious to write manually, but is much more efficient than a direct implementation of nested arrays. (As segmented arrays correspond to arrays with one level of nesting, vectorisation collapses arbitrary nesting to one level of nesting.)

So far, we have implemented large parts of the concurrent array library (Part 1), but not the vectorisation transformation (Part 2). Hence, users must choose between the following two options: (1) The convenient programming model of arbitrarily nested, irregular array computations with a reasonably efficient, but not highly optimised and only purely sequential implementation. (2) An aggresively optimising, concurrent array library with a less expressive API of segmented (instead of nested) arrays, but which is still purely functional.

Convenience without the speed: nested arrays in Haskell

Any recent stable version of GHC (e.g., version 6.6) includes syntactic support for array comprehensions and a library of frequently used array operations. To use these, you need to pass GHC the command line option -fparr (to enable the extra syntax) and import the module GHC.PArr (a Prelude extension for arrays). (If you like to use parallel array comprehensions, you also need -fglasgow-exts.) For example, the following module implements a dot product using arrays:

{-# OPTIONS -fparr -fglasgow-exts #-}
module DotP (dotp)
where
import GHC.PArr

dotp :: Num a => [:a:] -> [:a:] -> a
dotp xs ys = sumP [:x * y | x <- xs | y <- ys:]

You can use this module in an interactive GHCi session as follows:

Prelude> :set -fparr -fglasgow-exts
Prelude> :load DotP
[1 of 1] Compiling DotP             ( code/haskell/DotP.hs, interpreted )
Ok, modules loaded: DotP.
*DotP> dotp [:1..3:] [:4..6:]
32
*DotP>

(NB: The :set is needed despite the OPTIONS pragma in DotP.hs, so that you can use array syntax on the interactive command line of GHCi.)

Unfortunately, the current version of Haddock does not grok the special array syntax, so there is no nice HTML version of the interface for GHC.PArr. Instead, please consult the source code of GHC.PArr.

Speed with less convenience: package ndp

The concurrent, high-performance library of strict, segmented arrays mentioned above takes the form of a GHC package called ndp. This package is under development and only available in source form. The simplest way to build it is to first get and build a source distribution of GHC (preferably the current development version) - see the docu on how to get the sources and how to build them. Then, in the source tree, do the following

% cd libraries
% darcs get http://darcs.haskell.org/packages/ndp/
% cd ndp
% make boot
% make

Now, the option -package ndp is available for use with the inplace compiler (i.e., compiler/ghc-inplace). Alternatively, you can install it by invoking make install on the GHC source root and within libraries/ndp/. Then, the option -package ndp can be used in the installed compiler.

For example, the following module implements the dot product with package ndp:

module DotP_ndp (dotp)
where

import Data.Array.Parallel.Unlifted

dotp :: (Num a, UA a) => UArr a -> UArr a -> a
dotp xs ys = sumU (zipWithU (*) xs ys)

We can also use that in an interactive GHCi session:

Prelude> :set -package ndp
package flags have changed, ressetting and loading new packages...
Loading package ndp-1.0 ... linking ... done.
Prelude> :l /home/chak/code/haskell/DotP_ndp
[1 of 1] Compiling DotP_ndp         ( /home/chak/code/haskell/DotP_ndp.hs, interpreted )
Ok, modules loaded: DotP_ndp.
*DotP_ndp> dotp (toU [1..3]) (toU [4..6])
Loading package haskell98 ... linking ... done.
32.0
*DotP_ndp>

The difference between the package ndp and the -fparr version of the dot product is just a fairly small amount of sugar. However, for programs using arrays of more complex (including nested arrays), the difference is much bigger. Nevertheless, many programs can be implemented quite easily with just package ndp. The speed difference between the two options is dramatic.

Most of the functions under Data.Array.Parallel.Unlifted are still purely sequential, albeit much more efficient than GHC.PArr. In addition, the (currently only few) functions from Data.Array.Parallel.Unlifted.Parallel transparently use multiple processing elements if GHC was compiled with SMP multiprocessor support.

A number of examples of using package ndp are in the examples directory.