| Portability | non-portable (GHC extensions) | 
|---|---|
| Stability | experimental | 
| Maintainer | Manuel M T Chakravarty <chak@cse.unsw.edu.au> | 
| Safe Haskell | None | 
Data.Array.Accelerate.Array.Representation
Description
- class (Eq sh, Slice sh) => Shape sh  where
- dim :: sh -> Int
 - size :: sh -> Int
 - intersect :: sh -> sh -> sh
 - ignore :: sh
 - index :: sh -> sh -> Int
 - bound :: sh -> sh -> Boundary e -> Either e sh
 - iter :: sh -> (sh -> a) -> (a -> a -> a) -> a -> a
 - iter1 :: sh -> (sh -> a) -> (a -> a -> a) -> a
 - rangeToShape :: (sh, sh) -> sh
 - shapeToRange :: sh -> (sh, sh)
 - shapeToList :: sh -> [Int]
 - listToShape :: [Int] -> sh
 
 - class  Slice sl  where
- type SliceShape sl
 - type CoSliceShape sl
 - type FullShape sl
 - sliceIndex :: sl -> SliceIndex sl (SliceShape sl) (CoSliceShape sl) (FullShape sl)
 
 - data  SliceIndex ix slice coSlice sliceDim where
- SliceNil :: SliceIndex () () () ()
 - SliceAll :: SliceIndex ix slice co dim -> SliceIndex (ix, ()) (slice, Int) co (dim, Int)
 - SliceFixed :: SliceIndex ix slice co dim -> SliceIndex (ix, Int) slice (co, Int) (dim, Int)
 
 
Array shapes, indices, and slices
class (Eq sh, Slice sh) => Shape sh whereSource
Index representation
Class of index representations (which are nested pairs)
Methods
Arguments
| :: sh | |
| -> Int | number of dimensions (>= 0); rank of the array  | 
Arguments
| :: sh | |
| -> Int | total number of elements in an array of this shape  | 
intersect :: sh -> sh -> shSource
index :: sh -> sh -> IntSource
bound :: sh -> sh -> Boundary e -> Either e shSource
iter :: sh -> (sh -> a) -> (a -> a -> a) -> a -> aSource
iter1 :: sh -> (sh -> a) -> (a -> a -> a) -> aSource
rangeToShape :: (sh, sh) -> shSource
shapeToRange :: sh -> (sh, sh)Source
shapeToList :: sh -> [Int]Source
listToShape :: [Int] -> shSource
Slice representation
Class of slice representations (which are nested pairs)
Methods
sliceIndex :: sl -> SliceIndex sl (SliceShape sl) (CoSliceShape sl) (FullShape sl)Source
data SliceIndex ix slice coSlice sliceDim whereSource
Generalised array index, which may index only in a subset of the dimensions of a shape.
Constructors
| SliceNil :: SliceIndex () () () () | |
| SliceAll :: SliceIndex ix slice co dim -> SliceIndex (ix, ()) (slice, Int) co (dim, Int) | |
| SliceFixed :: SliceIndex ix slice co dim -> SliceIndex (ix, Int) slice (co, Int) (dim, Int) | 
Instances
| Show (SliceIndex ix slice coSlice sliceDim) |