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

Safe HaskellSafe-Infered

Data.Array.Parallel

Contents

Description

User level interface to vectorised parallel arrays.

WARNING: In the current implementation, the functionality provided in this module is tied to the vectoriser pass of GHC, invoked by `-fvectorise`. These functions will not work at all in unvectorised code. To operate on parallel arrays in unvectorised code, use the functions in Data.Array.Parallel.PArray and convert between array representations by using fromPArrayP and toPArrayP from vectorised code.

Synopsis

Documentation

Conversions

data PArray a Source

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

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) 

fromPArrayP :: PArray a -> [:a:]Source

O(1). Convert between PArray and [::] array representations.

toPArrayP :: [:a:] -> PArray aSource

O(1). Convert between PArray and [::] array representations.

fromNestedPArrayP :: PArray (PArray a) -> [:[:a:]:]Source

O(1). Convert between PArray and [::] array representations.

Constructors

emptyP :: [:a:]Source

Construct an empty array, with no elements.

singletonP :: a -> [:a:]Source

Construct an array with a single element.

replicateP :: Int -> a -> [:a:]Source

Construct an array by replicating the given element some number of times.

appendP, (+:+) :: [:a:] -> [:a:] -> [:a:]Source

Append two arrays.

concatP :: [:[:a:]:] -> [:a:]Source

Concatenate an array of arrays.

Projections

lengthP :: [:a:] -> IntSource

Take the length of an array.

indexP, (!:) :: [:a:] -> Int -> aSource

Lookup a single element from the source array.

sliceP :: Int -> Int -> [:a:] -> [:a:]Source

Extract a slice from an array.

Traversals

mapP :: (a -> b) -> [:a:] -> [:b:]Source

Apply a worker function to every element of an array.

zipWithP :: (a -> b -> c) -> [:a:] -> [:b:] -> [:c:]Source

Apply a worker function to every pair of two arrays.

crossMapP :: [:a:] -> (a -> [:b:]) -> [:(a, b):]Source

For every element a apply the function to get an array of b then, and return an array of all the as and bs.

Filtering

filterP :: (a -> Bool) -> [:a:] -> [:a:]Source

Filter an array, keeping only those elements that match the given predicate.

Ziping and Unzipping

zipP :: [:a:] -> [:b:] -> [:(a, b):]Source

Zip a pair of arrays into an array of pairs.

unzipP :: [:(a, b):] -> ([:a:], [:b:])Source

Unzip an array of pairs into a pair of arrays.