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

Safe HaskellNone

Data.Array.Parallel.PArray

Contents

Description

Unvectorised parallel arrays.

  • These operators may be used directly by unvectorised client programs.
  • They are also used by the Data.Array.Parallel.Lifted.Combinators module to define the closure converted versions that vectorised code uses.
  • In general, the operators here are all unsafe and don't do bounds checks. The lifted versions also don't check that each of the argument arrays have the same length.

Synopsis

Documentation

data PArray a Source

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

Instances

Typeable1 PArray 
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) 
(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 conversions methods should all be O(1).

Instances

PA Bool 
PA Double 
PA Int 
PA Integer 
PA Ordering 
PA Word8 
PA () 
PA Void 
(PR (PRepr (PArray a)), PA a) => PA (PArray a) 
(PR (PRepr (Either a b)), PR a, PR b) => PA (Either a b) 
(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) 

valid :: PA a => PArray a -> BoolSource

Check that an array has a valid internal representation.

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

Force an array to normal form.

typeRep :: PA a => a -> TypeRepSource

Get the type of a thing.

Constructors

empty :: PA a => PArray aSource

O(1). An empty array.

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

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

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

O(n). Produce an array of singleton arrays.

replicate :: PA a => Int -> a -> PArray 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.

replicatel :: PA a => PArray Int -> PArray a -> PArray (PArray a)Source

O(sum lengths). Lifted replicate.

replicates :: PA a => Segd -> PArray a -> PArray aSource

O(sum lengths). Segmented replicate.

replicates' :: PA a => PArray Int -> PArray a -> PArray aSource

O(sum lengths). Wrapper for segmented replicate that takes replication counts and uses them to build the Segd.

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

Append two arrays.

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

Lifted append. Both arrays must have the same length

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

Concatenate a nested array.

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

Lifted concat.

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

Impose a nesting structure on a flat array

nestUSegd :: PA a => Segd -> PArray a -> PArray (PArray a)Source

Create a nested array from a segment descriptor and some flat data. The segment descriptor must represent as many elements as present in the flat data array, else error

Projections

length :: PArray a -> IntSource

Take the length field of a PArray.

lengthl :: PA a => PArray (PArray a) -> PArray IntSource

Take the length of some arrays.

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

O(1). Lookup a single element from the source array.

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

O(len indices). Lookup a several elements from several source arrays

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

Extract a range of elements from an array.

extracts :: PA a => Vector (PArray a) -> SSegd -> PArray aSource

Segmented extract.

extracts'Source

Arguments

:: PA a 
=> Vector (PArray a) 
-> PArray Int

id of source array for each segment.

-> PArray Int

starting index of each segment in its source array.

-> PArray Int

length of each segment.

-> PArray a 

Wrapper for extracts that takes arrays of sources, starts and lengths of the segments, and uses these to build the SSegd. TODO: The lengths of the sources, starts and lengths arrays must be the same, but this is not checked. All sourceids must point to valid data arrays. Segments must be within their corresponding source array.

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

Extract a range of elements from an arrary. Like extract but with the parameters in a different order.

slicel :: PA a => PArray Int -> PArray Int -> PArray (PArray a) -> PArray (PArray a)Source

Extract some slices from some arrays. The arrays of starting indices and lengths must themselves have the same length.

takeUSegd :: PArray (PArray a) -> SegdSource

Take the segment descriptor from a nested array and demote it to a plain Segd. This is unsafe because it can cause index space overflow.

Pack and Combine

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

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

packl :: PA a => PArray (PArray a) -> PArray (PArray Bool) -> PArray (PArray a)Source

Lifted pack.

packByTag :: PA a => PArray a -> Array Tag -> Tag -> PArray aSource

Filter an array based on some tags.

combine2 :: forall a. PA a => Sel2 -> PArray a -> PArray a -> PArray aSource

Combine two arrays based on a selector.

Enumerations

enumFromTo :: Int -> Int -> PArray IntSource

Construct a range of integers.

Tuples

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

O(1). Zip a pair of arrays into an array of pairs. The two arrays must have the same length, else error.

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

Lifted zip.

zip3 :: PArray a -> PArray b -> PArray c -> PArray (a, b, c)Source

O(1). Zip three arrays. All arrays must have the same length, else error.

zip4 :: PArray a -> PArray b -> PArray c -> PArray d -> PArray (a, b, c, d)Source

O(1). Zip four arrays. All arrays must have the same length, else error.

zip5 :: PArray a -> PArray b -> PArray c -> PArray d -> PArray e -> PArray (a, b, c, d, e)Source

O(1). Zip five arrays. All arrays must have the same length, else error.

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

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

unzipl :: PArray (PArray (a, b)) -> PArray (PArray a, PArray b)Source

Lifted unzip

Conversions

fromVector :: PA a => Vector a -> PArray aSource

Convert a Vector to a PArray

toVector :: PA a => PArray a -> Vector aSource

Convert a PArray to a Vector

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

Convert a list to a PArray.

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

Convert a PArray to a list.

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

Convert an U.Array of pairs to a PArray.