Safe Haskell | None |
---|---|
Language | Haskell98 |
Data.Array.Comfort.Shape
Synopsis
- class C sh where
- class C sh => Indexed sh where
- class Indexed sh => InvIndexed sh where
- newtype ZeroBased n = ZeroBased {
- zeroBasedSize :: n
- newtype OneBased n = OneBased {
- oneBasedSize :: n
- data Range n = Range {}
- data Shifted n = Shifted {
- shiftedOffset, shiftedSize :: n
- data sh0 :+: sh1 = sh0 :+: sh1
Documentation
Minimal complete definition
Instances
C () Source # | |
Defined in Data.Array.Comfort.Shape | |
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 sh0, C sh1) => C (sh0, sh1) Source # | Row-major composition of two dimensions. |
Defined in Data.Array.Comfort.Shape | |
(C sh0, C sh1) => C (sh0 :+: sh1) Source # | |
(C sh0, C sh1, C sh2) => C (sh0, sh1, sh2) Source # | |
Defined in Data.Array.Comfort.Shape |
class C sh => Indexed sh where Source #
Minimal complete definition
indices, (sizeOffset | offset), inBounds
Methods
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 -> Index sh -> (Int, Int) Source #
uncheckedSizeOffset :: sh -> Index sh -> (Int, Int) Source #
Instances
class Indexed sh => InvIndexed sh where Source #
Minimal complete definition
Methods
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
ZeroBased
denotes a range starting at zero and has a certain length.
Constructors
ZeroBased | |
Fields
|
Instances
OneBased
denotes a range starting at one and has a certain length.
Constructors
OneBased | |
Fields
|
Instances
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.
Instances
Functor Range Source # | |
Eq n => Eq (Range n) Source # | |
Show n => Show (Range n) Source # | |
Storable n => Storable (Range n) Source # | |
Ix n => InvIndexed (Range n) Source # | |
Defined in Data.Array.Comfort.Shape | |
Ix n => Indexed (Range n) Source # | |
Defined in Data.Array.Comfort.Shape Methods 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 -> Index (Range n) -> (Int, Int) Source # uncheckedSizeOffset :: Range n -> Index (Range n) -> (Int, 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.
Constructors
Shifted | |
Fields
|
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 | |
Integral n => InvIndexed (Shifted n) Source # | |
Defined in Data.Array.Comfort.Shape | |
Integral n => Indexed (Shifted n) Source # | |
Defined in Data.Array.Comfort.Shape Methods 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 -> Index (Shifted n) -> (Int, Int) Source # uncheckedSizeOffset :: Shifted n -> Index (Shifted n) -> (Int, Int) Source # | |
Integral n => C (Shifted n) Source # | |
type Index (Shifted n) Source # | |
Defined in Data.Array.Comfort.Shape |
data sh0 :+: sh1 infixr 5 Source #
Constructors
sh0 :+: sh1 infixr 5 |
Instances
(Eq sh0, Eq sh1) => Eq (sh0 :+: sh1) Source # | |
(Show sh0, Show sh1) => Show (sh0 :+: sh1) Source # | |
(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 Methods 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) -> Index (sh0 :+: sh1) -> (Int, Int) Source # uncheckedSizeOffset :: (sh0 :+: sh1) -> Index (sh0 :+: sh1) -> (Int, Int) Source # | |
(C sh0, C sh1) => C (sh0 :+: sh1) Source # | |
type Index (sh0 :+: sh1) Source # | |