| Copyright | (c) Artem Chirkin |
|---|---|
| License | BSD3 |
| Safe Haskell | None |
| Language | Haskell2010 |
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) =>usingIdx dto index data is always safe, but creating an index using unsafe functions can yield anOutOfDimBoundsexception at runtime.(d ~ XN m) =>usingIdx dto index data can result in anOutOfDimBoundsexception, but you can safely manipulate the index itself using familiar interfaces, such asEnum,Num, etc; as ifIdx dwas a plain synonym toWord.
Synopsis
- data Idx (d :: k) where
- pattern Idx :: forall d. BoundedDim d => Word -> Idx d
- type Idxs = TypedList Idx :: [k] -> Type
- idxFromWord :: forall d. BoundedDim d => Word -> Maybe (Idx d)
- idxToWord :: forall d. Idx d -> Word
- listIdxs :: forall ds. Idxs ds -> [Word]
- idxsFromWords :: forall ds. BoundedDims ds => [Word] -> Maybe (Idxs ds)
- liftIdxs :: forall (ds :: [XNat]) (ns :: [Nat]). FixedDims ds ns => Idxs ns -> Idxs ds
- unliftIdxs :: forall (ds :: [XNat]) (ns :: [Nat]). (FixedDims ds ns, Dimensions ns) => Idxs ds -> Maybe (Idxs ns)
- unsafeUnliftIdxs :: forall (ds :: [XNat]) (ns :: [Nat]). (FixedDims ds ns, Dimensions ns) => Idxs ds -> Idxs ns
- data TypedList (f :: k -> Type) (xs :: [k]) where
- pattern XIdxs :: forall (ds :: [XNat]) (ns :: [Nat]). (FixedDims ds ns, Dimensions ns) => Idxs ns -> Idxs ds
- pattern U :: forall (k :: Type) (f :: k -> Type) (xs :: [k]). () => xs ~ '[] => TypedList f xs
- pattern (:*) :: forall f xs. () => forall y ys. xs ~ (y ': ys) => f y -> TypedList f ys -> TypedList f xs
- pattern Empty :: forall (k :: Type) (f :: k -> Type) (xs :: [k]). () => xs ~ '[] => TypedList f xs
- pattern Cons :: forall f xs. () => forall y ys. xs ~ (y ': ys) => f y -> TypedList f ys -> TypedList f xs
- pattern Snoc :: forall f xs. () => forall sy y. SnocList sy y xs => TypedList f sy -> f y -> TypedList f xs
- pattern Reverse :: forall f xs. () => forall sx. ReverseList xs sx => TypedList f sx -> TypedList f xs
- data OutOfDimBounds = OutOfDimBounds {}
- outOfDimBounds :: (HasCallStack, Integral i) => String -> i -> Word -> Maybe Word -> Maybe ([Word], [Word]) -> a
- outOfDimBoundsNoCallStack :: Integral i => String -> i -> Word -> Maybe Word -> Maybe ([Word], [Word]) -> a
Data types
data Idx (d :: k) where Source #
This type is used to index a single dimension.
(k ~ Nat) =>the range of indices is from0tod-1.(d ~ N n) =>the range of indices is from0ton-1.(d ~ XN m) =>the range of indices is from0tomaxBound :: 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 | Converting from Converting from
If |
Instances
| BoundedDims ds => Bounded (Idxs ds) Source # | |
| BoundedDim d => Bounded (Idx d) Source # | |
| Dimensions ds => Enum (Idxs ds) Source # |
|
| KnownDim n => Enum (Idx n) Source # | |
Defined in Numeric.Dimensions.Idx | |
| BoundedDim d => Enum (Idx d) Source # | Although |
Defined in Numeric.Dimensions.Idx | |
| Eq (Idxs xs) Source # | |
| Eq (Idx d) Source # | |
| BoundedDim d => Integral (Idx d) Source # | |
| (Typeable d, Typeable k) => Data (Idx d) Source # | |
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) # 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 # | |
| BoundedDim d => Num (Idx d) Source # | Although |
| 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 sort == sortOn fromEnum |
Defined in Numeric.Dimensions.Idx | |
| Ord (Idx d) Source # | |
| BoundedDims xs => Read (Idxs xs) Source # | |
| BoundedDim d => Read (Idx d) Source # | |
| BoundedDim d => Real (Idx d) Source # | |
Defined in Numeric.Dimensions.Idx Methods toRational :: Idx d -> Rational # | |
| Show (Idxs xs) Source # | |
| Show (Idx d) Source # | |
| Generic (Idx d) Source # | |
| Storable (Idx d) Source # | |
| type Rep (Idx d) Source # | |
Defined in Numeric.Dimensions.Idx | |
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).
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 Note, this pattern is not a |
| 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 |
| 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
| (RepresentableList xs, All Bounded xs) => Bounded (Tuple xs) Source # | |
| (RepresentableList xs, All Bounded xs) => Bounded (Tuple xs) Source # | |
| All Eq xs => Eq (Tuple xs) Source # | |
| All Eq xs => Eq (Tuple xs) Source # | |
| (All Eq xs, All Ord xs) => Ord (Tuple xs) Source # | Lexicorgaphic ordering; same as normal Haskell lists. |
Defined in Numeric.Tuple.Strict | |
| (All Eq xs, All Ord xs) => Ord (Tuple xs) Source # | Lexicorgaphic ordering; same as normal Haskell lists. |
Defined in Numeric.Tuple.Lazy | |
| (All Read xs, RepresentableList xs) => Read (Tuple xs) Source # | |
| (All Read xs, RepresentableList xs) => Read (Tuple xs) Source # | |
| All Show xs => Show (Tuple xs) Source # | |
| All Show xs => Show (Tuple xs) Source # | |
| All Semigroup xs => Semigroup (Tuple xs) Source # | |
| All Semigroup xs => Semigroup (Tuple xs) Source # | |
| (RepresentableList xs, All Semigroup xs, All Monoid xs) => Monoid (Tuple xs) Source # | |
| (RepresentableList xs, All Semigroup xs, All Monoid xs) => Monoid (Tuple xs) Source # | |
| BoundedDims ds => Bounded (Idxs ds) Source # | |
| Dimensions ds => Enum (Idxs ds) Source # |
|
| Eq (Dims ds) Source # | |
| Eq (Dims ds) Source # | |
| Eq (Idxs xs) Source # | |
| Ord (Dims ds) Source # | |
Defined in Numeric.Dimensions.Dim | |
| Ord (Dims ds) Source # | |
Defined in Numeric.Dimensions.Dim | |
| 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 sort == sortOn fromEnum |
Defined in Numeric.Dimensions.Idx | |
| BoundedDims xs => Read (Dims xs) Source # | |
| BoundedDims xs => Read (Idxs xs) Source # | |
| Show (Dims xs) Source # | |
| Show (Idxs xs) Source # | |
| (Typeable k, Typeable f, Typeable xs, All Data (Map f xs)) => Data (TypedList f xs) Source # | Term-level structure of a |
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 # | |
| type Rep (TypedList f xs) Source # | |
Defined in Numeric.TypedList | |
Checking the index bounds
data OutOfDimBounds Source #
Typically, this exception can occur in the following cases:
- Converting from integral values to
Idx dwhend ~ N nord :: Nat. - Using
EnumandNumwhend ~ N nord :: Nat. - Converting from
Idx (XN m :: XNat)toIdx (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
| |
Instances
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.