dph-lifted-vseg-0.6.0.2: Data Parallel Haskell lifted array combinators.

Safe HaskellSafe-Infered

Data.Array.Parallel.PArray.PData

Contents

Description

Parallel array data.

This is an interface onto the internal array types and operators defined by the library, and should not normally be used by client programs.

Synopsis

Parallel array types

data PArray a Source

A parallel array consisting of a length field and some array data.

Constructors

PArray Int# (PData a) 

Instances

PA e => Array PArray e 
(Eq a, PA a) => Eq (PArray a) 
(Show (PDatas a), Show (PData a)) => Show (PDatas (PArray a)) 
(Show (PDatas a), Show (PData a)) => Show (PData (PArray a)) 
(Show a, PA a) => Show (PArray a) 
PA a => PprPhysical (PArray a) 
(PprVirtual a, PA a) => PprVirtual (PArray a) 
PR a => PR (PArray a) 
PA a => PA (PArray a) 

data family PData a Source

A chunk of parallel array data with a linear index space.

In contrast to a PArray, a PData may not have a fixed length, and its elements may have been converted to a generic representation. Whereas a PArray is the "user view" of an array, a PData is a type only used internally to the library.

data family PDatas a Source

Several chunks of parallel array data.

Although a PArray of atomic type such as Int only contains a single PData chunk, nested arrays may contain several, which we wrap up into a PDatas.

length :: PArray a -> IntSource

Take the length field of a PArray.

takeData :: PArray a -> PData aSource

Take the PData of a PArray.

PR (Parallel Representation)

class PR a whereSource

The PR (Parallel Representation) class holds primitive array operators that work on our generic representation of data.

There are instances for all atomic types such as Int and Double, tuples, nested arrays `PData (PArray a)` and for the generic types we used to represent user level algebraic data, Sum2 and Wrap and Void. All array data is converted to this fixed set of types.

TODO: refactor to change PData Int to U.Array Int, there's not need to wrap an extra PData constructor around these arrays, and the type of bpermute is different than the others.

Methods

validPR :: PData a -> BoolSource

(debugging) Check that an array has a well formed representation. This should only return False where there is a bug in the library.

nfPR :: PData a -> ()Source

(debugging) Ensure an array is fully evaluted.

similarPR :: a -> a -> BoolSource

(debugging) Weak equality of contained elements.

Returns True for functions of the same type. In the case of nested arrays, returns True if the array defines the same set of elements, but does not care about the exact form of the segement descriptors.

coversPR :: Bool -> PData a -> Int -> BoolSource

(debugging) Check that an index is within an array.

Arrays containing Void elements don't have a fixed length, and return Void for all indices. If the array does have a fixed length, and the flag is true, then we allow the index to be equal to this length, as well as less than it.

pprpPR :: a -> DocSource

(debugging) Pretty print the physical representation of an element.

pprpDataPR :: PData a -> DocSource

(debugging) Pretty print the physical representation of some array data.

emptyPR :: PData aSource

Produce an empty array with size zero.

replicatePR :: Int -> a -> PData aSource

O(n). Define an array of the given size, that maps all elements to the same value.

We require the replication count to be > 0 so that it's easier to maintain the validPR invariants for nested arrays.

replicatesPR :: Segd -> PData a -> PData aSource

O(sum lengths). Segmented replicate.

Given a Segment Descriptor (Segd), replicate each each element in the array according to the length of the corrsponding segment. The array data must define at least as many elements as there are segments in the descriptor.

appendPR :: PData a -> PData a -> PData aSource

Append two arrays.

appendsPR :: Segd -> Segd -> PData a -> Segd -> PData a -> PData aSource

Segmented append.

The first descriptor defines the segmentation of the result, and the others define the segmentation of each source array.

lengthPR :: PData a -> IntSource

O(1). Get the length of an array, if it has one.

Applying this function to an array of Void will yield error, as these arrays have no fixed length. To check array bounds, use the coversPR method instead, as that is a total function.

indexPR :: PData a -> Int -> aSource

O(1). Retrieve a single element from a single array.

indexsPR :: PDatas a -> Array (Int, Int) -> PData aSource

O(1). Shared indexing. Retrieve several elements from several chunks of array data, given the chunkid and index in that chunk for each element.

indexvsPR :: PDatas a -> VSegd -> Array (Int, Int) -> PData aSource

O(1). Shared indexing

extractPR :: PData a -> Int -> Int -> PData aSource

O(slice len). Extract a slice of elements from an array, given the starting index and length of the slice.

extractssPR :: PDatas a -> SSegd -> PData aSource

O(sum seglens). Shared extract. Extract several slices from several source arrays.

The Scattered Segment Descriptor (SSegd) describes where to get each slice, and all slices are concatenated together into the result.

extractvsPR :: PDatas a -> VSegd -> PData aSource

O(sum seglens). Shared extract. Extract several slices from several source arrays. TODO: we're refactoring the library so functions use the VSeg form directly, instead of going via a SSegd.

packByTagPR :: PData a -> Array Tag -> Tag -> PData aSource

Select elements of an array that have their corresponding tag set to the given value.

The data array must define at least as many elements as the length of the tags array.

combine2PR :: Sel2 -> PData a -> PData a -> PData aSource

Combine two arrays based on a selector.

See the documentation for selectors in the dph-prim-seq library for how this works.

fromVectorPR :: Vector a -> PData aSource

Convert a boxed vector to an array.

toVectorPR :: PData a -> Vector aSource

Convert an array to a boxed vector.

emptydPR :: PDatas aSource

O(1). Yield an empty collection of PData.

singletondPR :: PData a -> PDatas aSource

O(1). Yield a singleton collection of PData.

lengthdPR :: PDatas a -> IntSource

O(1). Yield how many PData are in the collection.

indexdPR :: PDatas a -> Int -> PData aSource

O(1). Lookup a PData from a collection.

appenddPR :: PDatas a -> PDatas a -> PDatas aSource

O(n). Append two collections of PData.

fromVectordPR :: Vector (PData a) -> PDatas aSource

O(n). Convert a vector of PData to a PDatas.

toVectordPR :: PDatas a -> Vector (PData a)Source

O(n). Convert a PDatas to a vector of PData.

Instances

PR Double 
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) 

Extra conversions

fromListPR :: PR a => [a] -> PData aSource

Convert a list to a PData.

toListPR :: PR a => PData a -> [a]Source

Convert a PData to a list.

Nested arrays

mkPNested :: PR a => VSegd -> PDatas a -> Segd -> PData a -> PData (PArray a)Source

Construct a nested array.

concatPR :: PR a => PData (PArray a) -> PData aSource

Concatenate a nested array.

concatlPR :: PR a => PData (PArray (PArray a)) -> PData (PArray a)Source

Lifted concatenation.

Concatenate all the arrays in a triply nested array.

flattenPR :: PR a => PData (PArray a) -> (Segd, PData a)Source

Flatten a nested array, yielding a plain segment descriptor and concatenated data.

takeSegdPD :: PData (PArray a) -> SegdSource

Take the segment descriptor from a nested array and demote it to a plain Segd.

unconcatPR :: PR b => PData (PArray a) -> PData b -> PData (PArray b)Source

Build a nested array given a single flat data vector, and a template nested array that defines the segmentation.

appendlPR :: PR a => PData (PArray a) -> PData (PArray a) -> PData (PArray a)Source

Lifted append. Both arrays must contain the same number of elements.

indexlPR :: PR a => PData (PArray a) -> PData Int -> PData aSource

O(len result). Lifted indexing

slicelPRSource

Arguments

:: PR a 
=> PData Int

Starting indices of slices.

-> PData Int

Lengths of slices.

-> PData (PArray a)

Arrays to slice.

-> PData (PArray a) 

Extract some slices from some arrays.

All three parameters must have the same length, and we take one slice from each of the source arrays.

extractvs_delay :: PR a => PDatas a -> VSegd -> PData aSource

Wrapper for extracts that is NOT INLINED.

This is experimental, used to initialise the pnested_flat field of a nested array. Its marked at NOINLINE to avoid code explosion.

Tuple arrays

zipPD :: PData a -> PData b -> PData (a, b)Source

O(1). Zip a pair of arrays into an array of pairs.

ziplPR :: (PR a, PR b) => PData (PArray a) -> PData (PArray b) -> PData (PArray (a, b))Source

Lifted zip.

unzipPD :: PData (a, b) -> (PData a, PData b)Source

O(1). Unzip an array of pairs into a pair of arrays.

unziplPD :: PData (PArray (a, b)) -> PData (PArray a, PArray b)Source

Lifted unzip.

zip3PD :: PData a -> PData b -> PData c -> PData (a, b, c)Source

O(1). Zip a pair of arrays into an array of pairs.

zip4PD :: PData a -> PData b -> PData c -> PData d -> PData (a, b, c, d)Source

O(1). Zip a pair of arrays into an array of pairs.

zip5PD :: PData a -> PData b -> PData c -> PData d -> PData e -> PData (a, b, c, d, e)Source

O(1). Zip a pair of arrays into an array of pairs.