dph-lifted-copy-0.7.0.1: Data Parallel Haskell lifted array combinators. (deprecated version)

Safe HaskellNone

Data.Array.Parallel.PArray

Contents

Description

Parallel Arrays.

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) 
(PR (PRepr (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 
(PR (PRepr (PArray a)), PA a) => PA (PArray a) 
(PR (PRepr (a, b)), PA a, PA b) => PA (a, b) 
(PR (PRepr (:-> a b)), PA a, PA b) => PA (:-> a b) 
(PR (PRepr (a, b, c)), PA a, PA b, PA c) => PA (a, b, c) 
(PR (PRepr (a, b, c, d)), PA a, PA b, PA c, PA d) => PA (a, b, c, d) 
(PR (PRepr (a, b, c, d, e)), PA a, PA b, PA c, PA d, PA e) => PA (a, b, c, d, e) 
(PR (PRepr (a, b, c, d, e, f)), PA a, PA b, PA c, PA d, PA e, PA f) => PA (a, b, c, d, e, f) 
(PR (PRepr (a, b, c, d, e, f, g)), PA a, PA b, PA c, PA d, PA e, PA f, PA g) => PA (a, b, c, d, e, f, g) 
(PR (PRepr (a, b, c, d, e, f, g, h)), PA a, PA b, PA c, PA d, PA e, PA f, PA g, PA h) => PA (a, b, c, d, e, f, g, h) 
(PR (PRepr (a, b, c, d, e, f, g, h, i)), PA a, PA b, PA c, PA d, PA e, PA f, PA g, PA h, PA i) => PA (a, b, c, d, e, f, g, h, i) 
(PR (PRepr (a, b, c, d, e, f, g, h, i, j)), PA a, PA b, PA c, PA d, PA e, PA f, PA g, PA h, PA i, PA j) => PA (a, b, c, d, e, f, g, h, i, j) 
(PR (PRepr (a, b, c, d, e, f, g, h, i, j, k)), PA a, PA b, PA c, PA d, PA e, PA f, PA g, PA h, PA i, PA j, PA k) => PA (a, b, c, d, e, f, g, h, i, j, k) 
(PR (PRepr (a, b, c, d, e, f, g, h, i, j, k, l)), PA a, PA b, PA c, PA d, PA e, PA f, PA g, PA h, PA i, PA j, PA k, PA l) => PA (a, b, c, d, e, f, g, h, i, j, k, l) 
(PR (PRepr (a, b, c, d, e, f, g, h, i, j, k, l, m)), PA a, PA b, PA c, PA d, PA e, PA f, PA g, PA h, PA i, PA j, PA k, PA l, PA m) => PA (a, b, c, d, e, f, g, h, i, j, k, l, m) 
(PR (PRepr (a, b, c, d, e, f, g, h, i, j, k, l, m, n)), PA a, PA b, PA c, PA d, PA e, PA f, PA g, PA h, PA i, PA j, PA k, PA l, PA m, PA n) => PA (a, b, c, d, e, f, g, h, i, j, k, l, m, n) 
(PR (PRepr (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)), PA a, PA b, PA c, PA d, PA e, PA f, PA g, PA h, PA i, PA j, PA k, PA l, PA m, PA n, PA o) => PA (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) 

class Random a whereSource

Methods

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

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

Instances

Evaluation

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

Ensure an array is fully evaluated.

Constructors

empty :: PA a => PArray aSource

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

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

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

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

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

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

Append two arrays

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

Concatenate an array of arrays into a single array.

nestUSegdSource

Arguments

:: Segd

segment descriptor

-> PArray a

array of data elements.

-> PArray (PArray a) 

O(1). Create a nested array.

Projections

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

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

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

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

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

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

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

Pack and Combine

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]

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]

Enumerations

enumFromTo :: Int -> Int -> PArray IntSource

O(n). Generate a range of Ints.

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)]

Tuples

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.

Conversions

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.

fromUArray :: Scalar a => Array a -> PArray aSource

Create a PArray out of a scalar U.Array, the first argument is the array length.

TODO: ditch this version, just use fromUArrPA'

toUArray :: Scalar a => PArray a -> Array aSource

Convert a PArray back to a plain U.Array.

fromUArray2 :: (Scalar a, Scalar b) => Array (a, b) -> PArray (a, b)Source

Convert an U.Array of pairs to a PArray.

fromUArray3 :: (Scalar a, Scalar b, Scalar c) => Array ((a, b), c) -> PArray (a, b, c)Source

Convert a U.Array of triples to a PArray.