dph-prim-interface-0.5.1.1: Backend Interface for Data Parallel Haskell

Data.Array.Parallel.Unlifted

Contents

Description

This module provides the API for the DPH backend.

These are the DPH array primitives that the vectoriser introduces when transforming code. The actual code in this module is fake, in the sense that is provides a partial reference implementation using lists to represent arrays, but this code isn't acually used at runtime.

The actual code used by compiled programs depends on whether -fdph-par or -fdph-seq is passed when compiling it. Depending on the flag, the implementation in either the dph-prim-par or dph-prim-seq packages is swapped in. These packages export the same API, but use a more efficient, and perhaps parallel implementation.

All three packages are forced to use the same API by the DPH_Header.h and DPH_Interface.h include files in dph-prim-interface/interface.

Synopsis

Basics

class Elt a Source

Instances

Elt Bool 
Elt Double 
Elt Float 
Elt Int 
Elt Word8 
Elt a => Elt [a] 
(Elt a, Elt b) => Elt (a, b) 

type Array a = [a]Source

length :: Elt a => Array a -> IntSource

O(1). Take the number of elements in an array.

Constructors

empty :: Elt a => Array aSource

An array with no elements.

(+:+) :: Elt a => Array a -> Array a -> Array aSource

O(n). Append two arrays.

generate :: Elt a => Int -> (Int -> a) -> Array aSource

Generate a new array given its length and a function to compute each element.

replicate :: Elt a => Int -> a -> Array aSource

O(n). Produce a new array by replicating a single element the given number of times.

repeatSource

Arguments

:: Elt a 
=> Int

number of times to repeat the source

-> Int

length of source (can be less than the provided array)

-> Array a

array elements to repeat

-> Array a 

Produce an array by copying a portion of another array.

indexed :: Elt a => Array a -> Array (Int, a)Source

Tag each element of an array with its index.

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

enumFromTo :: Int -> Int -> Array IntSource

Generate a range of Ints.

Projections

(!:) :: Elt a => Array a -> Int -> aSource

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

extractSource

Arguments

:: Elt a 
=> Array a

source array

-> Int

starting index in source array

-> Int

length of result array

-> Array a 

O(n). Extract a subrange of elements from an array. Example: extract [:23, 42, 93, 50, 27:] 1 3 = [:42, 93, 50:]

drop :: Elt a => Int -> Array a -> Array aSource

O(n). Drop some elements from the front of an array, returning the latter portion.

filter :: Elt a => (a -> Bool) -> Array a -> Array aSource

Extract the elements from an array that match the given predicate.

Permutation

permuteSource

Arguments

:: Elt a 
=> Array a

source array

-> Array Int

indices in the destination to copy elements to

-> Array a 

O(n). Forwards permutation of array elements.

bpermuteSource

Arguments

:: Elt a 
=> Array a

source array

-> Array Int

indices in the source to copy elements from.

-> Array a 

O(n). Backwards permutation of array elements.

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

mbpermute :: (Elt a, Elt b) => (a -> b) -> Array a -> Array Int -> Array bSource

Combination of map and bpermute.

The advantage of using this combined version is that we dont need to apply the parameter function to source elements that dont appear in the result.

bpermuteDft :: Elt e => Int -> (Int -> e) -> Array (Int, e) -> Array eSource

Default backwards permutation.

  • The values of the index-value pairs are written into the position in the result array that is indicated by the corresponding index.
  • All positions not covered by the index-value pairs will have the value determined by the initialiser function for that index position.

Update

update :: Elt a => Array a -> Array (Int, a) -> Array aSource

O(n). Copy the source array in the destination, using new values for the given indices.

Packing and Combining

pack :: Elt a => Array a -> Array Bool -> Array aSource

Extract elements of an array where the associated flag is true.

combine :: Elt a => Array Bool -> Array a -> Array a -> Array aSource

Combine two arrays, using a tag array to tell us where to get each element from.

Example: combine [T,F,F,T,T,F] [1,2,3] [4,5,6] = [1,4,5,2,3,6]

combine2 :: Elt a => Array Tag -> SelRep2 -> Array a -> Array a -> Array aSource

Like combine, but use a precomputed selector to speed up the process.

See dph-prim-seq:Data.Array.Parallel.Unlifted.Sequential.Segmented.USel for a description of how this works.

interleave :: Elt a => Array a -> Array a -> Array aSource

Interleave the elements of two arrays.

Example: interleave [1,2,3] [4,5,6] = [1,4,2,5,3,6]

Map and ZipWith

map :: (Elt a, Elt b) => (a -> b) -> Array a -> Array bSource

Apply a worker function to each element of an array, yielding a new array.

zipWith :: (Elt a, Elt b, Elt c) => (a -> b -> c) -> Array a -> Array b -> Array cSource

zipWith generalises zip by zipping with the function given as the first argument, instead of a tupling function.

zipWith3 :: (Elt a, Elt b, Elt c, Elt d) => (a -> b -> c -> d) -> Array a -> Array b -> Array c -> Array dSource

zipWith4 :: (Elt a, Elt b, Elt c, Elt d, Elt e) => (a -> b -> c -> d -> e) -> Array a -> Array b -> Array c -> Array d -> Array eSource

Zipping and Unzipping

zip :: (Elt a, Elt b) => Array a -> Array b -> Array (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 :: (Elt a, Elt b) => Array (a, b) -> (Array a, Array b)Source

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

fsts :: (Elt a, Elt b) => Array (a, b) -> Array aSource

O(1). Take the first elements of an array of pairs.

snds :: (Elt a, Elt b) => Array (a, b) -> Array bSource

O(1). Take the second elements of an array of pairs.

Folds

fold :: Elt a => (a -> a -> a) -> a -> Array a -> aSource

Left fold over an array.

fold1 :: Elt a => (a -> a -> a) -> Array a -> aSource

Left fold over an array, using the first element to initialise the state.

and :: Array Bool -> BoolSource

Compute the conjunction of all elements in a boolean array.

sum :: (Num a, Elt a) => Array a -> aSource

Compute the sum of an array of numbers.

scan :: Elt a => (a -> a -> a) -> a -> Array a -> Array aSource

Similar to foldl but return an array of the intermediate states, including the final state that is computed by foldl.

Segmented Constructors

append_sSource

Arguments

:: Elt a 
=> Segd

segment descriptor of result aarray

-> Segd

segment descriptor of first array

-> Array a

data of first array

-> Segd

segment descriptor of second array

-> Array a

data of first array

-> Array a 

Segmented Folds

fold_s :: Elt a => (a -> a -> a) -> a -> Segd -> Array a -> Array aSource

fold1_s :: Elt a => (a -> a -> a) -> Segd -> Array a -> Array aSource

fold_r :: Elt a => (a -> a -> a) -> a -> Int -> Array a -> Array aSource

sum_s :: (Num a, Elt a) => Segd -> Array a -> Array aSource

sum_r :: (Num a, Elt a) => Int -> Array a -> Array aSource

Segment Descriptors

Selectors

mkSel2Source

Arguments

:: Array Tag

tags array

-> Array Int

indices array

-> Int

number of elements taken from first source array

-> Int

number of elements taken from second source array

-> SelRep2 
-> Sel2 

O(1). Construct a selector. Selectors are used to speed up the combine2 operation.

See dph-prim-seq:Data.Array.Parallel.Unlifted.Sequential.Segmented.USel for a description of how this works.

tagsSel2 :: Sel2 -> Array TagSource

O(1). Get the tags array of a selector.

indicesSel2 :: Sel2 -> Array IntSource

O(1). Get the indices array of a selector.

elementsSel2_0 :: Sel2 -> IntSource

O(1). Get the number of elements that will be taken from the first array.

elementsSel2_1 :: Sel2 -> IntSource

O(1). Get the number of elements that will be taken from the second array.

repSel2 :: Sel2 -> SelRep2Source

tagsToSel2 :: Array Tag -> Sel2Source

O(n), Compute a selector from a tags array.

mkSelRep2 :: Array Tag -> SelRep2Source

Packing and picking

packByTagSource

Arguments

:: Elt a 
=> Array a

data values

-> Array Tag

tag values

-> Tag

the tag of values to select

-> Array a

data values that had that tag

Select the elements of an array that have a corresponding tag.

 packByTag [12, 24, 42, 93] [1, 0, 0, 1] 0
  = [24, 42]

pick :: (Elt a, Eq a) => Array a -> a -> Array BoolSource

Counting

count :: (Elt a, Eq a) => Array a -> a -> IntSource

Count the number of elements in array that are equal to the given value.

count_s :: (Elt a, Eq a) => Segd -> Array a -> a -> Array IntSource

Count the number of elements in segments that are equal to the given value.

Random arrays

randoms :: (Elt a, Random a, RandomGen g) => Int -> g -> Array aSource

randomRs :: (Elt a, Random a, RandomGen g) => Int -> (a, a) -> g -> Array aSource

Array IO

class Elt a => IOElt a Source

Instances

IOElt Double 
IOElt Int 
(IOElt a, IOElt b) => IOElt (a, b) 

hGet :: IOElt a => Handle -> IO (Array a)Source

Read an array from a file.

hPut :: IOElt a => Handle -> Array a -> IO ()Source

Write an array to a file.

toList :: Elt a => Array a -> [a]Source

Convert an array to a list of elements.

fromList :: Elt a => [a] -> Array aSource

Convert a list of elements to an array.