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

Copyright(c) Artem Chirkin
LicenseBSD3
Safe HaskellNone
LanguageHaskell2010

Data.Type.List

Contents

Description

Provides type-level operations on lists.

Synopsis

Basic operations

type (++) (as :: [k]) (bs :: [k]) = Concat as bs infixr 5 Source #

Infix-style synonym for concatenation

type (+:) (ns :: [k]) (n :: k) = Snoc ns n infixl 6 Source #

Synonym for a type-level Snoc.

type (:+) (a :: k) (as :: [k]) = a ': as infixr 5 Source #

Synonym for a type-level Cons.

type Empty = '[] Source #

Empty list, same as '[].

type Cons (a :: k) (as :: [k]) = a ': as Source #

Appending a list, represents an Op counterpart of (':).

type family Snoc (xs :: [k]) (x :: k) = (ys :: [k]) where ... Source #

Appending a list on the other side.

Equations

Snoc (x ': xs) y = x ': Snoc xs y 
Snoc '[] y = '[y] 

type family Head (xs :: [k]) :: k where ... Source #

Extract the first element of a list, which must be non-empty.

Equations

Head ('[] :: [k]) = TypeError (ListError k "Head: empty type-level list.") 
Head (x ': _) = x 

type family Tail (xs :: [k]) :: [k] where ... Source #

Extract the elements after the head of a list, which must be non-empty.

Equations

Tail ('[] :: [k]) = TypeError (ListError k "Tail: empty type-level list.") 
Tail (_ ': xs) = xs 

type family Last (xs :: [k]) :: k where ... Source #

Extract the last element of a list, which must be non-empty.

Equations

Last ('[] :: [k]) = TypeError (ListError k "Last: empty type-level list.") 
Last '[x] = x 
Last (_ ': xs) = Last xs 

type family Init (xs :: [k]) :: [k] where ... Source #

Extract all but last elements of a list, which must be non-empty.

Equations

Init ('[] :: [k]) = TypeError (ListError k "Init: empty type-level list.") 
Init '[x] = '[] 
Init (x ': xs) = x ': Init xs 

type family Concat (as :: [k]) (bs :: [k]) :: [k] where ... Source #

Append two lists.

Equations

Concat '[] bs = bs 
Concat as '[] = as 
Concat (a ': as) bs = a ': Concat as bs 

type family StripPrefix (as :: [k]) (asbs :: [k]) :: [k] where ... Source #

Remove prefix as from a list asbs if as is a prefix; fail otherwise.

Equations

StripPrefix as as = '[] 
StripPrefix '[] asbs = asbs 
StripPrefix (a ': as) (a ': asbs) = StripPrefix as asbs 
StripPrefix (a ': as) (b ': asbs) = TypeError ((Text "StripPrefix: the first argument is not a prefix of the second." :$$: (Text "Failed prefix: " :<>: ShowType (a ': as))) :$$: (Text "Second argument: " :<>: ShowType (b ': asbs))) 
StripPrefix (a ': as) '[] = TypeError ((Text "StripPrefix: the first argument is longer than the second." :$$: (Text "Failed prefix: " :<>: ShowType (a ': as))) :$$: Text "The reduced second argument is empty.") 

type family StripSuffix (bs :: [k]) (asbs :: [k]) :: [k] where ... Source #

Remove suffix bs from a list asbs if bs is a suffix; fail otherwise.

Equations

StripSuffix bs bs = '[] 
StripSuffix '[] asbs = asbs 
StripSuffix (a ': bs) (b ': bs) = TypeError (Text "StripSuffix: the first argument is not a suffix of the second." :$$: (Text "Failed match: " :<>: ShowType ((a ': bs) ~ (b ': bs)))) 
StripSuffix (b ': bs) '[] = TypeError ((Text "StripSuffix: the first argument is longer than the second." :$$: (Text "Failed suffix: " :<>: ShowType (b ': bs))) :$$: Text "The reduced second argument is empty.") 
StripSuffix bs (a ': asbs) = a ': StripSuffix bs asbs 

type family Reverse (xs :: [k]) :: [k] where ... Source #

Returns the elements of a list in reverse order.

Equations

Reverse '[] = '[] 
Reverse (x ': xs) = Snoc (Reverse xs) x 

type family Take (n :: Nat) (xs :: [k]) :: [k] where ... Source #

Take n xs returns the prefix of a list of length max n (length xs).

Equations

Take 0 _ = '[] 
Take n (x ': xs) = x ': Take (n - 1) xs 
Take _ '[] = '[] 

type family Drop (n :: Nat) (xs :: [k]) :: [k] where ... Source #

Drop n xs drops up to n elements of xs.

Equations

Drop 0 xs = xs 
Drop n (_ ': xs) = Drop (n - 1) xs 
Drop _ '[] = '[] 

type family Length (xs :: [k]) :: Nat where ... Source #

Number of elements in a list.

Equations

Length '[] = 0 
Length (x ': xs) = Length xs + 1 

Operations on elements

type family All (f :: k -> Constraint) (xs :: [k]) :: Constraint where ... Source #

All elements of a type list must satisfy the same constraint.

Equations

All _ '[] = () 
All f (x ': xs) = (f x, All f xs) 

type family Map (f :: a -> b) (xs :: [a]) :: [b] where ... Source #

Map a functor over the elements of a type list.

Equations

Map f '[] = '[] 
Map f (x ': xs) = f x ': Map f xs 

type family Elem (x :: k) (xs :: [k]) :: Constraint where ... Source #

Check if an item is a member of a list.

Equations

Elem x (x ': xs) = () 
Elem x (_ ': xs) = Elem x xs 

Concatenation and its evidence

type ConcatList (as :: [k]) (bs :: [k]) (asbs :: [k]) = (asbs ~ Concat as bs, as ~ StripSuffix bs asbs, bs ~ StripPrefix as asbs) Source #

Represent a triple of lists forming a relation (as ++ bs) ~ asbs

evStripSuffix :: forall (k :: Type) (as :: [k]) (bs :: [k]) (asbs :: [k]). (as ~ StripSuffix bs asbs) :- ConcatList as bs asbs Source #

Derive ConcatList given StripSuffix

evStripPrefix :: forall (k :: Type) (as :: [k]) (bs :: [k]) (asbs :: [k]). (bs ~ StripPrefix as asbs) :- ConcatList as bs asbs Source #

Derive ConcatList given StripPrefix

evConcat :: forall (k :: Type) (as :: [k]) (bs :: [k]) (asbs :: [k]). (asbs ~ Concat as bs) :- ConcatList as bs asbs Source #

Derive ConcatList given Concat

Data.Typeable

inferTypeableCons :: forall (k :: Type) (ys :: [k]) (x :: k) (xs :: [k]). (Typeable ys, ys ~ (x ': xs)) => Dict (Typeable x, Typeable xs) Source #

Given a Typeable list, infer this constraint for its parts.