dimensions-1.0.0.0: Safe type-level dimensionality for multidimensional data.

Copyright(c) Artem Chirkin
LicenseBSD3
Maintainerchirkin@arch.ethz.ch
Safe HaskellNone
LanguageHaskell2010

Numeric.Dimensions.Idxs

Contents

Description

Provides a data type Idx that enumerates through multiple dimensions. Lower indices go first, i.e. assumed enumeration is i = i1 + i2*n1 + i3*n1*n2 + ... + ik*n1*n2*...*n(k-1). This is also to encourage column-first matrix enumeration and array layout.

Synopsis

Data types

newtype Idx n Source #

This type is used to index a single dimension; the range of indices is from 1 to n.

Note, this type has a weird Enum instance:

>>> fromEnum (Idx 7)
6

The logic behind this is that the Enum class is used to transform indices to offsets. That is, element of an array at index k :: Idx n is the element taken by an offset `k - 1 :: Int`.

Constructors

Idx 

Fields

Instances

Generic1 k (Idx k) Source # 

Associated Types

type Rep1 (Idx k) (f :: Idx k -> *) :: k -> * #

Methods

from1 :: f a -> Rep1 (Idx k) f a #

to1 :: Rep1 (Idx k) f a -> f a #

Dimensions k ds => Bounded (Idxs k ds) Source # 

Methods

minBound :: Idxs k ds #

maxBound :: Idxs k ds #

KnownDim k n => Bounded (Idx k n) Source # 

Methods

minBound :: Idx k n #

maxBound :: Idx k n #

Dimensions k ds => Enum (Idxs k ds) Source # 

Methods

succ :: Idxs k ds -> Idxs k ds #

pred :: Idxs k ds -> Idxs k ds #

toEnum :: Int -> Idxs k ds #

fromEnum :: Idxs k ds -> Int #

enumFrom :: Idxs k ds -> [Idxs k ds] #

enumFromThen :: Idxs k ds -> Idxs k ds -> [Idxs k ds] #

enumFromTo :: Idxs k ds -> Idxs k ds -> [Idxs k ds] #

enumFromThenTo :: Idxs k ds -> Idxs k ds -> Idxs k ds -> [Idxs k ds] #

KnownDim k n => Enum (Idx k n) Source # 

Methods

succ :: Idx k n -> Idx k n #

pred :: Idx k n -> Idx k n #

toEnum :: Int -> Idx k n #

fromEnum :: Idx k n -> Int #

enumFrom :: Idx k n -> [Idx k n] #

enumFromThen :: Idx k n -> Idx k n -> [Idx k n] #

enumFromTo :: Idx k n -> Idx k n -> [Idx k n] #

enumFromThenTo :: Idx k n -> Idx k n -> Idx k n -> [Idx k n] #

Eq (Idxs k xs) Source # 

Methods

(==) :: Idxs k xs -> Idxs k xs -> Bool #

(/=) :: Idxs k xs -> Idxs k xs -> Bool #

Eq (Idx k n) Source # 

Methods

(==) :: Idx k n -> Idx k n -> Bool #

(/=) :: Idx k n -> Idx k n -> Bool #

KnownDim k n => Integral (Idx k n) Source # 

Methods

quot :: Idx k n -> Idx k n -> Idx k n #

rem :: Idx k n -> Idx k n -> Idx k n #

div :: Idx k n -> Idx k n -> Idx k n #

mod :: Idx k n -> Idx k n -> Idx k n #

quotRem :: Idx k n -> Idx k n -> (Idx k n, Idx k n) #

divMod :: Idx k n -> Idx k n -> (Idx k n, Idx k n) #

toInteger :: Idx k n -> Integer #

(Typeable * k, Typeable k n) => Data (Idx k n) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Idx k n -> c (Idx k n) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Idx k n) #

toConstr :: Idx k n -> Constr #

dataTypeOf :: Idx k n -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Idx k n)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Idx k n)) #

gmapT :: (forall b. Data b => b -> b) -> Idx k n -> Idx k n #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Idx k n -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Idx k n -> r #

gmapQ :: (forall d. Data d => d -> u) -> Idx k n -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Idx k n -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Idx k n -> m (Idx k n) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Idx k n -> m (Idx k n) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Idx k n -> m (Idx k n) #

KnownDim k n => Num (Idxs k ((:) k n ([] k))) Source #

With this instance we can slightly reduce indexing expressions, e.g.

x ! (1 :* 2 :* 4) == x ! (1 :* 2 :* 4 :* U)

Methods

(+) :: Idxs k ((k ': n) [k]) -> Idxs k ((k ': n) [k]) -> Idxs k ((k ': n) [k]) #

(-) :: Idxs k ((k ': n) [k]) -> Idxs k ((k ': n) [k]) -> Idxs k ((k ': n) [k]) #

(*) :: Idxs k ((k ': n) [k]) -> Idxs k ((k ': n) [k]) -> Idxs k ((k ': n) [k]) #

negate :: Idxs k ((k ': n) [k]) -> Idxs k ((k ': n) [k]) #

abs :: Idxs k ((k ': n) [k]) -> Idxs k ((k ': n) [k]) #

signum :: Idxs k ((k ': n) [k]) -> Idxs k ((k ': n) [k]) #

fromInteger :: Integer -> Idxs k ((k ': n) [k]) #

KnownDim k n => Num (Idx k n) Source # 

Methods

(+) :: Idx k n -> Idx k n -> Idx k n #

(-) :: Idx k n -> Idx k n -> Idx k n #

(*) :: Idx k n -> Idx k n -> Idx k n #

negate :: Idx k n -> Idx k n #

abs :: Idx k n -> Idx k n #

signum :: Idx k n -> Idx k n #

fromInteger :: Integer -> Idx k n #

Ord (Idxs k xs) Source #

Compare indices by their importance in lexicorgaphic order from the last dimension to the first dimension (the last dimension is the most significant one) O(Length xs).

Literally,

compare a b = compare (reverse $ listIdxs a) (reverse $ listIdxs b)

This is the same compare rule, as for Dims. Another reason to reverse the list of indices is to have a consistent behavior when calculating index offsets:

sort == sortOn fromEnum

Methods

compare :: Idxs k xs -> Idxs k xs -> Ordering #

(<) :: Idxs k xs -> Idxs k xs -> Bool #

(<=) :: Idxs k xs -> Idxs k xs -> Bool #

(>) :: Idxs k xs -> Idxs k xs -> Bool #

(>=) :: Idxs k xs -> Idxs k xs -> Bool #

max :: Idxs k xs -> Idxs k xs -> Idxs k xs #

min :: Idxs k xs -> Idxs k xs -> Idxs k xs #

Ord (Idx k n) Source # 

Methods

compare :: Idx k n -> Idx k n -> Ordering #

(<) :: Idx k n -> Idx k n -> Bool #

(<=) :: Idx k n -> Idx k n -> Bool #

(>) :: Idx k n -> Idx k n -> Bool #

(>=) :: Idx k n -> Idx k n -> Bool #

max :: Idx k n -> Idx k n -> Idx k n #

min :: Idx k n -> Idx k n -> Idx k n #

Read (Idx k n) Source # 

Methods

readsPrec :: Int -> ReadS (Idx k n) #

readList :: ReadS [Idx k n] #

readPrec :: ReadPrec (Idx k n) #

readListPrec :: ReadPrec [Idx k n] #

KnownDim k n => Real (Idx k n) Source # 

Methods

toRational :: Idx k n -> Rational #

Show (Idxs k xs) Source # 

Methods

showsPrec :: Int -> Idxs k xs -> ShowS #

show :: Idxs k xs -> String #

showList :: [Idxs k xs] -> ShowS #

Show (Idx k n) Source # 

Methods

showsPrec :: Int -> Idx k n -> ShowS #

show :: Idx k n -> String #

showList :: [Idx k n] -> ShowS #

Generic (Idx k n) Source # 

Associated Types

type Rep (Idx k n) :: * -> * #

Methods

from :: Idx k n -> Rep (Idx k n) x #

to :: Rep (Idx k n) x -> Idx k n #

Storable (Idx k n) Source # 

Methods

sizeOf :: Idx k n -> Int #

alignment :: Idx k n -> Int #

peekElemOff :: Ptr (Idx k n) -> Int -> IO (Idx k n) #

pokeElemOff :: Ptr (Idx k n) -> Int -> Idx k n -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Idx k n) #

pokeByteOff :: Ptr b -> Int -> Idx k n -> IO () #

peek :: Ptr (Idx k n) -> IO (Idx k n) #

poke :: Ptr (Idx k n) -> Idx k n -> IO () #

type Rep1 k (Idx k) Source # 
type Rep1 k (Idx k) = D1 k (MetaData "Idx" "Numeric.Dimensions.Idxs" "dimensions-1.0.0.0-JqapYVXbO0lFbcgM5G0LVG" True) (C1 k (MetaCons "Idx" PrefixI True) (S1 k (MetaSel (Just Symbol "unIdx") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 k Word)))
type Rep (Idx k n) Source # 
type Rep (Idx k n) = D1 * (MetaData "Idx" "Numeric.Dimensions.Idxs" "dimensions-1.0.0.0-JqapYVXbO0lFbcgM5G0LVG" True) (C1 * (MetaCons "Idx" PrefixI True) (S1 * (MetaSel (Just Symbol "unIdx") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Word)))

type Idxs (xs :: [k]) = TypedList Idx xs Source #

Type-level dimensional indexing with arbitrary Word values inside. Most of the operations on it require Dimensions constraint, because the Idxs itself does not store info about dimension bounds.

Note, this type has a special Enum instance: fromEnum gives an offset of the index in a flat 1D array; this is in line with a weird Enum instance of Idx type.

idxFromWord :: forall d. KnownDim d => Word -> Maybe (Idx d) Source #

unsafeIdxFromWord :: forall d. KnownDim d => Word -> Idx d Source #

idxsFromWords :: forall ds. Dimensions ds => [Word] -> Maybe (Idx ds) Source #

Re-export dimensions types