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

Description

Provide a type-indexed heterogeneous list type TypedList. Behind the facade, TypedList is just a plain list of haskell pointers. It is used to represent dimension lists, indices, and just flexible tuples.

Most of type-level functionality is implemented using GADT-like pattern synonyms. Import this module qualified to use list-like functionality.

Synopsis

Documentation

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

Type-indexed list

Bundled Patterns

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 EvList :: forall (c :: k -> Constraint) (xs :: [k]). (All c xs, RepresentableList xs) => EvidenceList c xs

Pattern matching against this allows manipulating lists of constraints. Useful when creating functions that change the shape of dimensions.

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 #

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 #

cons :: f x -> TypedList f xs -> TypedList f (x :+ xs) Source #

snoc :: TypedList f xs -> f x -> TypedList f (xs +: x) Source #

take :: Dim n -> TypedList f xs -> TypedList f (Take n xs) Source #

drop :: Dim n -> TypedList f xs -> TypedList f (Drop n xs) Source #

head :: TypedList f xs -> f (Head xs) Source #

tail :: TypedList f xs -> TypedList f (Tail xs) Source #

last :: TypedList f xs -> f (Last xs) Source #

init :: TypedList f xs -> TypedList f (Init xs) Source #

splitAt :: Dim n -> TypedList f xs -> (TypedList f (Take n xs), TypedList f (Drop n xs)) Source #

concat :: TypedList f xs -> TypedList f ys -> TypedList f (xs ++ ys) Source #

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

map :: (forall a. f a -> g a) -> TypedList f xs -> TypedList g xs Source #

Map a function over contents of a typed list