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

Safe HaskellNone

Data.Array.Parallel.Prim

Description

This is the API used by the vectoriser. The vectoriser wants a slightly different interface to the one used natively by the library. This module performs the impedance matching.

Synopsis

Documentation

data family PData a

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

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.

type family PRepr a

Family of Representable types. These are the 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 by the library. For algebraic types, it's up to the vectoriser/client module to create a suitable instance.

class PR (PRepr a) => PA a where

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) 

class PR a where

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 -> Bool

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

(debugging) Ensure an array is fully evaluted.

similarPR :: a -> a -> Bool

(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 -> Bool

(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 -> Doc

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

pprpDataPR :: PData a -> Doc

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

typeRepPR :: a -> TypeRep

(debugging) Get the representation of this type. We don't use the Typeable class for this because the vectoriser won't handle the Typeable superclass on PR.

typeRepDataPR :: PData a -> TypeRep

(debugging) Given a 'PData a' get the representation of the a

typeRepDatasPR :: PDatas a -> TypeRep

(debugging) Given a 'PDatas a' get the representation of the a

emptyPR :: PData a

Produce an empty array with size zero.

replicatePR :: Int -> a -> PData a

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 a

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 a

Append two arrays.

appendvsPR :: Segd -> VSegd -> PDatas a -> VSegd -> PDatas a -> PData a

Segmented append.

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

lengthPR :: PData a -> Int

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 -> a

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

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

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 a

O(1). Shared indexing

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

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 a

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 a

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 a

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 a

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 a

Convert a boxed vector to an array.

toVectorPR :: PData a -> Vector a

Convert an array to a boxed vector.

emptydPR :: PDatas a

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

singletondPR :: PData a -> PDatas a

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

lengthdPR :: PDatas a -> Int

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

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

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

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

O(n). Append two collections of PData.

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

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

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

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) 
(PR a, PR b, PR c, PR d, PR e, PR f) => PR (a, b, c, d, e, f) 
(PR a, PR b, PR c, PR d, PR e, PR f, PR g) => PR (a, b, c, d, e, f, g) 

emptyPD :: PA a => PData a

replicatePD :: PA a => Int# -> a -> PData a

packByTagPD :: PA a => PData a -> Int# -> Array Tag -> Int# -> PData a

combine2PD :: PA a => Int# -> Sel2 -> PData a -> PData a -> PData a

class (PA a, Elt a) => Scalar a where

Class of Scalar data that can be converted to and from single unboxed vectors.

scalar_map :: (Scalar a, Scalar b) => (a -> b) -> PArray a -> PArray b

scalar_zipWith :: (Scalar a, Scalar b, Scalar c) => (a -> b -> c) -> PArray a -> PArray b -> PArray c

scalar_zipWith3 :: (Scalar a, Scalar b, Scalar c, Scalar d) => (a -> b -> c -> d) -> PArray a -> PArray b -> PArray c -> PArray d

scalar_zipWith4 :: (Scalar a, Scalar b, Scalar c, Scalar d, Scalar e) => (a -> b -> c -> d -> e) -> PArray a -> PArray b -> PArray c -> PArray d -> PArray e

scalar_zipWith5 :: (Scalar a, Scalar b, Scalar c, Scalar d, Scalar e, Scalar f) => (a -> b -> c -> d -> e -> f) -> PArray a -> PArray b -> PArray c -> PArray d -> PArray e -> PArray f

scalar_zipWith6 :: (Scalar a, Scalar b, Scalar c, Scalar d, Scalar e, Scalar f, Scalar g) => (a -> b -> c -> d -> e -> f -> g) -> PArray a -> PArray b -> PArray c -> PArray d -> PArray e -> PArray f -> PArray g

scalar_zipWith7 :: (Scalar a, Scalar b, Scalar c, Scalar d, Scalar e, Scalar f, Scalar g, Scalar h) => (a -> b -> c -> d -> e -> f -> g -> h) -> PArray a -> PArray b -> PArray c -> PArray d -> PArray e -> PArray f -> PArray g -> PArray h

scalar_zipWith8 :: (Scalar a, Scalar b, Scalar c, Scalar d, Scalar e, Scalar f, Scalar g, Scalar h, Scalar i) => (a -> b -> c -> d -> e -> f -> g -> h -> i) -> PArray a -> PArray b -> PArray c -> PArray d -> PArray e -> PArray f -> PArray g -> PArray h -> PArray i

data Void

The Void type is used when representing enumerations.

A type like Bool is represented as Sum2 Void Void, meaning that we only only care about the tag of the data constructor and not its argumnent.

void :: Void

A value with the void type. Used as a placholder like undefined. Forcing this yields error.

fromVoid :: a

Coerce a Void to a different type. Used as a placeholder like undefined. Forcing the result yields error.

punit :: Int -> PData ()

newtype Wrap a

When converting a data type to its generic representation, we use Wrap to help us convert only one layer at a time. For example:

   data Foo a = Foo Int a

instance PA a => PA (Foo a) where
    type PRepr (Foo a) = (Int, Wrap a)  -- define how (Foo a) is represented

Here we've converted the Foo data constructor to a pair, and Int is its own representation type. We have PData/PR instances for pairs and Ints, so we can work with arrays of these types. However, we can't just use (Int, a) as the representation of (Foo a) because a might be user defined and we won't have PData/PR instances for it.

Instead, we wrap the second element with the Wrap constructor, which tells us that if we want to process this element we still need to convert it to the generic representation (and back). This last part is done by the PR instance of Wrap, who's methods are defined by calls to the *PD functions from Data.Array.Parallel.PArray.PRepr.

Constructors

Wrap 

Fields

unWrap :: a
 

Instances

Typeable1 Wrap 
PA a => PR (Wrap a) 

data Sum2 a b

Sum types used for the generic representation of algebraic data.

Constructors

Alt2_1 a 
Alt2_2 b 

Instances

Typeable2 Sum2 
(PprPhysical a, PprPhysical b) => PprPhysical (Sum2 a b) 
(PR a, PR b) => PR (Sum2 a b) 

data Sum3 a b c

Constructors

Alt3_1 a 
Alt3_2 b 
Alt3_3 c 

Instances

data a :-> b

Define the fixity of the closure type constructor.

The type of closures. This bundles up:

Constructors

forall env . PA env => Clo (env -> a -> b) (Int -> PData env -> PData a -> PData b) env 

Instances

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

closure :: forall a b e. PA e => (e -> a -> b) -> (Int# -> PData e -> PData a -> PData b) -> e -> a :-> b

Construct a closure.

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

Apply a closure.

liftedClosure :: forall a b e. PA e => (e -> a -> b) -> (Int# -> PData e -> PData a -> PData b) -> PData e -> PData (a :-> b)

Construct a lifted closure.

liftedApply :: Int# -> PData (a :-> b) -> PData a -> PData b

Apply a lifted closure.

closure1 :: forall a b. (a -> b) -> (PArray a -> PArray b) -> a :-> b

closure2 :: forall a b c. PA a => (a -> b -> c) -> (PArray a -> PArray b -> PArray c) -> a :-> (b :-> c)

closure3 :: forall a b c d. (PA a, PA b) => (a -> b -> c -> d) -> (PArray a -> PArray b -> PArray c -> PArray d) -> a :-> (b :-> (c :-> d))

closure4 :: forall a b c d e. (PA a, PA b, PA c) => (a -> b -> c -> d -> e) -> (PArray a -> PArray b -> PArray c -> PArray d -> PArray e) -> a :-> (b :-> (c :-> (d :-> e)))

closure5 :: forall a b c d e f. (PA a, PA b, PA c, PA d) => (a -> b -> c -> d -> e -> f) -> (PArray a -> PArray b -> PArray c -> PArray d -> PArray e -> PArray f) -> a :-> (b :-> (c :-> (d :-> (e :-> f))))

closure6 :: forall a b c d e f g. (PA a, PA b, PA c, PA d, PA e) => (a -> b -> c -> d -> e -> f -> g) -> (PArray a -> PArray b -> PArray c -> PArray d -> PArray e -> PArray f -> PArray g) -> a :-> (b :-> (c :-> (d :-> (e :-> (f :-> g)))))

closure7 :: forall a b c d e f g h. (PA a, PA b, PA c, PA d, PA e, PA f, PA g) => (a -> b -> c -> d -> e -> f -> g -> h) -> (PArray a -> PArray b -> PArray c -> PArray d -> PArray e -> PArray f -> PArray g -> PArray h) -> a :-> (b :-> (c :-> (d :-> (e :-> (f :-> (g :-> h))))))

closure8 :: forall 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) => (a -> b -> c -> d -> e -> f -> g -> h -> i) -> (PArray a -> PArray b -> PArray c -> PArray d -> PArray e -> PArray f -> PArray g -> PArray h -> PArray i) -> a :-> (b :-> (c :-> (d :-> (e :-> (f :-> (g :-> (h :-> i)))))))

type Sel2 = Sel2

emptyPA_Int# :: PArray_Int#

emptyPA_Double# :: PArray_Double#

replicatePA_Int# :: Int# -> Int# -> PArray_Int#

replicatePA_Double# :: Int# -> Double# -> PArray_Double#

combine2PA_Int# :: Int# -> PArray_Int# -> PArray_Int# -> PArray_Int# -> PArray_Int# -> PArray_Int#

combine2PA_Double# :: Int# -> PArray_Int# -> PArray_Int# -> PArray_Double# -> PArray_Double# -> PArray_Double#

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

tup3 :: (PA a, PA b, PA c) => a :-> (b :-> (c :-> (a, b, c)))

tup4 :: (PA a, PA b, PA c, PA d) => a :-> (b :-> (c :-> (d :-> (a, b, c, d))))

tup5 :: (PA a, PA b, PA c, PA d, PA e) => a :-> (b :-> (c :-> (d :-> (e :-> (a, b, c, d, e)))))