Safe Haskell | None |
---|---|
Language | Haskell2010 |
Index types.
Synopsis
- data Z = Z
- data tail :. head = !tail :. !head
- type DIM0 = Z
- type DIM1 = DIM0 :. Int
- type DIM2 = DIM1 :. Int
- type DIM3 = DIM2 :. Int
- type DIM4 = DIM3 :. Int
- type DIM5 = DIM4 :. Int
- ix1 :: Int -> DIM1
- ix2 :: Int -> Int -> DIM2
- ix3 :: Int -> Int -> Int -> DIM3
- ix4 :: Int -> Int -> Int -> Int -> DIM4
- ix5 :: Int -> Int -> Int -> Int -> Int -> DIM5
Index types
An index of dimension zero
Instances
Eq Z Source # | |
Ord Z Source # | |
Read Z Source # | |
Show Z Source # | |
Arbitrary Z Source # | This module exports instances of |
CoArbitrary Z Source # | |
Defined in Data.Array.Repa.Arbitrary coarbitrary :: Z -> Gen b -> Gen b # | |
Shape Z Source # | |
Defined in Data.Array.Repa.Index | |
Slice Z Source # | |
Defined in Data.Array.Repa.Slice sliceOfFull :: Z -> FullShape Z -> SliceShape Z Source # fullOfSlice :: Z -> SliceShape Z -> FullShape Z Source # | |
Elt e => LoadRange D DIM2 e Source # | Compute a range of elements in a rank-2 array. |
Elt e => LoadRange C DIM2 e Source # | Compute a range of elements in a rank-2 array. |
Elt e => Load C DIM2 e Source # | Compute all elements in an rank-2 array. |
type SliceShape Z Source # | |
Defined in Data.Array.Repa.Slice | |
type FullShape Z Source # | |
Defined in Data.Array.Repa.Slice |
data tail :. head infixl 3 Source #
Our index type, used for both shapes and indices.
!tail :. !head infixl 3 |
Instances
Elt e => LoadRange D DIM2 e Source # | Compute a range of elements in a rank-2 array. |
Elt e => LoadRange C DIM2 e Source # | Compute a range of elements in a rank-2 array. |
Elt e => Load C DIM2 e Source # | Compute all elements in an rank-2 array. |
(Eq tail, Eq head) => Eq (tail :. head) Source # | |
(Ord tail, Ord head) => Ord (tail :. head) Source # | |
Defined in Data.Array.Repa.Index compare :: (tail :. head) -> (tail :. head) -> Ordering # (<) :: (tail :. head) -> (tail :. head) -> Bool # (<=) :: (tail :. head) -> (tail :. head) -> Bool # (>) :: (tail :. head) -> (tail :. head) -> Bool # (>=) :: (tail :. head) -> (tail :. head) -> Bool # | |
(Read tail, Read head) => Read (tail :. head) Source # | |
(Show tail, Show head) => Show (tail :. head) Source # | |
Arbitrary a => Arbitrary (a :. Int) Source # | |
CoArbitrary a => CoArbitrary (a :. Int) Source # | |
Defined in Data.Array.Repa.Arbitrary | |
Shape sh => Shape (sh :. Int) Source # | |
Defined in Data.Array.Repa.Index rank :: (sh :. Int) -> Int Source # intersectDim :: (sh :. Int) -> (sh :. Int) -> sh :. Int Source # addDim :: (sh :. Int) -> (sh :. Int) -> sh :. Int Source # size :: (sh :. Int) -> Int Source # sizeIsValid :: (sh :. Int) -> Bool Source # toIndex :: (sh :. Int) -> (sh :. Int) -> Int Source # fromIndex :: (sh :. Int) -> Int -> sh :. Int Source # inShapeRange :: (sh :. Int) -> (sh :. Int) -> (sh :. Int) -> Bool Source # listOfShape :: (sh :. Int) -> [Int] Source # | |
Slice sl => Slice (sl :. All) Source # | |
Defined in Data.Array.Repa.Slice | |
Slice sl => Slice (sl :. Int) Source # | |
Defined in Data.Array.Repa.Slice | |
type SliceShape (sl :. All) Source # | |
Defined in Data.Array.Repa.Slice | |
type SliceShape (sl :. Int) Source # | |
Defined in Data.Array.Repa.Slice | |
type FullShape (sl :. All) Source # | |
type FullShape (sl :. Int) Source # | |
Common dimensions.
Helper for index construction.
Use this instead of explicit constructors like (Z :. (x :: Int))
.
The this is sometimes needed to ensure that x
is constrained to
be in Int
.