dph-par-0.5.1.1: Data structures for Nested Data-Parallel Haskell.

Data.Array.Parallel.PArray

Contents

Description

Parallel Arrays.

Parallel arrays use a fixed generic representation. All data stored in them is converted to the generic representation, and we have a small number of operators that work on arrays of these generic types.

Representation types include Ints, Floats, Tuples and Sums, so arrays of these types can be stored directly. However, user defined algebraic data needs to be converted as we don't have operators that work directly on arrays of these types.

The top-level PArray type is built up from several type families and clases:

PArray - This is the top level type. It holds an array length, and array data in the generic representation (PData).

PRepr - Family of types that can be converted to the generic representation. We supply instances for basic types like Ints Floats etc, but the vectoriser needs to make the instances for user-defined data types itself. PA class - Contains methods to convert to and from the generic representation (PData).

PData - Family of types that can be stored directly in parallel arrays. We supply all the PData instances we need here in the library. PR class - Contains methods that work directly on parallel arrays. Most of these are just wrappers for the corresponding U.Array operators.

Scalar class - Contains methods to convert between the generic representation (PData) and plain U.Arrays.

Note that the PRepr family and PA class are related. so are the PData family and PR class.

For motivational material see: An Approach to Fast Arrays in Haskell, Chakravarty and Keller, 2003

For discussion of how the mapping to generic types works see: Instant Generics: Fast and Easy, Chakravarty, Ditu and Keller, 2009

Synopsis

Documentation

data PArray a Source

Lifted/bulk parallel arrays This contains the array length, along with the element data.

Instances

(PA a, Show a) => Show (PArray a) 
PR a => PR (PArray a) 
PA a => PA (PArray a) 

class PR (PRepr a) => PA a Source

A PA dictionary contains the functions that we use to convert a representable type to and from its generic representation. The conversion methods should all be O(1).

Instances

PA Bool 
PA Double 
PA Float 
PA Int 
PA Word8 
PA () 
PA Void 
PA a => PA (PArray a) 
(PA a, PA b) => PA (a, b) 
(PA a, PA b) => PA (:-> a b) 
(PA a, PA b, PA c) => PA (a, b, c) 
(PA a, PA b, PA c, PA d) => PA (a, b, c, d) 
(PA a, PA b, PA c, PA d, PA e) => PA (a, b, c, d, e) 

class Random a whereSource

Methods

randoms :: RandomGen g => Int -> g -> PArray aSource

randomRs :: RandomGen g => Int -> (a, a) -> g -> PArray aSource

Instances

Array operators.

length :: PA a => PArray a -> IntSource

O(1). Yield the length of an array.

empty :: PA a => PArray aSource

O(1). An empty array, with no elements.

replicate :: PA a => Int -> a -> PArray aSource

O(n). Produce an array containing copies of a given element.

singleton :: PA a => a -> PArray aSource

O(1). Produce an array containing a single element.

(!:) :: PA a => PArray a -> Int -> aSource

O(1). Retrieve a numbered element from an array.

zip :: (PA a, PA b) => PArray a -> PArray b -> PArray (a, b)Source

O(1). Takes two arrays and returns an array of corresponding pairs. If one array is short, excess elements of the longer array are discarded.

unzip :: (PA a, PA b) => PArray (a, b) -> (PArray a, PArray b)Source

O(1). Transform an array into an array of the first components, and an array of the second components.

pack :: PA a => PArray a -> PArray Bool -> PArray aSource

Select the elements of an array that have their tag set as True.

 packPA [12, 24, 42, 93] [True, False, False, True]
  = [24, 42]

concat :: PA a => PArray (PArray a) -> PArray aSource

Concatenate an array of arrays into a single array.

(+:+) :: PA a => PArray a -> PArray a -> PArray aSource

Append two arrays

indexed :: PA a => PArray a -> PArray (Int, a)Source

O(n). Tag each element of an array with its index.

indexed [42, 93, 13] = [(0, 42), (1, 93), (2, 13)]

slice :: PA a => Int -> Int -> PArray a -> PArray aSource

Extract a subrange of elements from an array. The first argument is the starting index, while the second is the length of the slice.

update :: PA a => PArray a -> PArray (Int, a) -> PArray aSource

Copy the source array in the destination, using new values for the given indices.

bpermute :: PA a => PArray a -> PArray Int -> PArray aSource

O(n). Backwards permutation of array elements.

bpermute [50, 60, 20, 30] [0, 3, 2]  = [50, 30, 20]

enumFromTo :: Int -> Int -> PArray IntSource

O(n). Generate a range of Ints.

Conversion

fromList :: PA a => [a] -> PArray aSource

Create a PArray from a list.

toList :: PA a => PArray a -> [a]Source

Create a list from a PArray.

fromUArrPA' :: Scalar a => Array a -> PArray aSource

Create a PArray out of a scalar U.Array, reading the length directly from the U.Array.

Evaluation

nf :: PA a => PArray a -> ()Source

Ensure an array is fully evaluated.