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
- module Data.Array.Repa.Shape
- module Data.Array.Repa.Index
- module Data.Array.Repa.Slice
- class (Show a, Unbox a) => Elt a where
- data Array sh a = Array {
- arrayExtent :: sh
- arrayRegions :: [Region sh a]
- data Region sh a = Region {
- regionRange :: Range sh
- regionGenerator :: Generator sh a
- data Range sh
- = RangeAll
- | RangeRects {
- rangeMatch :: sh -> Bool
- rangeRects :: [Rect sh]
- data Rect sh = Rect sh sh
- data Generator sh a
- = GenManifest (Vector a)
- | forall cursor . GenCursor {
- genMakeCursor :: sh -> cursor
- genShiftCursor :: sh -> cursor -> cursor
- genLoadElem :: cursor -> a
- deepSeqArray :: Shape sh => Array sh a -> b -> b
- deepSeqArrays :: Shape sh => [Array sh a] -> b -> b
- singleton :: Elt a => a -> Array Z a
- toScalar :: Elt a => Array Z a -> a
- extent :: Array sh a -> sh
- delay :: (Shape sh, Elt a) => Array sh a -> (sh, sh -> a)
- withManifest :: (Shape sh, Elt a) => (Array sh a -> b) -> Array sh a -> b
- withManifest' :: (Shape sh, Elt a) => Array sh a -> (Array sh a -> b) -> b
- (!) :: forall sh a. (Shape sh, Elt a) => Array sh a -> sh -> a
- index :: forall sh a. (Shape sh, Elt a) => Array sh a -> sh -> a
- (!?) :: forall sh a. (Shape sh, Elt a) => Array sh a -> sh -> Maybe a
- safeIndex :: forall sh a. (Shape sh, Elt a) => Array sh a -> sh -> Maybe a
- unsafeIndex :: forall sh a. (Shape sh, Elt a) => Array sh a -> sh -> a
- fromFunction :: Shape sh => sh -> (sh -> a) -> Array sh a
- fromVector :: Shape sh => sh -> Vector a -> Array sh a
- fromList :: (Shape sh, Elt a) => sh -> [a] -> Array sh a
- force :: (Shape sh, Elt a) => Array sh a -> Array sh a
- force2 :: Elt a => Array DIM2 a -> Array DIM2 a
- toVector :: (Shape sh, Elt a) => Array sh a -> Vector a
- toList :: (Shape sh, Elt a) => Array sh a -> [a]
- reshape :: (Shape sh, Shape sh', Elt a) => sh' -> Array sh a -> Array sh' a
- append :: (Shape sh, Elt a) => Array (sh :. Int) a -> Array (sh :. Int) a -> Array (sh :. Int) a
- (++) :: (Shape sh, Elt a) => Array (sh :. Int) a -> Array (sh :. Int) a -> Array (sh :. Int) a
- transpose :: (Shape sh, Elt a) => Array ((sh :. Int) :. Int) a -> Array ((sh :. Int) :. Int) a
- extend :: (Slice sl, Shape (FullShape sl), Shape (SliceShape sl), Elt e) => sl -> Array (SliceShape sl) e -> Array (FullShape sl) e
- slice :: (Slice sl, Shape (FullShape sl), Shape (SliceShape sl), Elt e) => Array (FullShape sl) e -> sl -> Array (SliceShape sl) e
- backpermute :: forall sh sh' a. (Shape sh, Shape sh', Elt a) => sh' -> (sh' -> sh) -> Array sh a -> Array sh' a
- backpermuteDft :: forall sh sh' a. (Shape sh, Shape sh', Elt a) => Array sh' a -> (sh' -> Maybe sh) -> Array sh a -> Array sh' a
- map :: (Shape sh, Elt a, Elt b) => (a -> b) -> Array sh a -> Array sh b
- zipWith :: (Shape sh, Elt a, Elt b, Elt c) => (a -> b -> c) -> Array sh a -> Array sh b -> Array sh c
- (+^) :: (Shape sh, Elt c, Num c) => Array sh c -> Array sh c -> Array sh c
- (-^) :: (Shape sh, Elt c, Num c) => Array sh c -> Array sh c -> Array sh c
- (*^) :: (Shape sh, Elt c, Num c) => Array sh c -> Array sh c -> Array sh c
- (/^) :: (Shape sh, Elt c, Fractional c) => Array sh c -> Array sh c -> Array sh c
- fold :: (Shape sh, Elt a) => (a -> a -> a) -> a -> Array (sh :. Int) a -> Array sh a
- foldAll :: (Shape sh, Elt a) => (a -> a -> a) -> a -> Array sh a -> a
- sum :: (Shape sh, Elt a, Num a) => Array (sh :. Int) a -> Array sh a
- sumAll :: (Shape sh, Elt a, Num a) => Array sh a -> a
- traverse :: forall sh sh' a b. (Shape sh, Shape sh', Elt a) => Array sh a -> (sh -> sh') -> ((sh -> a) -> sh' -> b) -> Array sh' b
- traverse2 :: forall sh sh' sh'' a b c. (Shape sh, Shape sh', Shape sh'', Elt a, Elt b, Elt c) => Array sh a -> Array sh' b -> (sh -> sh' -> sh'') -> ((sh -> a) -> (sh' -> b) -> sh'' -> c) -> 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, Elt d) => Array sh1 a -> Array sh2 b -> Array sh3 c -> (sh1 -> sh2 -> sh3 -> sh4) -> ((sh1 -> a) -> (sh2 -> b) -> (sh3 -> c) -> sh4 -> d) -> Array sh4 d
- 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, Elt e) => 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 e
- unsafeTraverse :: (Shape sh1, Shape sh, Elt a1) => Array sh1 a1 -> (sh1 -> sh) -> ((sh1 -> a1) -> sh -> a) -> Array sh a
- unsafeTraverse2 :: forall sh sh' sh'' a b c. (Shape sh, Shape sh', Shape sh'', Elt a, Elt b, Elt c) => Array sh a -> Array sh' b -> (sh -> sh' -> sh'') -> ((sh -> a) -> (sh' -> b) -> sh'' -> c) -> Array sh'' c
- unsafeTraverse3 :: forall sh1 sh2 sh3 sh4 a b c d. (Shape sh1, Shape sh2, Shape sh3, Shape sh4, Elt a, Elt b, Elt c, Elt d) => Array sh1 a -> Array sh2 b -> Array sh3 c -> (sh1 -> sh2 -> sh3 -> sh4) -> ((sh1 -> a) -> (sh2 -> b) -> (sh3 -> c) -> sh4 -> d) -> Array sh4 d
- 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, Elt e) => 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 e
- interleave2 :: (Shape sh, Elt a) => Array (sh :. Int) a -> Array (sh :. Int) a -> Array (sh :. Int) a
- interleave3 :: (Shape sh, Elt a) => Array (sh :. Int) a -> Array (sh :. Int) a -> Array (sh :. Int) a -> Array (sh :. Int) a
- interleave4 :: (Shape sh, Elt a) => Array (sh :. Int) a -> Array (sh :. Int) a -> Array (sh :. Int) a -> Array (sh :. Int) a -> Array (sh :. Int) a
- select :: Elt a => (Int -> Bool) -> (Int -> a) -> Int -> Array DIM1 a
Documentation
module Data.Array.Repa.Shape
module Data.Array.Repa.Index
module Data.Array.Repa.Slice
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.
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.
Generic zero value, helpful for debugging.
Generic one value, helpful for debugging.
Elt Bool | |
Elt Double | |
Elt Float | |
Elt Int | |
Elt Int8 | |
Elt Int16 | |
Elt Word | |
Elt Word8 | |
Elt Word16 | |
(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) |
Repa arrays.
Array | |
|
Defines the values in a region of the array.
Region | |
|
Represents a range of elements in the array.
RangeAll | Covers the entire array. |
RangeRects | The union of a possibly disjoint set of rectangles. |
|
A rectangle/cube of arbitrary dimension. The indices are of the minimum and maximim elements to fill.
Rect sh sh |
Generates array elements for a particular region in the array.
GenManifest (Vector a) | Elements are already computed and sitting in this vector. |
forall cursor . GenCursor | Elements can be computed using these cursor functions. |
|
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.
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
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.
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.
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.
:: 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.
:: forall sh sh' a . (Shape sh, Shape sh', Elt a) | |
=> Array sh' a | Default values ( |
-> (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.
Reductions
fold :: (Shape sh, Elt a) => (a -> a -> a) -> a -> Array (sh :. Int) a -> Array sh aSource
Sequentially fold the innermost dimension of an array.
Combine this with transpose
to fold any other dimension.
foldAll :: (Shape sh, Elt a) => (a -> a -> a) -> a -> Array sh a -> aSource
Sequentially fold all the elements of an array.
sum :: (Shape sh, Elt a, Num a) => Array (sh :. Int) a -> Array sh aSource
Sum the innermost dimension of an array.
Generic Traversal
:: 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.
:: 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 |
traverse3 :: forall sh1 sh2 sh3 sh4 a b c d. (Shape sh1, Shape sh2, Shape sh3, Shape sh4, Elt a, Elt b, Elt c, Elt d) => 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, Elt e) => 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
:: 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.
unsafeTraverse3 :: forall sh1 sh2 sh3 sh4 a b c d. (Shape sh1, Shape sh2, Shape sh3, Shape sh4, Elt a, Elt b, Elt c, Elt d) => 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, Elt e) => 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 dimenion 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
:: 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.