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

Data.Array.Repa

Contents

Description

See the repa-examples package for examples.

More information is also at http:code.haskell.orgtracrepa

NOTE: To get decent performance you must use GHC head branch > 6.13.20100309.

WARNING: Most of the functions that operate on indices don't perform bounds checks. Doing these checks would interfere with code optimisation and reduce performance. Indexing outside arrays, or failing to meet the stated obligations will likely cause heap corruption.

Synopsis

Documentation

data Array sh a Source

Possibly delayed arrays.

Constructors

Manifest sh (Array a)

An array represented as some concrete unboxed data.

Delayed sh (sh -> a)

An array represented as a function that computes each element.

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) 

Constructors

fromUArray :: Shape sh => sh -> Array a -> Array sh aSource

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

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

Create a Delayed array from a function.

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

Wrap a scalar into a singleton array.

Projections

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.

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

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

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

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

Get an indexed element from an array.

OBLIGATION: The index must be within the array.

inRange zeroDim (shape arr) ix == True

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

Take the scalar value from a singleton array.

Basic Operations

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

Force an array, so that it becomes Manifest.

isManifest :: Array sh a -> Array sh aSource

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

Ensure an array's structure is fully evaluated. This evaluates the extent and outer constructor, but does not force the elements.

Conversion

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.

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

Convert an array to a list.

Index space transformations

reshape :: (Shape sh, Shape sh', Elt a) => Array sh a -> sh' -> 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.

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.

OBLIGATION: The higher dimensions of both arrays must have the same extent.

tail (listOfShape (shape arr1)) == tail (listOfShape (shape arr2))

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.

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

Replicate an array, according to a given slice specification.

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.

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.

Reductions

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

Fold the innermost dimension of an array. Combine this with transpose to fold any other dimension.

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, Elt c) 
=> 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.

Testing

arbitrarySmallArray :: (Shape sh, Elt a, Arbitrary sh, Arbitrary a) => Int -> Gen (Array (sh :. Int) a)Source

Create an arbitrary small array, restricting the size of each of the dimensions to some value.

props_DataArrayRepa :: [(String, Property)]Source

QuickCheck properties for this module and its children.