repa-2.1.0.1: High performance, regular, shape polymorphic parallel arrays.

Data.Array.Repa

Contents

Description

See the repa-examples package for examples.

More information at http://repa.ouroborus.net.

There is a draft tutorial at http://www.haskell.org/haskellwiki/Numeric_Haskell:_A_Repa_Tutorial

Release Notes:
  For 2.1.0.1:
   * The fold and foldAll functions now run in parallel and require the
     starting element to be neutral with respect to the reduction operator.
                                   -- thanks to Trevor McDonell
   * Added (//) update function.   -- thanks to Trevor McDonell
   * Dropped unneeded Elt constraints from traverse functions.

Synopsis

Documentation

class (Show a, Unbox a) => Elt a whereSource

Element types that can be stored in Repa arrays. Repa uses Data.Vector.Unboxed to store the actual data. The implementation of this library is based on type families and picks an efficient, specialised representation for every element type. In particular, unboxed vectors of pairs are represented as pairs of unboxed vectors.

Methods

touch :: a -> IO ()Source

We use this to prevent bindings from being floated inappropriatey. Doing a seq sometimes isn't enough, because the GHC simplifier can erase these, and/or still move around the bindings.

zero :: aSource

Generic zero value, helpful for debugging.

one :: aSource

Generic one value, helpful for debugging.

Instances

Elt Bool 
Elt Double 
Elt Float 
Elt Int 
Elt Int8 
Elt Int16 
Elt Int32 
Elt Int64 
Elt Word 
Elt Word8 
Elt Word16 
Elt Word32 
Elt Word64 
(Elt a, Elt b) => Elt (a, b) 
(Elt a, Elt b, Elt c) => Elt (a, b, c) 
(Elt a, Elt b, Elt c, Elt d) => Elt (a, b, c, d) 
(Elt a, Elt b, Elt c, Elt d, Elt e) => Elt (a, b, c, d, e) 
(Elt a, Elt b, Elt c, Elt d, Elt e, Elt f) => Elt (a, b, c, d, e, f) 

data Array sh a Source

Repa arrays.

Constructors

Array 

Fields

arrayExtent :: sh

The entire extent of the array.

arrayRegions :: [Region sh a]

Arrays can be partitioned into several regions.

Instances

(Shape sh, Elt a, Eq a) => Eq (Array sh a) 
(Shape sh, Elt a, Num a) => Num (Array sh a) 
(Shape sh, Elt a, Show a) => Show (Array sh a) 

data Region sh a Source

Defines the values in a region of the array.

Constructors

Region 

Fields

regionRange :: Range sh

The range of elements this region applies to.

regionGenerator :: Generator sh a

How to compute the array elements in this region.

data Range sh Source

Represents a range of elements in the array.

Constructors

RangeAll

Covers the entire array.

RangeRects

The union of a possibly disjoint set of rectangles.

Fields

rangeMatch :: sh -> Bool
 
rangeRects :: [Rect sh]
 

data Rect sh Source

A rectangle/cube of arbitrary dimension. The indices are of the minimum and maximim elements to fill.

Constructors

Rect sh sh 

data Generator sh a Source

Generates array elements for a particular region in the array.

Constructors

GenManifest (Vector a)

Elements are already computed and sitting in this vector.

forall cursor . GenCursor

Elements can be computed using these cursor functions.

Fields

genMakeCursor :: sh -> cursor

Make a cursor to a particular element.

genShiftCursor :: sh -> cursor -> cursor

Shift the cursor by an offset, to get to another element.

genLoadElem :: cursor -> a

Load/compute the element at the given cursor.

deepSeqArray :: Shape sh => Array sh a -> b -> bSource

Ensure the structure for an array is fully evaluated. As we are in a lazy language, applying the force function to a delayed array doesn't actually compute it at that point. Rather, Haskell builds a suspension representing the appliction of the force function to that array. Use deepSeqArray to ensure the array is actually computed at a particular point in the program.

deepSeqArrays :: Shape sh => [Array sh a] -> b -> bSource

Like deepSeqArray but seqs all the arrays in a list. This is specialised up to lists of 4 arrays. Using more in the list will break fusion.

singleton :: Elt a => a -> Array Z aSource

Wrap a scalar into a singleton array.

toScalar :: Elt a => Array Z a -> aSource

Take the scalar value from a singleton array.

extent :: Array sh a -> shSource

Take the extent of an array.

delay :: (Shape sh, Elt a) => Array sh a -> (sh, sh -> a)Source

Unpack an array into delayed form.

withManifest :: (Shape sh, Elt a) => (Array sh a -> b) -> Array sh a -> bSource

Force an array before passing it to a function.

withManifest' :: (Shape sh, Elt a) => Array sh a -> (Array sh a -> b) -> bSource

Force an array before passing it to a function.

Indexing

(!) :: forall sh a. (Shape sh, Elt a) => Array sh a -> sh -> aSource

index :: forall sh a. (Shape sh, Elt a) => Array sh a -> sh -> aSource

Get an indexed element from an array. This uses the same level of bounds checking as your Data.Vector installation.

(!?) :: forall sh a. (Shape sh, Elt a) => Array sh a -> sh -> Maybe aSource

safeIndex :: forall sh a. (Shape sh, Elt a) => Array sh a -> sh -> Maybe aSource

Get an indexed element from an array. If the element is out of range then Nothing.

unsafeIndex :: forall sh a. (Shape sh, Elt a) => Array sh a -> sh -> aSource

Get an indexed element from an array, without bounds checking. This assumes that the regions in the array give full coverage. An array with no regions gets zero for every element.

Construction

fromFunction :: Shape sh => sh -> (sh -> a) -> Array sh aSource

Create a Delayed array from a function.

fromVector :: Shape sh => sh -> Vector a -> Array sh aSource

Create a Manifest array from an unboxed Vector. The elements are in row-major order.

fromList :: (Shape sh, Elt a) => sh -> [a] -> Array sh aSource

Convert a list to an array. The length of the list must be exactly the size of the extent given, else error.

Forcing

force :: (Shape sh, Elt a) => Array sh a -> Array sh aSource

Force an array, so that it becomes Manifest. The array is split into linear chunks and each chunk evaluated in parallel.

force2 :: Elt a => Array DIM2 a -> Array DIM2 aSource

Force an array, so that it becomes Manifest. This forcing function is specialised for DIM2 arrays, and does blockwise filling.

toVector :: (Shape sh, Elt a) => Array sh a -> Vector aSource

Convert an array to an unboxed Data.Vector, forcing it if required. The elements come out in row-major order.

toList :: (Shape sh, Elt a) => Array sh a -> [a]Source

Convert an array to a list, forcing it if required.

Index space transformations

reshape :: (Shape sh, Shape sh', Elt a) => sh' -> Array sh a -> Array sh' aSource

Impose a new shape on the elements of an array. The new extent must be the same size as the original, else error.

TODO: This only works for arrays with a single region.

append :: (Shape sh, Elt a) => Array (sh :. Int) a -> Array (sh :. Int) a -> Array (sh :. Int) aSource

(++) :: (Shape sh, Elt a) => Array (sh :. Int) a -> Array (sh :. Int) a -> Array (sh :. Int) aSource

Append two arrays.

transpose :: (Shape sh, Elt a) => Array ((sh :. Int) :. Int) a -> Array ((sh :. Int) :. Int) aSource

Transpose the lowest two dimensions of an array. Transposing an array twice yields the original.

extend :: (Slice sl, Shape (FullShape sl), Shape (SliceShape sl), Elt e) => sl -> Array (SliceShape sl) e -> Array (FullShape sl) eSource

Extend an array, according to a given slice specification. (used to be called replicate).

slice :: (Slice sl, Shape (FullShape sl), Shape (SliceShape sl), Elt e) => Array (FullShape sl) e -> sl -> Array (SliceShape sl) eSource

Take a slice from an array, according to a given specification.

backpermuteSource

Arguments

:: forall sh sh' a . (Shape sh, Shape sh', Elt a) 
=> sh'

Extent of result array.

-> (sh' -> sh)

Function mapping each index in the result array to an index of the source array.

-> Array sh a

Source array.

-> Array sh' a 

Backwards permutation of an array's elements. The result array has the same extent as the original.

backpermuteDftSource

Arguments

:: forall sh sh' a . (Shape sh, Shape sh', Elt a) 
=> Array sh' a

Default values (arrDft)

-> (sh' -> Maybe sh)

Function mapping each index in the result array to an index in the source array.

-> Array sh a

Source array.

-> Array sh' a 

Default backwards permutation of an array's elements. If the function returns Nothing then the value at that index is taken from the default array (arrDft)

Structure preserving operations

map :: (Shape sh, Elt a, Elt b) => (a -> b) -> Array sh a -> Array sh bSource

Apply a worker function to each element of an array, yielding a new array with the same extent.

This is specialised for arrays of up to four regions, using more breaks fusion.

zipWith :: (Shape sh, Elt a, Elt b, Elt c) => (a -> b -> c) -> Array sh a -> Array sh b -> Array sh cSource

Combine two arrays, element-wise, with a binary operator. If the extent of the two array arguments differ, then the resulting array's extent is their intersection.

(+^) :: (Shape sh, Elt c, Num c) => Array sh c -> Array sh c -> Array sh cSource

(-^) :: (Shape sh, Elt c, Num c) => Array sh c -> Array sh c -> Array sh cSource

(*^) :: (Shape sh, Elt c, Num c) => Array sh c -> Array sh c -> Array sh cSource

(/^) :: (Shape sh, Elt c, Fractional c) => Array sh c -> Array sh c -> Array sh cSource

Bulk updates

(//) :: (Shape sh, Elt a) => Array sh a -> [(sh, a)] -> Array sh aSource

For each pair (sh, a) from the list of index/value pairs, replace the element at position sh by a.

 update <5,9,2,7> [(2,1),(0,3),(2,8)] = <3,9,8,7>

Reductions

fold :: (Shape sh, Elt a) => (a -> a -> a) -> a -> Array (sh :. Int) a -> Array sh aSource

Reduction of the innermost dimension of an arbitrary rank array. The first argument needs to be an associative operator. The starting element must be neutral with respect to the operator, for example 0 is neutral with respect to (+) as 0 + a = a. These restrictions are required to support parallel evaluation, as the starting element may be used multiple times depending on the number of threads.

foldAll :: (Shape sh, Elt a) => (a -> a -> a) -> a -> Array sh a -> aSource

Reduction of an array of arbitrary rank to a single scalar value. The first argument needs to be an associative operator. The starting element must be neutral with respect to the operator, for example 0 is neutral with respect to (+) as 0 + a = a. These restrictions are required to support parallel evaluation, as the starting element may be used multiple times depending on the number of threads.

sum :: (Shape sh, Elt a, Num a) => Array (sh :. Int) a -> Array sh aSource

Sum the innermost dimension of an array.

sumAll :: (Shape sh, Elt a, Num a) => Array sh a -> aSource

Sum all the elements of an array.

Generic Traversal

traverseSource

Arguments

:: forall sh sh' a b . (Shape sh, Shape sh', Elt a) 
=> Array sh a

Source array.

-> (sh -> sh')

Function to produce the extent of the result.

-> ((sh -> a) -> sh' -> b)

Function to produce elements of the result. It is passed a lookup function to get elements of the source.

-> Array sh' b 

Unstructured traversal.

traverse2Source

Arguments

:: forall sh sh' sh'' a b c . (Shape sh, Shape sh', Shape sh'', Elt a, Elt b) 
=> Array sh a

First source array.

-> Array sh' b

Second source array.

-> (sh -> sh' -> sh'')

Function to produce the extent of the result.

-> ((sh -> a) -> (sh' -> b) -> sh'' -> c)

Function to produce elements of the result. It is passed lookup functions to get elements of the source arrays.

-> Array sh'' c 

traverse3 :: forall sh1 sh2 sh3 sh4 a b c d. (Shape sh1, Shape sh2, Shape sh3, Shape sh4, Elt a, Elt b, Elt c) => Array sh1 a -> Array sh2 b -> Array sh3 c -> (sh1 -> sh2 -> sh3 -> sh4) -> ((sh1 -> a) -> (sh2 -> b) -> (sh3 -> c) -> sh4 -> d) -> Array sh4 dSource

traverse4 :: forall sh1 sh2 sh3 sh4 sh5 a b c d e. (Shape sh1, Shape sh2, Shape sh3, Shape sh4, Shape sh5, Elt a, Elt b, Elt c, Elt d) => Array sh1 a -> Array sh2 b -> Array sh3 c -> Array sh4 d -> (sh1 -> sh2 -> sh3 -> sh4 -> sh5) -> ((sh1 -> a) -> (sh2 -> b) -> (sh3 -> c) -> (sh4 -> d) -> sh5 -> e) -> Array sh5 eSource

unsafeTraverse :: (Shape sh1, Shape sh, Elt a1) => Array sh1 a1 -> (sh1 -> sh) -> ((sh1 -> a1) -> sh -> a) -> Array sh aSource

unsafeTraverse2Source

Arguments

:: forall sh sh' sh'' a b c . (Shape sh, Shape sh', Shape sh'', Elt a, Elt b) 
=> Array sh a

First source array.

-> Array sh' b

Second source array.

-> (sh -> sh' -> sh'')

Function to produce the extent of the result.

-> ((sh -> a) -> (sh' -> b) -> sh'' -> c)

Function to produce elements of the result. It is passed lookup functions to get elements of the source arrays.

-> Array sh'' c 

Unstructured traversal over two arrays at once.

unsafeTraverse3 :: forall sh1 sh2 sh3 sh4 a b c d. (Shape sh1, Shape sh2, Shape sh3, Shape sh4, Elt a, Elt b, Elt c) => Array sh1 a -> Array sh2 b -> Array sh3 c -> (sh1 -> sh2 -> sh3 -> sh4) -> ((sh1 -> a) -> (sh2 -> b) -> (sh3 -> c) -> sh4 -> d) -> Array sh4 dSource

Unstructured traversal over three arrays at once.

unsafeTraverse4 :: forall sh1 sh2 sh3 sh4 sh5 a b c d e. (Shape sh1, Shape sh2, Shape sh3, Shape sh4, Shape sh5, Elt a, Elt b, Elt c, Elt d) => Array sh1 a -> Array sh2 b -> Array sh3 c -> Array sh4 d -> (sh1 -> sh2 -> sh3 -> sh4 -> sh5) -> ((sh1 -> a) -> (sh2 -> b) -> (sh3 -> c) -> (sh4 -> d) -> sh5 -> e) -> Array sh5 eSource

Unstructured traversal over four arrays at once.

Interleaving

interleave2 :: (Shape sh, Elt a) => Array (sh :. Int) a -> Array (sh :. Int) a -> Array (sh :. Int) aSource

Interleave the elements of two arrays. All the input arrays must have the same extent, else error. The lowest dimension of the result array is twice the size of the inputs.

  interleave2 a1 a2   b1 b2  =>  a1 b1 a2 b2
              a3 a4   b3 b4      a3 b3 a4 b4

interleave3 :: (Shape sh, Elt a) => Array (sh :. Int) a -> Array (sh :. Int) a -> Array (sh :. Int) a -> Array (sh :. Int) aSource

Interleave the elements of three arrays.

interleave4 :: (Shape sh, Elt a) => Array (sh :. Int) a -> Array (sh :. Int) a -> Array (sh :. Int) a -> Array (sh :. Int) a -> Array (sh :. Int) aSource

Interleave the elements of four arrays.

Selection

selectSource

Arguments

:: Elt a 
=> (Int -> Bool)

If the Int matches this predicate,

-> (Int -> a)

... then pass it to this fn to produce a value

-> Int

Range between 0 and this maximum.

-> Array DIM1 a

Array containing produced values.

Produce an array by applying a predicate to a range of integers. If the predicate matches, then use the second function to generate the element.

This is a low-level function helpful for writing filtering operations on arrays. Use the integer as the index into the array you're filtering.