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

Data.Array.Parallel.Lifted

Synopsis

Documentation

data PArray a Source

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

Constructors

PArray Int# (PData a) 

Instances

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

data family PData a Source

Parallel Data. This is the family of types that store parallel array data.

PData takes the type of an element and produces the type we use to store an array of those elements. The instances for PData use an efficient representation that depends on the type of elements being stored. For example, an array of pairs is stored as two separate arrays, one for each element type. This lets us avoid storing the intermediate Pair/Tuple constructors and the pointers to the elements.

Most of the instances are defined in Data.Array.Parallel.PArray.Instances, though the instances for function closures are defined in their own module, Data.Array.Parallel.Lifted.Closure.

Note that PData is just a flat chunk of memory containing elements, and doesn't include a field giving the length of the array. We use PArray when we want to pass around the array data along with its length.

class PR (PRepr a) => PA a whereSource

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) 

lengthPA# :: PArray a -> Int#Source

Take the length field of a PArray.

dataPA# :: PArray a -> PData aSource

Take the data field of a PArray.

replicatePA# :: PA a => Int# -> a -> PArray aSource

repeatPA# :: PA a => Int# -> PArray a -> PArray aSource

indexPA# :: PA a => PArray a -> Int# -> aSource

extractPA# :: PA a => PArray a -> Int# -> Int# -> PArray aSource

appPA# :: PA a => PArray a -> PArray a -> PArray aSource

applPA# :: PA a => Segd -> Segd -> PArray a -> Segd -> PArray a -> PArray aSource

combine2PA# :: PA a => Int# -> Sel2 -> PArray a -> PArray a -> PArray aSource

updatePA# :: PA a => PArray a -> Array Int -> PArray a -> PArray aSource

fromListPA# :: PA a => Int# -> [a] -> PArray aSource

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

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

replicatePD :: PA a => T_replicatePR aSource

replicatelPD :: PA a => T_replicatelPR aSource

repeatPD :: PA a => T_repeatPR aSource

emptyPD :: PA a => T_emptyPR aSource

indexPD :: PA a => T_indexPR aSource

extractPD :: PA a => T_extractPR aSource

bpermutePD :: PA a => T_bpermutePR aSource

appPD :: PA a => T_appPR aSource

applPD :: PA a => T_applPR aSource

packByTagPD :: PA a => T_packByTagPR aSource

combine2PD :: PA a => T_combine2PR aSource

updatePD :: PA a => T_updatePR aSource

fromListPD :: PA a => T_fromListPR aSource

nfPD :: PA a => T_nfPR aSource

type family PRepr a Source

Representable types.

The family of types that we know how to represent generically. PRepr takes an arbitrary type and produces the generic type we use to represent it.

Instances for simple types are defined in Data.Array.Parallel.Lifted.Instances. For algebraic types, it's up to the vectoriser/client module to create a suitable instance.

class PR a whereSource

A PR dictionary contains the primitive functions that operate directly on parallel array data.

It's called PR because the functions work on our internal, efficient Representation of the user-level array.

Methods

emptyPR :: T_emptyPR aSource

replicatePR :: T_replicatePR aSource

replicatelPR :: T_replicatelPR aSource

repeatPR :: T_repeatPR aSource

indexPR :: T_indexPR aSource

extractPR :: T_extractPR aSource

bpermutePR :: T_bpermutePR aSource

appPR :: T_appPR aSource

applPR :: T_applPR aSource

packByTagPR :: T_packByTagPR aSource

combine2PR :: T_combine2PR aSource

updatePR :: T_updatePR aSource

fromListPR :: T_fromListPR aSource

nfPR :: T_nfPR aSource

Instances

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

class Elt a => Scalar a whereSource

Class of scalar types. Scalar types are the ones that we can store in our underlying U.Arrays (which are currently implemented as Data.Vectors).

To perform an operation on a PData array of scalar elements, we coerce it to the underling U.Array and use the corresponding U.Array operators.

replicatePRScalar :: Scalar a => T_replicatePR aSource

replicatelPRScalar :: Scalar a => T_replicatelPR aSource

repeatPRScalar :: Scalar a => T_repeatPR aSource

emptyPRScalar :: Scalar a => T_emptyPR aSource

indexPRScalar :: Scalar a => T_indexPR aSource

extractPRScalar :: Scalar a => T_extractPR aSource

bpermutePRScalar :: Scalar a => T_bpermutePR aSource

appPRScalar :: Scalar a => T_appPR aSource

applPRScalar :: Scalar a => T_applPR aSource

packByTagPRScalar :: Scalar a => T_packByTagPR aSource

combine2PRScalar :: Scalar a => T_combine2PR aSource

updatePRScalar :: Scalar a => T_updatePR aSource

fromListPRScalar :: Scalar a => T_fromListPR aSource

nfPRScalar :: Scalar a => T_nfPR aSource

data a :-> b Source

The type of closures. This bundles up: 1) the vectorised version of the function that takes an explicit environment 2) the lifted version, that works on arrays. the first parameter of this function is the 'lifting context' that gives the length of the array. 3) the environment of the closure.

The vectoriser closure-converts the source program so that all functions types are expressed in this form.

Instances

PR (:-> a b) 
(PA a, PA b) => PA (:-> a b) 

($:) :: forall a b. (a :-> b) -> a -> bSource

Apply a closure to its argument.

($:^) :: forall a b. PArray (a :-> b) -> PArray a -> PArray bSource

Lifted closure application