Safe Haskell | None |
---|---|
Language | Haskell98 |
Synopsis
- class C sh where
- size :: sh -> Int
- uncheckedSize :: sh -> Int
- class C sh => Indexed sh where
- class Indexed sh => InvIndexed sh where
- indexFromOffset :: sh -> Int -> Index sh
- uncheckedIndexFromOffset :: sh -> Int -> Index sh
- class (C sh, Eq sh) => Static sh where
- static :: sh
- data Zero = Zero
- newtype ZeroBased n = ZeroBased {
- zeroBasedSize :: n
- zeroBasedSplit :: Real n => n -> ZeroBased n -> ZeroBased n :+: ZeroBased n
- newtype OneBased n = OneBased {
- oneBasedSize :: n
- data Range n = Range {}
- data Shifted n = Shifted {
- shiftedOffset, shiftedSize :: n
- data Enumeration n = Enumeration
- newtype Deferred sh = Deferred sh
- newtype DeferredIndex sh = DeferredIndex Int
- deferIndex :: (Indexed sh, Index sh ~ ix) => sh -> ix -> DeferredIndex sh
- revealIndex :: (InvIndexed sh, Index sh ~ ix) => sh -> DeferredIndex sh -> ix
- data sh0 :+: sh1 = sh0 :+: sh1
- newtype Square sh = Square {
- squareSize :: sh
- newtype Cube sh = Cube {
- cubeSize :: sh
- data Triangular part size = Triangular {
- triangularPart :: part
- triangularSize :: size
- data Lower = Lower
- data Upper = Upper
- type LowerTriangular = Triangular Lower
- type UpperTriangular = Triangular Upper
- lowerTriangular :: size -> LowerTriangular size
- upperTriangular :: size -> UpperTriangular size
- triangleSize :: Int -> Int
- triangleRoot :: Floating a => a -> a
- newtype Cyclic n = Cyclic {
- cyclicSize :: n
Documentation
Instances
C () Source # | |
Defined in Data.Array.Comfort.Shape | |
C Zero Source # | |
Ord n => C (Set n) Source # | |
Integral n => C (Cyclic n) Source # | |
C sh => C (Cube sh) Source # | |
C sh => C (Square sh) Source # | |
C sh => C (Deferred sh) Source # | |
(Enum n, Bounded n) => C (Enumeration n) Source # | |
Defined in Data.Array.Comfort.Shape size :: Enumeration n -> Int Source # uncheckedSize :: Enumeration n -> Int Source # | |
Integral n => C (Shifted n) Source # | |
Ix n => C (Range n) Source # | |
Integral n => C (OneBased n) Source # | |
Integral n => C (ZeroBased n) Source # | |
C f => C (Shape f) Source # | |
(C sh0, C sh1) => C (sh0, sh1) Source # | |
Defined in Data.Array.Comfort.Shape | |
(Ord k, C shape) => C (Map k shape) Source # | Concatenate many arrays according to the shapes stored in a |
(C sh0, C sh1) => C (sh0 :+: sh1) Source # | |
(TriangularPart part, C size) => C (Triangular part size) Source # | |
Defined in Data.Array.Comfort.Shape size :: Triangular part size -> Int Source # uncheckedSize :: Triangular part size -> Int Source # | |
(C sh0, C sh1, C sh2) => C (sh0, sh1, sh2) Source # | |
Defined in Data.Array.Comfort.Shape | |
C sh => C (Tagged s sh) Source # | |
class C sh => Indexed sh where Source #
indices, (sizeOffset | offset), inBounds
indices :: sh -> [Index sh] Source #
offset :: sh -> Index sh -> Int Source #
uncheckedOffset :: sh -> Index sh -> Int Source #
inBounds :: sh -> Index sh -> Bool Source #
sizeOffset :: sh -> (Int, Index sh -> Int) Source #
uncheckedSizeOffset :: sh -> (Int, Index sh -> Int) Source #
Instances
class Indexed sh => InvIndexed sh where Source #
indexFromOffset :: sh -> Int -> Index sh Source #
It should hold indexFromOffset sh k == indices sh !! k
,
but indexFromOffset
should generally be faster.
uncheckedIndexFromOffset :: sh -> Int -> Index sh Source #
Instances
class (C sh, Eq sh) => Static sh where Source #
Instances
Static () Source # | |
Defined in Data.Array.Comfort.Shape | |
Static Zero Source # | |
Defined in Data.Array.Comfort.Shape | |
Static sh => Static (Deferred sh) Source # | |
Defined in Data.Array.Comfort.Shape | |
(Enum n, Bounded n) => Static (Enumeration n) Source # | |
Defined in Data.Array.Comfort.Shape static :: Enumeration n Source # | |
(Static sh0, Static sh1) => Static (sh0, sh1) Source # | |
Defined in Data.Array.Comfort.Shape | |
(Static sh0, Static sh1) => Static (sh0 :+: sh1) Source # | |
Defined in Data.Array.Comfort.Shape | |
(TriangularPart part, Static size) => Static (Triangular part size) Source # | |
Defined in Data.Array.Comfort.Shape static :: Triangular part size Source # | |
(Static sh0, Static sh1, Static sh2) => Static (sh0, sh1, sh2) Source # | |
Defined in Data.Array.Comfort.Shape | |
Static sh => Static (Tagged s sh) Source # | |
Defined in Data.Array.Comfort.Shape |
ZeroBased
denotes a range starting at zero and has a certain length.
>>>
Shape.indices (Shape.ZeroBased (7::Int))
[0,1,2,3,4,5,6]
ZeroBased | |
|
Instances
OneBased
denotes a range starting at one and has a certain length.
>>>
Shape.indices (Shape.OneBased (7::Int))
[1,2,3,4,5,6,7]
OneBased | |
|
Instances
Functor OneBased Source # | |
Applicative OneBased Source # | |
Eq n => Eq (OneBased n) Source # | |
Show n => Show (OneBased n) Source # | |
Storable n => Storable (OneBased n) Source # | |
Defined in Data.Array.Comfort.Shape | |
NFData n => NFData (OneBased n) Source # | |
Defined in Data.Array.Comfort.Shape | |
Integral n => InvIndexed (OneBased n) Source # | |
Defined in Data.Array.Comfort.Shape | |
Integral n => Indexed (OneBased n) Source # | |
Defined in Data.Array.Comfort.Shape indices :: OneBased n -> [Index (OneBased n)] Source # offset :: OneBased n -> Index (OneBased n) -> Int Source # uncheckedOffset :: OneBased n -> Index (OneBased n) -> Int Source # inBounds :: OneBased n -> Index (OneBased n) -> Bool Source # sizeOffset :: OneBased n -> (Int, Index (OneBased n) -> Int) Source # uncheckedSizeOffset :: OneBased n -> (Int, Index (OneBased n) -> Int) Source # | |
Integral n => C (OneBased n) Source # | |
type Index (OneBased n) Source # | |
Defined in Data.Array.Comfort.Shape |
Range
denotes an inclusive range like
those of the Haskell 98 standard Array
type from the array
package.
E.g. the shape type (Range Int32, Range Int64)
is equivalent to the ix type (Int32, Int64)
for Array
s.
>>>
Shape.indices (Shape.Range (-5) (5::Int))
[-5,-4,-3,-2,-1,0,1,2,3,4,5]>>>
Shape.indices (Shape.Range (-1,-1) (1::Int,1::Int))
[(-1,-1),(-1,0),(-1,1),(0,-1),(0,0),(0,1),(1,-1),(1,0),(1,1)]
Instances
Functor Range Source # | |
Eq n => Eq (Range n) Source # | |
Show n => Show (Range n) Source # | |
Storable n => Storable (Range n) Source # | |
NFData n => NFData (Range n) Source # | |
Defined in Data.Array.Comfort.Shape | |
Ix n => InvIndexed (Range n) Source # | |
Defined in Data.Array.Comfort.Shape | |
Ix n => Indexed (Range n) Source # | |
Defined in Data.Array.Comfort.Shape indices :: Range n -> [Index (Range n)] Source # offset :: Range n -> Index (Range n) -> Int Source # uncheckedOffset :: Range n -> Index (Range n) -> Int Source # inBounds :: Range n -> Index (Range n) -> Bool Source # sizeOffset :: Range n -> (Int, Index (Range n) -> Int) Source # uncheckedSizeOffset :: Range n -> (Int, Index (Range n) -> Int) Source # | |
Ix n => C (Range n) Source # | |
type Index (Range n) Source # | |
Defined in Data.Array.Comfort.Shape |
Shifted
denotes a range defined by the start index and the length.
>>>
Shape.indices (Shape.Shifted (-4) (8::Int))
[-4,-3,-2,-1,0,1,2,3]
Shifted | |
|
Instances
Functor Shifted Source # | |
Eq n => Eq (Shifted n) Source # | |
Show n => Show (Shifted n) Source # | |
Storable n => Storable (Shifted n) Source # | |
Defined in Data.Array.Comfort.Shape | |
NFData n => NFData (Shifted n) Source # | |
Defined in Data.Array.Comfort.Shape | |
Integral n => InvIndexed (Shifted n) Source # | |
Defined in Data.Array.Comfort.Shape | |
Integral n => Indexed (Shifted n) Source # | |
Defined in Data.Array.Comfort.Shape indices :: Shifted n -> [Index (Shifted n)] Source # offset :: Shifted n -> Index (Shifted n) -> Int Source # uncheckedOffset :: Shifted n -> Index (Shifted n) -> Int Source # inBounds :: Shifted n -> Index (Shifted n) -> Bool Source # sizeOffset :: Shifted n -> (Int, Index (Shifted n) -> Int) Source # uncheckedSizeOffset :: Shifted n -> (Int, Index (Shifted n) -> Int) Source # | |
Integral n => C (Shifted n) Source # | |
type Index (Shifted n) Source # | |
Defined in Data.Array.Comfort.Shape |
data Enumeration n Source #
Enumeration
denotes a shape of fixed size
that is defined by Enum
and Bounded
methods.
For correctness it is necessary that the Enum
and Bounded
instances
are properly implemented.
Automatically derived instances are fine.
>>>
Shape.indices (Shape.Enumeration :: Shape.Enumeration Ordering)
[LT,EQ,GT]
Instances
This data type wraps another array shape.
Its index type is a wrapped Int
.
The advantages are:
No conversion forth and back Int
and Index sh
.
You can convert once using deferIndex
and revealIndex
whenever you need your application specific index type.
No need for e.g. Storable (Index sh)
, because Int
is already Storable
.
You get Indexed
and InvIndexed
instances
without the need for an Index
type.
The disadvantage is:
A deferred index should be bound to a specific shape, but this is not checked.
That is, you may obtain a deferred index for one shape
and accidentally abuse it for another shape without a warning.
Example:
>>>
:{
let sh2 = (Shape.ZeroBased (2::Int), Shape.ZeroBased (2::Int)) in let sh3 = (Shape.ZeroBased (3::Int), Shape.ZeroBased (3::Int)) in (Shape.offset sh3 $ Shape.indexFromOffset sh2 3, Shape.offset (Shape.Deferred sh3) $ Shape.indexFromOffset (Shape.Deferred sh2) 3) :} (4,3)
Deferred sh |
Instances
Eq sh => Eq (Deferred sh) Source # | |
Show sh => Show (Deferred sh) Source # | |
NFData sh => NFData (Deferred sh) Source # | |
Defined in Data.Array.Comfort.Shape | |
Static sh => Static (Deferred sh) Source # | |
Defined in Data.Array.Comfort.Shape | |
C sh => InvIndexed (Deferred sh) Source # | |
Defined in Data.Array.Comfort.Shape | |
C sh => Indexed (Deferred sh) Source # | |
Defined in Data.Array.Comfort.Shape indices :: Deferred sh -> [Index (Deferred sh)] Source # offset :: Deferred sh -> Index (Deferred sh) -> Int Source # uncheckedOffset :: Deferred sh -> Index (Deferred sh) -> Int Source # inBounds :: Deferred sh -> Index (Deferred sh) -> Bool Source # sizeOffset :: Deferred sh -> (Int, Index (Deferred sh) -> Int) Source # uncheckedSizeOffset :: Deferred sh -> (Int, Index (Deferred sh) -> Int) Source # | |
C sh => C (Deferred sh) Source # | |
type Index (Deferred sh) Source # | |
Defined in Data.Array.Comfort.Shape |
newtype DeferredIndex sh Source #
DeferredIndex
has an Ord
instance
that is based on the storage order in memory.
This way, you can put DeferredIndex
values
in a Set
or use them as keys in a Map
even if Index sh
has no Ord
instance.
The downside is, that the ordering of DeferredIndex sh
may differ from the one of Index sh
.
Instances
deferIndex :: (Indexed sh, Index sh ~ ix) => sh -> ix -> DeferredIndex sh Source #
revealIndex :: (InvIndexed sh, Index sh ~ ix) => sh -> DeferredIndex sh -> ix Source #
data sh0 :+: sh1 infixr 5 Source #
Row-major composition of two dimensions.
>>>
Shape.indices (Shape.ZeroBased (3::Int) :+: Shape.Range 'a' 'c')
[Left 0,Left 1,Left 2,Right 'a',Right 'b',Right 'c']
sh0 :+: sh1 infixr 5 |
Instances
(Eq sh0, Eq sh1) => Eq (sh0 :+: sh1) Source # | |
(Show sh0, Show sh1) => Show (sh0 :+: sh1) Source # | |
(NFData sh0, NFData sh1) => NFData (sh0 :+: sh1) Source # | |
Defined in Data.Array.Comfort.Shape | |
(Static sh0, Static sh1) => Static (sh0 :+: sh1) Source # | |
Defined in Data.Array.Comfort.Shape | |
(InvIndexed sh0, InvIndexed sh1) => InvIndexed (sh0 :+: sh1) Source # | |
Defined in Data.Array.Comfort.Shape | |
(Indexed sh0, Indexed sh1) => Indexed (sh0 :+: sh1) Source # | |
Defined in Data.Array.Comfort.Shape indices :: (sh0 :+: sh1) -> [Index (sh0 :+: sh1)] Source # offset :: (sh0 :+: sh1) -> Index (sh0 :+: sh1) -> Int Source # uncheckedOffset :: (sh0 :+: sh1) -> Index (sh0 :+: sh1) -> Int Source # inBounds :: (sh0 :+: sh1) -> Index (sh0 :+: sh1) -> Bool Source # sizeOffset :: (sh0 :+: sh1) -> (Int, Index (sh0 :+: sh1) -> Int) Source # uncheckedSizeOffset :: (sh0 :+: sh1) -> (Int, Index (sh0 :+: sh1) -> Int) Source # | |
(C sh0, C sh1) => C (sh0 :+: sh1) Source # | |
type Index (sh0 :+: sh1) Source # | |
Square
is like a Cartesian product,
but it is statically asserted that both dimension shapes match.
>>>
Shape.indices $ Shape.Square $ Shape.ZeroBased (3::Int)
[(0,0),(0,1),(0,2),(1,0),(1,1),(1,2),(2,0),(2,1),(2,2)]
Square | |
|
Instances
Functor Square Source # | |
Applicative Square Source # | |
Eq sh => Eq (Square sh) Source # | |
Show sh => Show (Square sh) Source # | |
Storable sh => Storable (Square sh) Source # | |
Defined in Data.Array.Comfort.Shape | |
NFData sh => NFData (Square sh) Source # | |
Defined in Data.Array.Comfort.Shape | |
InvIndexed sh => InvIndexed (Square sh) Source # | |
Defined in Data.Array.Comfort.Shape | |
Indexed sh => Indexed (Square sh) Source # | |
Defined in Data.Array.Comfort.Shape indices :: Square sh -> [Index (Square sh)] Source # offset :: Square sh -> Index (Square sh) -> Int Source # uncheckedOffset :: Square sh -> Index (Square sh) -> Int Source # inBounds :: Square sh -> Index (Square sh) -> Bool Source # sizeOffset :: Square sh -> (Int, Index (Square sh) -> Int) Source # uncheckedSizeOffset :: Square sh -> (Int, Index (Square sh) -> Int) Source # | |
C sh => C (Square sh) Source # | |
type Index (Square sh) Source # | |
Defined in Data.Array.Comfort.Shape |
Cube
is like a Cartesian product,
but it is statically asserted that both dimension shapes match.
>>>
Shape.indices $ Shape.Cube $ Shape.ZeroBased (2::Int)
[(0,0,0),(0,0,1),(0,1,0),(0,1,1),(1,0,0),(1,0,1),(1,1,0),(1,1,1)]
Instances
Functor Cube Source # | |
Applicative Cube Source # | |
Eq sh => Eq (Cube sh) Source # | |
Show sh => Show (Cube sh) Source # | |
Storable sh => Storable (Cube sh) Source # | |
NFData sh => NFData (Cube sh) Source # | |
Defined in Data.Array.Comfort.Shape | |
InvIndexed sh => InvIndexed (Cube sh) Source # | |
Defined in Data.Array.Comfort.Shape | |
Indexed sh => Indexed (Cube sh) Source # | |
Defined in Data.Array.Comfort.Shape indices :: Cube sh -> [Index (Cube sh)] Source # offset :: Cube sh -> Index (Cube sh) -> Int Source # uncheckedOffset :: Cube sh -> Index (Cube sh) -> Int Source # inBounds :: Cube sh -> Index (Cube sh) -> Bool Source # sizeOffset :: Cube sh -> (Int, Index (Cube sh) -> Int) Source # uncheckedSizeOffset :: Cube sh -> (Int, Index (Cube sh) -> Int) Source # | |
C sh => C (Cube sh) Source # | |
type Index (Cube sh) Source # | |
data Triangular part size Source #
>>>
Shape.indices $ Shape.Triangular Shape.Upper $ Shape.ZeroBased (3::Int)
[(0,0),(0,1),(0,2),(1,1),(1,2),(2,2)]>>>
Shape.indices $ Shape.Triangular Shape.Lower $ Shape.ZeroBased (3::Int)
[(0,0),(1,0),(1,1),(2,0),(2,1),(2,2)]
Triangular | |
|
Instances
type LowerTriangular = Triangular Lower Source #
type UpperTriangular = Triangular Upper Source #
lowerTriangular :: size -> LowerTriangular size Source #
upperTriangular :: size -> UpperTriangular size Source #
triangleSize :: Int -> Int Source #
triangleRoot :: Floating a => a -> a Source #
Cyclic
is a shape, where the indices wrap around at the array boundaries.
E.g.
let shape = Shape.Cyclic (10::Int) in Shape.offset shape (-1) == Shape.offset shape 9
This also means that there are multiple indices that address the same array element.
>>>
Shape.indices (Shape.Cyclic (7::Int))
[0,1,2,3,4,5,6]
Cyclic | |
|
Instances
Functor Cyclic Source # | |
Applicative Cyclic Source # | |
Eq n => Eq (Cyclic n) Source # | |
Show n => Show (Cyclic n) Source # | |
Storable n => Storable (Cyclic n) Source # | |
Defined in Data.Array.Comfort.Shape | |
NFData n => NFData (Cyclic n) Source # | |
Defined in Data.Array.Comfort.Shape | |
Integral n => InvIndexed (Cyclic n) Source # | |
Defined in Data.Array.Comfort.Shape | |
Integral n => Indexed (Cyclic n) Source # | |
Defined in Data.Array.Comfort.Shape indices :: Cyclic n -> [Index (Cyclic n)] Source # offset :: Cyclic n -> Index (Cyclic n) -> Int Source # uncheckedOffset :: Cyclic n -> Index (Cyclic n) -> Int Source # inBounds :: Cyclic n -> Index (Cyclic n) -> Bool Source # sizeOffset :: Cyclic n -> (Int, Index (Cyclic n) -> Int) Source # uncheckedSizeOffset :: Cyclic n -> (Int, Index (Cyclic n) -> Int) Source # | |
Integral n => C (Cyclic n) Source # | |
type Index (Cyclic n) Source # | |
Defined in Data.Array.Comfort.Shape |