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
- newtype ZeroBased n = ZeroBased {
- zeroBasedSize :: 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
- data DeferredIndex ix
- deferIndex :: (Indexed sh, Index sh ~ ix) => sh -> ix -> DeferredIndex ix
- revealIndex :: (InvIndexed sh, Index sh ~ ix) => sh -> DeferredIndex ix -> ix
- data sh0 :+: sh1 = sh0 :+: sh1
- data Triangular part size = Triangular {
- triangularPart :: part
- triangularSize :: size
- data Lower = Lower
- data Upper = Upper
- triangleSize :: Int -> Int
- triangleRoot :: Floating a => a -> a
Documentation
Instances
C () Source # | |
Defined in Data.Array.Comfort.Shape | |
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 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 # | |
(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 |
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 -> Index sh -> (Int, Int) Source #
uncheckedSizeOffset :: sh -> Index sh -> (Int, 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
ZeroBased
denotes a range starting at zero and has a certain length.
ZeroBased | |
|
Instances
OneBased
denotes a range starting at one and has a certain length.
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 -> Index (OneBased n) -> (Int, Int) Source # uncheckedSizeOffset :: OneBased n -> Index (OneBased n) -> (Int, 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.
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 -> 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.
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 -> 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 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
are properly implemented.
Automatically derived instances are fine.
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
.
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 | |
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 -> Index (Deferred sh) -> (Int, Int) Source # uncheckedSizeOffset :: Deferred sh -> Index (Deferred sh) -> (Int, Int) Source # | |
C sh => C (Deferred sh) Source # | |
type Index (Deferred sh) Source # | |
Defined in Data.Array.Comfort.Shape |
data DeferredIndex ix Source #
Instances
Eq (DeferredIndex ix) Source # | |
Defined in Data.Array.Comfort.Shape (==) :: DeferredIndex ix -> DeferredIndex ix -> Bool # (/=) :: DeferredIndex ix -> DeferredIndex ix -> Bool # | |
Show (DeferredIndex ix) Source # | |
Defined in Data.Array.Comfort.Shape showsPrec :: Int -> DeferredIndex ix -> ShowS # show :: DeferredIndex ix -> String # showList :: [DeferredIndex ix] -> ShowS # | |
Storable (DeferredIndex ix) Source # | |
Defined in Data.Array.Comfort.Shape sizeOf :: DeferredIndex ix -> Int # alignment :: DeferredIndex ix -> Int # peekElemOff :: Ptr (DeferredIndex ix) -> Int -> IO (DeferredIndex ix) # pokeElemOff :: Ptr (DeferredIndex ix) -> Int -> DeferredIndex ix -> IO () # peekByteOff :: Ptr b -> Int -> IO (DeferredIndex ix) # pokeByteOff :: Ptr b -> Int -> DeferredIndex ix -> IO () # peek :: Ptr (DeferredIndex ix) -> IO (DeferredIndex ix) # poke :: Ptr (DeferredIndex ix) -> DeferredIndex ix -> IO () # |
deferIndex :: (Indexed sh, Index sh ~ ix) => sh -> ix -> DeferredIndex ix Source #
revealIndex :: (InvIndexed sh, Index sh ~ ix) => sh -> DeferredIndex ix -> ix Source #
data sh0 :+: sh1 infixr 5 Source #
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 | |
(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) -> 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 # | |
data Triangular part size Source #
Triangular | |
|
Instances
triangleSize :: Int -> Int Source #
triangleRoot :: Floating a => a -> a Source #