dimensions-2.1.1.0: Safe type-level dimensionality for multidimensional data.
Copyright(c) Artem Chirkin
LicenseBSD3
Safe HaskellNone
LanguageHaskell2010

Numeric.Dimensions.Idx

Description

Provides a data type Idx to index Dim and Idxs that enumerates through multiple dimensions.

Higher indices go first, i.e. assumed enumeration is i = i1*n1*n2*...*n(k-1) + ... + i(k-2)*n1*n2 + i(k-1)*n1 + ik This corresponds to row-first layout of matrices and multidimenional arrays.

Type safety

Same as Dim and Dims, Idx and Idxs defined in this module incorporate two different indexing mechanics. Both of them can be specified with exact Nat values (when d :: Nat or d ~ N n), or with lower bound values (i.e. d ~ XN m). In the former case, the Idx/Idxs type itself guarantees that the value inside is within the Dim/Dims bounds. In the latter case, Idx/Idxs can contain any values of type Word. In other words:

  • (d :: Nat) || (d ~ N n) => using Idx d to index data is always safe, but creating an index using unsafe functions can yield an OutOfDimBounds exception at runtime.
  • (d ~ XN m) => using Idx d to index data can result in an OutOfDimBounds exception, but you can safely manipulate the index itself using familiar interfaces, such as Enum, Num, etc; as if Idx d was a plain synonym to Word.
Synopsis

Data types

data Idx (d :: k) where Source #

This type is used to index a single dimension.

  • (k ~ Nat) => the range of indices is from 0 to d-1.
  • (d ~ N n) => the range of indices is from 0 to n-1.
  • (d ~ XN m) => the range of indices is from 0 to maxBound :: Word.

That is, using Idx (n :: Nat) or Idx (N n) is guaranteed to be safe by the type system. But an index of type Idx (XN m) can have any value, and using it may yield an OutOfDimBounds exception -- just the same as a generic index function that takes a plain Int or Word as an argument. Thus, if you have data indexed by (XN m), I would suggest to use lookup-like functions that return Maybe. You're warned.

Bundled Patterns

pattern Idx :: forall d. BoundedDim d => Word -> Idx d

Convert between Word and Idx.

Converting from Idx to Word is always safe.

Converting from Word to Idx generally is unsafe:

  • (k ~ Nat) => if w >= d, it fails with an OutOfDimBounds exception.
  • (d ~ N n) => if w >= n, it fails with an OutOfDimBounds exception.
  • (d ~ XN m) => the constructor always succeeds, but using the result for indexing may fail with an OutOfDimBounds exception later.

If unsafeindices flag it turned on, this function always succeeds.

Instances

Instances details
BoundedDims ds => Bounded (Idxs ds) Source # 
Instance details

Defined in Numeric.Dimensions.Idx

Methods

minBound :: Idxs ds #

maxBound :: Idxs ds #

BoundedDim d => Bounded (Idx d) Source # 
Instance details

Defined in Numeric.Dimensions.Idx

Methods

minBound :: Idx d #

maxBound :: Idx d #

Dimensions ds => Enum (Idxs ds) Source #

ds must be fixed (either [Nat] or all (N n)) to know exact bounds in each dimension.

Instance details

Defined in Numeric.Dimensions.Idx

Methods

succ :: Idxs ds -> Idxs ds #

pred :: Idxs ds -> Idxs ds #

toEnum :: Int -> Idxs ds #

fromEnum :: Idxs ds -> Int #

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

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

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

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

KnownDim n => Enum (Idx n) Source # 
Instance details

Defined in Numeric.Dimensions.Idx

Methods

succ :: Idx n -> Idx n #

pred :: Idx n -> Idx n #

toEnum :: Int -> Idx n #

fromEnum :: Idx n -> Int #

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

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

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

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

BoundedDim d => Enum (Idx d) Source #

Although Enum (Idx d) requires BoundedDim d, it does not use maxBound when (d ~ XN m). You can use list comprehensions safely for known dims ((k ~ Nat) or (d ~ N d)), but you may get an index larger than your struct to be indexed when d ~ XN m.

Instance details

Defined in Numeric.Dimensions.Idx

Methods

succ :: Idx d -> Idx d #

pred :: Idx d -> Idx d #

toEnum :: Int -> Idx d #

fromEnum :: Idx d -> Int #

enumFrom :: Idx d -> [Idx d] #

enumFromThen :: Idx d -> Idx d -> [Idx d] #

enumFromTo :: Idx d -> Idx d -> [Idx d] #

enumFromThenTo :: Idx d -> Idx d -> Idx d -> [Idx d] #

Eq (Idxs xs) Source # 
Instance details

Defined in Numeric.Dimensions.Idx

Methods

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

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

Eq (Idx d) Source # 
Instance details

Defined in Numeric.Dimensions.Idx

Methods

(==) :: Idx d -> Idx d -> Bool #

(/=) :: Idx d -> Idx d -> Bool #

BoundedDim d => Integral (Idx d) Source # 
Instance details

Defined in Numeric.Dimensions.Idx

Methods

quot :: Idx d -> Idx d -> Idx d #

rem :: Idx d -> Idx d -> Idx d #

div :: Idx d -> Idx d -> Idx d #

mod :: Idx d -> Idx d -> Idx d #

quotRem :: Idx d -> Idx d -> (Idx d, Idx d) #

divMod :: Idx d -> Idx d -> (Idx d, Idx d) #

toInteger :: Idx d -> Integer #

(Typeable d, Typeable k) => Data (Idx d) Source # 
Instance details

Defined in Numeric.Dimensions.Idx

Methods

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

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

toConstr :: Idx d -> Constr #

dataTypeOf :: Idx d -> DataType #

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

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

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

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

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

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

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

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

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

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

KnownDim n => Num (Idx n) Source # 
Instance details

Defined in Numeric.Dimensions.Idx

Methods

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

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

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

negate :: Idx n -> Idx n #

abs :: Idx n -> Idx n #

signum :: Idx n -> Idx n #

fromInteger :: Integer -> Idx n #

BoundedDim d => Num (Idx d) Source #

Although Num (Idx d) requires BoundedDim d, it does not use maxBound when (d ~ XN m). That is, if (d ~ XN m) then i = fromIntegral n always succeeds.

Instance details

Defined in Numeric.Dimensions.Idx

Methods

(+) :: Idx d -> Idx d -> Idx d #

(-) :: Idx d -> Idx d -> Idx d #

(*) :: Idx d -> Idx d -> Idx d #

negate :: Idx d -> Idx d #

abs :: Idx d -> Idx d #

signum :: Idx d -> Idx d #

fromInteger :: Integer -> Idx d #

Ord (Idxs xs) Source #

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

Literally,

compare a b = compare (listIdxs a) (listIdxs b)

This is the same compare rule, as for Dims. This is also consistent with offsets:

sort == sortOn fromEnum
Instance details

Defined in Numeric.Dimensions.Idx

Methods

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

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

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

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

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

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

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

Ord (Idx d) Source # 
Instance details

Defined in Numeric.Dimensions.Idx

Methods

compare :: Idx d -> Idx d -> Ordering #

(<) :: Idx d -> Idx d -> Bool #

(<=) :: Idx d -> Idx d -> Bool #

(>) :: Idx d -> Idx d -> Bool #

(>=) :: Idx d -> Idx d -> Bool #

max :: Idx d -> Idx d -> Idx d #

min :: Idx d -> Idx d -> Idx d #

BoundedDims xs => Read (Idxs xs) Source # 
Instance details

Defined in Numeric.Dimensions.Idx

BoundedDim d => Read (Idx d) Source # 
Instance details

Defined in Numeric.Dimensions.Idx

BoundedDim d => Real (Idx d) Source # 
Instance details

Defined in Numeric.Dimensions.Idx

Methods

toRational :: Idx d -> Rational #

Show (Idxs xs) Source # 
Instance details

Defined in Numeric.Dimensions.Idx

Methods

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

show :: Idxs xs -> String #

showList :: [Idxs xs] -> ShowS #

Show (Idx d) Source # 
Instance details

Defined in Numeric.Dimensions.Idx

Methods

showsPrec :: Int -> Idx d -> ShowS #

show :: Idx d -> String #

showList :: [Idx d] -> ShowS #

Generic (Idx d) Source # 
Instance details

Defined in Numeric.Dimensions.Idx

Associated Types

type Rep (Idx d) :: Type -> Type #

Methods

from :: Idx d -> Rep (Idx d) x #

to :: Rep (Idx d) x -> Idx d #

Storable (Idx d) Source # 
Instance details

Defined in Numeric.Dimensions.Idx

Methods

sizeOf :: Idx d -> Int #

alignment :: Idx d -> Int #

peekElemOff :: Ptr (Idx d) -> Int -> IO (Idx d) #

pokeElemOff :: Ptr (Idx d) -> Int -> Idx d -> IO () #

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

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

peek :: Ptr (Idx d) -> IO (Idx d) #

poke :: Ptr (Idx d) -> Idx d -> IO () #

type Rep (Idx d) Source # 
Instance details

Defined in Numeric.Dimensions.Idx

type Rep (Idx d) = D1 ('MetaData "Idx" "Numeric.Dimensions.Idx" "dimensions-2.1.1.0-2AAe0No328E14IWRQP3FUr" 'True) (C1 ('MetaCons "Idx'" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word)))

type Idxs = TypedList Idx :: [k] -> Type Source #

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

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

Convert an arbitrary Word to Idx. This is a safe alternative to the pattern Idx.

Note, when (d ~ XN m), it returns Nothing if w >= m. Thus, the resulting index is always safe to use (but you cannot index stuff beyond DimBound d this way).

idxToWord :: forall d. Idx d -> Word Source #

Get the value of an Idx.

listIdxs :: forall ds. Idxs ds -> [Word] Source #

O(1) Convert Idxs xs to a plain list of words.

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

O(n) Convert a plain list of words into an Idxs, while checking the index bounds.

Same as with idxFromWord, it is always safe to use the resulting index, but you cannot index stuff outside of the DimsBound ds this way.

liftIdxs :: forall (ds :: [XNat]) (ns :: [Nat]). FixedDims ds ns => Idxs ns -> Idxs ds Source #

O(1) Coerce a Nat-indexed list of indices into a XNat-indexed one. This function does not need any runtime checks and thus runs in constant time.

unliftIdxs :: forall (ds :: [XNat]) (ns :: [Nat]). (FixedDims ds ns, Dimensions ns) => Idxs ds -> Maybe (Idxs ns) Source #

O(n) Coerce a XNat-indexed list of indices into a Nat-indexed one. This function checks if an index is within Dim bounds for every dimension.

unsafeUnliftIdxs :: forall (ds :: [XNat]) (ns :: [Nat]). (FixedDims ds ns, Dimensions ns) => Idxs ds -> Idxs ns Source #

Coerce a XNat-indexed list of indices into a Nat-indexed one. Can throw an OutOfDimBounds exception unless unsafeindices flag is active.

data TypedList (f :: k -> Type) (xs :: [k]) where Source #

Type-indexed list

Bundled Patterns

pattern XIdxs :: forall (ds :: [XNat]) (ns :: [Nat]). (FixedDims ds ns, Dimensions ns) => Idxs ns -> Idxs ds

Transform between Nat-indexed and XNat-indexed Idxs.

Note, this pattern is not a COMPLETE match, because converting from XNat to Nat indexed Idxs may fail (see unliftIdxs).

pattern U :: forall (k :: Type) (f :: k -> Type) (xs :: [k]). () => xs ~ '[] => TypedList f xs

Zero-length type list

pattern (:*) :: forall f xs. () => forall y ys. xs ~ (y ': ys) => f y -> TypedList f ys -> TypedList f xs infixr 5

Constructing a type-indexed list

pattern Empty :: forall (k :: Type) (f :: k -> Type) (xs :: [k]). () => xs ~ '[] => TypedList f xs

Zero-length type list; synonym to U.

pattern Cons :: forall f xs. () => forall y ys. xs ~ (y ': ys) => f y -> TypedList f ys -> TypedList f xs

Constructing a type-indexed list in the canonical way

pattern Snoc :: forall f xs. () => forall sy y. SnocList sy y xs => TypedList f sy -> f y -> TypedList f xs

Constructing a type-indexed list from the other end

pattern Reverse :: forall f xs. () => forall sx. ReverseList xs sx => TypedList f sx -> TypedList f xs

Reverse a typed list

Instances

Instances details
(RepresentableList xs, All Bounded xs) => Bounded (Tuple xs) Source # 
Instance details

Defined in Numeric.Tuple.Strict

Methods

minBound :: Tuple xs #

maxBound :: Tuple xs #

(RepresentableList xs, All Bounded xs) => Bounded (Tuple xs) Source # 
Instance details

Defined in Numeric.Tuple.Lazy

Methods

minBound :: Tuple xs #

maxBound :: Tuple xs #

All Eq xs => Eq (Tuple xs) Source # 
Instance details

Defined in Numeric.Tuple.Strict

Methods

(==) :: Tuple xs -> Tuple xs -> Bool #

(/=) :: Tuple xs -> Tuple xs -> Bool #

All Eq xs => Eq (Tuple xs) Source # 
Instance details

Defined in Numeric.Tuple.Lazy

Methods

(==) :: Tuple xs -> Tuple xs -> Bool #

(/=) :: Tuple xs -> Tuple xs -> Bool #

(All Eq xs, All Ord xs) => Ord (Tuple xs) Source #

Lexicorgaphic ordering; same as normal Haskell lists.

Instance details

Defined in Numeric.Tuple.Strict

Methods

compare :: Tuple xs -> Tuple xs -> Ordering #

(<) :: Tuple xs -> Tuple xs -> Bool #

(<=) :: Tuple xs -> Tuple xs -> Bool #

(>) :: Tuple xs -> Tuple xs -> Bool #

(>=) :: Tuple xs -> Tuple xs -> Bool #

max :: Tuple xs -> Tuple xs -> Tuple xs #

min :: Tuple xs -> Tuple xs -> Tuple xs #

(All Eq xs, All Ord xs) => Ord (Tuple xs) Source #

Lexicorgaphic ordering; same as normal Haskell lists.

Instance details

Defined in Numeric.Tuple.Lazy

Methods

compare :: Tuple xs -> Tuple xs -> Ordering #

(<) :: Tuple xs -> Tuple xs -> Bool #

(<=) :: Tuple xs -> Tuple xs -> Bool #

(>) :: Tuple xs -> Tuple xs -> Bool #

(>=) :: Tuple xs -> Tuple xs -> Bool #

max :: Tuple xs -> Tuple xs -> Tuple xs #

min :: Tuple xs -> Tuple xs -> Tuple xs #

(All Read xs, RepresentableList xs) => Read (Tuple xs) Source # 
Instance details

Defined in Numeric.Tuple.Strict

(All Read xs, RepresentableList xs) => Read (Tuple xs) Source # 
Instance details

Defined in Numeric.Tuple.Lazy

All Show xs => Show (Tuple xs) Source # 
Instance details

Defined in Numeric.Tuple.Strict

Methods

showsPrec :: Int -> Tuple xs -> ShowS #

show :: Tuple xs -> String #

showList :: [Tuple xs] -> ShowS #

All Show xs => Show (Tuple xs) Source # 
Instance details

Defined in Numeric.Tuple.Lazy

Methods

showsPrec :: Int -> Tuple xs -> ShowS #

show :: Tuple xs -> String #

showList :: [Tuple xs] -> ShowS #

All Semigroup xs => Semigroup (Tuple xs) Source # 
Instance details

Defined in Numeric.Tuple.Strict

Methods

(<>) :: Tuple xs -> Tuple xs -> Tuple xs #

sconcat :: NonEmpty (Tuple xs) -> Tuple xs #

stimes :: Integral b => b -> Tuple xs -> Tuple xs #

All Semigroup xs => Semigroup (Tuple xs) Source # 
Instance details

Defined in Numeric.Tuple.Lazy

Methods

(<>) :: Tuple xs -> Tuple xs -> Tuple xs #

sconcat :: NonEmpty (Tuple xs) -> Tuple xs #

stimes :: Integral b => b -> Tuple xs -> Tuple xs #

(RepresentableList xs, All Semigroup xs, All Monoid xs) => Monoid (Tuple xs) Source # 
Instance details

Defined in Numeric.Tuple.Strict

Methods

mempty :: Tuple xs #

mappend :: Tuple xs -> Tuple xs -> Tuple xs #

mconcat :: [Tuple xs] -> Tuple xs #

(RepresentableList xs, All Semigroup xs, All Monoid xs) => Monoid (Tuple xs) Source # 
Instance details

Defined in Numeric.Tuple.Lazy

Methods

mempty :: Tuple xs #

mappend :: Tuple xs -> Tuple xs -> Tuple xs #

mconcat :: [Tuple xs] -> Tuple xs #

BoundedDims ds => Bounded (Idxs ds) Source # 
Instance details

Defined in Numeric.Dimensions.Idx

Methods

minBound :: Idxs ds #

maxBound :: Idxs ds #

Dimensions ds => Enum (Idxs ds) Source #

ds must be fixed (either [Nat] or all (N n)) to know exact bounds in each dimension.

Instance details

Defined in Numeric.Dimensions.Idx

Methods

succ :: Idxs ds -> Idxs ds #

pred :: Idxs ds -> Idxs ds #

toEnum :: Int -> Idxs ds #

fromEnum :: Idxs ds -> Int #

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

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

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

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

Eq (Dims ds) Source # 
Instance details

Defined in Numeric.Dimensions.Dim

Methods

(==) :: Dims ds -> Dims ds -> Bool #

(/=) :: Dims ds -> Dims ds -> Bool #

Eq (Dims ds) Source # 
Instance details

Defined in Numeric.Dimensions.Dim

Methods

(==) :: Dims ds -> Dims ds -> Bool #

(/=) :: Dims ds -> Dims ds -> Bool #

Eq (Idxs xs) Source # 
Instance details

Defined in Numeric.Dimensions.Idx

Methods

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

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

Ord (Dims ds) Source # 
Instance details

Defined in Numeric.Dimensions.Dim

Methods

compare :: Dims ds -> Dims ds -> Ordering #

(<) :: Dims ds -> Dims ds -> Bool #

(<=) :: Dims ds -> Dims ds -> Bool #

(>) :: Dims ds -> Dims ds -> Bool #

(>=) :: Dims ds -> Dims ds -> Bool #

max :: Dims ds -> Dims ds -> Dims ds #

min :: Dims ds -> Dims ds -> Dims ds #

Ord (Dims ds) Source # 
Instance details

Defined in Numeric.Dimensions.Dim

Methods

compare :: Dims ds -> Dims ds -> Ordering #

(<) :: Dims ds -> Dims ds -> Bool #

(<=) :: Dims ds -> Dims ds -> Bool #

(>) :: Dims ds -> Dims ds -> Bool #

(>=) :: Dims ds -> Dims ds -> Bool #

max :: Dims ds -> Dims ds -> Dims ds #

min :: Dims ds -> Dims ds -> Dims ds #

Ord (Idxs xs) Source #

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

Literally,

compare a b = compare (listIdxs a) (listIdxs b)

This is the same compare rule, as for Dims. This is also consistent with offsets:

sort == sortOn fromEnum
Instance details

Defined in Numeric.Dimensions.Idx

Methods

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

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

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

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

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

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

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

BoundedDims xs => Read (Dims xs) Source # 
Instance details

Defined in Numeric.Dimensions.Dim

BoundedDims xs => Read (Idxs xs) Source # 
Instance details

Defined in Numeric.Dimensions.Idx

Show (Dims xs) Source # 
Instance details

Defined in Numeric.Dimensions.Dim

Methods

showsPrec :: Int -> Dims xs -> ShowS #

show :: Dims xs -> String #

showList :: [Dims xs] -> ShowS #

Show (Idxs xs) Source # 
Instance details

Defined in Numeric.Dimensions.Idx

Methods

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

show :: Idxs xs -> String #

showList :: [Idxs xs] -> ShowS #

(Typeable k, Typeable f, Typeable xs, All Data (Map f xs)) => Data (TypedList f xs) Source #

Term-level structure of a TypedList f xs is fully determined by its type Typeable xs. Thus, gunfold does not use its last argument (Constr) at all, relying on the structure of the type parameter.

Instance details

Defined in Numeric.TypedList

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TypedList f xs -> c (TypedList f xs) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (TypedList f xs) #

toConstr :: TypedList f xs -> Constr #

dataTypeOf :: TypedList f xs -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (TypedList f xs)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (TypedList f xs)) #

gmapT :: (forall b. Data b => b -> b) -> TypedList f xs -> TypedList f xs #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TypedList f xs -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TypedList f xs -> r #

gmapQ :: (forall d. Data d => d -> u) -> TypedList f xs -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TypedList f xs -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TypedList f xs -> m (TypedList f xs) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TypedList f xs -> m (TypedList f xs) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TypedList f xs -> m (TypedList f xs) #

Generic (TypedList f xs) Source # 
Instance details

Defined in Numeric.TypedList

Associated Types

type Rep (TypedList f xs) :: Type -> Type #

Methods

from :: TypedList f xs -> Rep (TypedList f xs) x #

to :: Rep (TypedList f xs) x -> TypedList f xs #

type Rep (TypedList f xs) Source # 
Instance details

Defined in Numeric.TypedList

type Rep (TypedList f xs)

Checking the index bounds

data OutOfDimBounds Source #

Typically, this exception can occur in the following cases:

  • Converting from integral values to Idx d when d ~ N n or d :: Nat.
  • Using Enum and Num when d ~ N n or d :: Nat.
  • Converting from Idx (XN m :: XNat) to Idx (n :: Nat).
  • Indexing or slicing data using Idx (XN m :: XNat).

If you are mad and want to avoid any overhead related to bounds checking and the related error handling, you can turn on the unsafeindices flag to remove all of this from the library at once.

Constructors

OutOfDimBounds 

Fields

outOfDimBounds Source #

Arguments

:: (HasCallStack, Integral i) 
=> String

Label (e.g. function name)

-> i

Bad index

-> Word

Target dim

-> Maybe Word

SubSpace Dim, if applicable.

-> Maybe ([Word], [Word])

Larger picture: Dims and Idxs

-> a 

Throw an OutOfDimBounds exception.

outOfDimBoundsNoCallStack Source #

Arguments

:: Integral i 
=> String

Label (e.g. function name)

-> i

Bad index

-> Word

Target dim

-> Maybe Word

SubSpace Dim, if applicable.

-> Maybe ([Word], [Word])

Larger picture: Dims and Idxs

-> a 

Throw an OutOfDimBounds exception without the CallStack attached.