symantic-6.3.2.20180208: Library for Typed Tagless-Final Higher-Order Composable DSL

Safe HaskellNone
LanguageHaskell2010

Language.Symantic.Typing.List

Contents

Description

List utilities at the type-level.

Synopsis

Type Index

type family Index xs x where ... Source #

Return the position of a type within a list of them. This is useful to work around OverlappingInstances.

Equations

Index (x ': xs) x = Zero 
Index (not_x ': xs) x = Succ (Index xs x) 

Type family (++)

type family xs ++ ys where ... infixr 5 Source #

Equations

'[] ++ ys = ys 
(x ': xs) ++ ys = x ': (xs ++ ys) 

Type family Concat

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

Equations

Concat '[] = '[] 
Concat (x ': xs) = x ++ Concat xs 

Type family Concat_Constraints

type family Concat_Constraints (cs :: [Constraint]) :: Constraint where ... Source #

Equations

Concat_Constraints '[] = () 
Concat_Constraints (c ': cs) = (c, Concat_Constraints cs) 

Type family DeleteAll

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

Equations

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

Type family Head

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

Equations

Head (x ': _xs) = x 

Type family Tail

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

Equations

Tail (_x ': xs) = xs 

Type family Nub

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

Equations

Nub '[] = '[] 
Nub (x ': xs) = x ': Nub (DeleteAll x xs) 

Type Len

data Len (xs :: [k]) where Source #

Constructors

LenZ :: Len '[] 
LenS :: Len xs -> Len (x ': xs) 
Instances
Show (Len vs) Source # 
Instance details

Defined in Language.Symantic.Typing.List

Methods

showsPrec :: Int -> Len vs -> ShowS #

show :: Len vs -> String #

showList :: [Len vs] -> ShowS #

addLen :: Len a -> Len b -> Len (a ++ b) Source #

shiftLen :: forall t b a. Len a -> Len (a ++ b) -> Len (a ++ (t ': b)) Source #

intLen :: Len xs -> Int Source #

Class LenInj

class LenInj (vs :: [k]) where Source #

Minimal complete definition

lenInj

Methods

lenInj :: Len vs Source #

Instances
LenInj ([] :: [k]) Source # 
Instance details

Defined in Language.Symantic.Typing.List

Methods

lenInj :: Len [] Source #

LenInj as => LenInj (a ': as :: [k]) Source # 
Instance details

Defined in Language.Symantic.Typing.List

Methods

lenInj :: Len (a ': as) Source #