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.Dims

Contents

Description

Provides a data type `Dims ds` to keep dimension sizes for multiple-dimensional data. Lower indices go first, i.e. assumed enumeration is i = i1 + i2*n1 + i3*n1*n2 + ... + ik*n1*n2*...*n(k-1).

Synopsis

Documentation

type Dims (xs :: [k]) = TypedList Dim xs Source #

Type-level dimensionality O(1).

data SomeDims Source #

Same as SomeNat, but for Dimensions: Hide all information about Dimensions inside

Constructors

SomeDims (Dims ns) 

class Dimensions (ds :: [k]) where Source #

Minimal complete definition

dims

Methods

dims :: Dims ds Source #

Get dimensionality of a space at runtime, represented as a list of Dim.

Note, this function is supposed to be used with TypeApplications, and the Dimensions class has varying kind of the parameter; thus, the function has two type paremeters (kind and type of ds). For example, you can type:

>>> :set -XTypeApplications
>>> :set -XDataKinds
>>> :t dims @_ @'[N 17, N 12]
dims @_ @'[N 17, N 12] :: Dims '[N 17, N 12]
>>> :t dims @XNat @'[]
dims @XNat @'[] :: Dims '[]
>>> :t dims @_ @(Tail '[3,2,5,7])
dims @_ @(Tail '[3,2,5,7]) :: Dims '[2, 5, 7]

Instances

Dimensions k ([] k) Source # 

Methods

dims :: Dims [k] ds Source #

(KnownDim k d, Dimensions k ds) => Dimensions k ((:) k d ds) Source # 

Methods

dims :: Dims ((k ': d) ds) ds Source #

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

Type-indexed list

Bundled Patterns

pattern Dims :: forall ds. Dimensions ds => Dims ds

O(1) Pattern-matching against this constructor brings a Dimensions instance into the scope. Thus, you can do arbitrary operations on your dims and use this pattern at any time to reconstruct the class instance at runtime.

pattern XDims :: forall (xns :: [XNat]). KnownXNatTypes xns => forall (ns :: [Nat]). (FixedDims xns ns, Dimensions ns) => Dims ns -> Dims xns

Pattern-matching against this constructor reveals Nat-kinded list of dims, pretending the dimensionality is known at compile time within the scope of the pattern match. This is the main recommended way to get Dims at runtime; for example, reading a list of dimensions from a file.

In order to use this pattern, one must know XNat type constructors in each dimension at compile time.

pattern AsXDims :: forall (ns :: [Nat]). (KnownXNatTypes (AsXDims ns), RepresentableList (AsXDims ns)) => Dims (AsXDims ns) -> Dims ns

An easy way to convert Nat-indexed dims into XNat-indexed dims.

pattern KnownDims :: forall ds. (All KnownDim ds, Dimensions ds) => Dims ds

O(Length ds) Dimensions and KnownDim for each individual dimension.

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

Zero-length type list

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

Constructing a type-indexed list

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

Zero-length type list; synonym to U.

pattern TypeList :: forall (xs :: [k]). RepresentableList xs => TypeList xs

Pattern matching against this causes RepresentableList instance come into scope. Also it allows constructing a term-level list out of a constraint.

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

Constructing a type-indexed list in the canonical way

pattern Snoc :: forall (f :: k -> Type) (xs :: [k]). forall (sy :: [k]) (y :: k). xs ~ (sy +: y) => TypedList f sy -> f y -> TypedList f xs

Constructing a type-indexed list from the other end

pattern Reverse :: forall (f :: k -> Type) (xs :: [k]). forall (sx :: [k]). (xs ~ Reverse sx, sx ~ Reverse xs) => TypedList f sx -> TypedList f xs

Reverse a typed list

Instances

(RepresentableList * xs, All * Bounded xs) => Bounded (Tuple xs) # 

Methods

minBound :: Tuple xs #

maxBound :: Tuple xs #

(RepresentableList * xs, All * Bounded xs) => Bounded (Tuple xs) # 

Methods

minBound :: Tuple xs #

maxBound :: Tuple xs #

All * Eq xs => Eq (Tuple xs) # 

Methods

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

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

All * Eq xs => Eq (Tuple xs) # 

Methods

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

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

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

Ord instance of the Tuple implements inverse lexicorgaphic ordering. That is, the last element in the tuple is the most significant one.

Note, this will never work on infinite-dimensional tuples!

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) #

Ord instance of the Tuple implements inverse lexicorgaphic ordering. That is, the last element in the tuple is the most significant one.

Note, this will never work on infinite-dimensional tuples!

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 #

(RepresentableList * xs, All * Read xs) => Read (Tuple xs) # 
(RepresentableList * xs, All * Read xs) => Read (Tuple xs) # 
All * Show xs => Show (Tuple xs) # 

Methods

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

show :: Tuple xs -> String #

showList :: [Tuple xs] -> ShowS #

All * Show xs => Show (Tuple xs) # 

Methods

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

show :: Tuple xs -> String #

showList :: [Tuple xs] -> ShowS #

All * Semigroup xs => Semigroup (Tuple xs) # 

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) # 

Methods

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

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

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

(Semigroup (Tuple xs), RepresentableList Type xs, All * Monoid xs) => Monoid (Tuple xs) # 

Methods

mempty :: Tuple xs #

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

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

(Semigroup (Tuple xs), RepresentableList Type xs, All * Monoid xs) => Monoid (Tuple xs) # 

Methods

mempty :: Tuple xs #

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

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

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

Methods

minBound :: Idxs k ds #

maxBound :: Idxs k ds #

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

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] #

Eq (Idxs k xs) # 

Methods

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

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

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

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]) #

Ord (Idxs k xs) #

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 #

Show (Idxs k xs) # 

Methods

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

show :: Idxs k xs -> String #

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

listDims :: Dims xs -> [Word] Source #

Convert `Dims xs` to a plain haskell list of dimension sizes O(1).

someDimsVal :: [Word] -> SomeDims Source #

Convert a plain haskell list of dimension sizes into an unknown type-level dimensionality O(1).

totalDim :: Dims xs -> Word Source #

Product of all dimension sizes O(Length xs).

totalDim' :: forall xs. Dimensions xs => Word Source #

Product of all dimension sizes O(Length xs).

sameDims :: Dims (as :: [Nat]) -> Dims (bs :: [Nat]) -> Maybe (Evidence (as ~ bs)) Source #

We either get evidence that this function was instantiated with the same type-level Dimensions, or Nothing O(Length xs).

Note, this function works on Nat-indexed dimensions only, because Dims '[XN x] does not have runtime evidence to infer x and `KnownDim x` does not imply `KnownDim (XN x)`.

sameDims' :: forall (as :: [Nat]) (bs :: [Nat]) p q. (Dimensions as, Dimensions bs) => p as -> q bs -> Maybe (Evidence (as ~ bs)) Source #

We either get evidence that this function was instantiated with the same type-level Dimensions, or Nothing O(Length xs).

compareDims :: Dims as -> Dims bs -> Ordering Source #

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

Literally,

compareDims a b = compare (reverse $ listDims a) (reverse $ listDims b)

compareDims' :: forall as bs p q. (Dimensions as, Dimensions bs) => p as -> q bs -> Ordering Source #

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

Literally,

compareDims a b = compare (reverse $ listDims a) (reverse $ listDims b)

This is the same compare rule, as for Idxs.

inSpaceOf :: a ds -> b ds -> a ds Source #

Similar to const or asProxyTypeOf; to be used on such implicit functions as dim, dimMax, etc.

asSpaceOf :: a ds -> (b ds -> c) -> b ds -> c Source #

Similar to asProxyTypeOf, Give a hint to type checker to fix the type of a function argument.

xDims :: FixedDims xns ns => Dims ns -> Dims xns Source #

Get XNat-indexed dims given their fixed counterpart.

xDims' :: forall xns ns. (FixedDims xns ns, Dimensions ns) => Dims xns Source #

Get XNat-indexed dims given their fixed counterpart.

Type-level programming

type family AsXDims (ns :: [Nat]) = (xns :: [XNat]) | xns -> ns where ... Source #

Map Dims onto XDims (injective)

Equations

AsXDims '[] = '[] 
AsXDims (n ': ns) = N n ': AsXDims ns 

type family AsDims (xns :: [XNat]) = (ns :: [Nat]) | ns -> xns where ... Source #

Map XDims onto Dims (injective)

Equations

AsDims '[] = '[] 
AsDims (N x ': xs) = x ': AsDims xs 

type family FixedDims (xns :: [XNat]) (ns :: [Nat]) :: Constraint where ... Source #

Constrain Nat dimensions hidden behind XNats.

Equations

FixedDims '[] ns = ns ~ '[] 
FixedDims (xn ': xns) ns = (ns ~ (Head ns ': Tail ns), FixedDim xn (Head ns), FixedDims xns (Tail ns)) 

type KnownXNatTypes xns = All KnownXNatType xns Source #

Know the structure of each dimension

type family (n :: Nat) :< (ns :: [Nat]) :: [Nat] where ... infixr 6 Source #

Synonym for (:+) that treats Nat values 0 and 1 in a special way: it preserves the property that all dimensions are greater than 1.

Equations

0 :< _ = '[] 
1 :< ns = ns 
n :< ns = n :+ ns 

type family (ns :: [Nat]) >: (n :: Nat) :: [Nat] where ... infixl 6 Source #

Synonym for (+:) that treats Nat values 0 and 1 in a special way: it preserves the property that all dimensions are greater than 1.

Equations

_ >: 0 = '[] 
ns >: 1 = ns 
ns >: n = ns +: n 

Re-export type list

class RepresentableList (xs :: [k]) where Source #

Representable type lists. Allows getting type information about list structure at runtime.

Minimal complete definition

tList

Methods

tList :: TypeList xs Source #

Get type-level constructed list

Instances

RepresentableList k ([] k) Source # 

Methods

tList :: TypeList [k] xs Source #

RepresentableList k xs => RepresentableList k ((:) k x xs) Source # 

Methods

tList :: TypeList ((k ': x) xs) xs Source #

type TypeList (xs :: [k]) = TypedList Proxy xs Source #

A list of type proxies

types :: TypedList f xs -> TypeList xs Source #

Get a constructible TypeList from any other TypedList; Pattern matching agains the result brings RepresentableList constraint into the scope:

case types ts of TypeList -> ...

order :: TypedList f xs -> Dim (Length xs) Source #

order' :: forall xs. RepresentableList xs => Dim (Length xs) Source #

Re-export single dimension type and functions

Orphan instances

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

Methods

minBound :: Dims k ds #

maxBound :: Dims k ds #

Eq (Dims Nat ds) Source # 

Methods

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

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

Eq (Dims XNat ds) Source # 

Methods

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

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

Ord (Dims Nat ds) Source # 

Methods

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

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

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

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

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

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

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

Ord (Dims XNat ds) Source # 

Methods

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

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

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

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

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

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

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

Show (Dims k xs) Source # 

Methods

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

show :: Dims k xs -> String #

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