Safe Haskell | None |
---|---|
Language | Haskell98 |
- type family Head (lst :: [a]) :: a where ...
- type family Tail (lst :: [a]) :: [a] where ...
- type family Index (lst :: [a]) (idx :: Nat) :: a where ...
- type family Insert (lst :: [a]) (idx :: Nat) (el :: a) :: [a] where ...
- type family Remove (lst :: [a]) (idx :: Nat) :: [a] where ...
- type family Append (lst :: [a]) (el :: a) :: [a] where ...
- type family Length (lst :: [a]) :: Nat where ...
- type family Drop (lst :: [a]) (i :: Nat) :: [a] where ...
- type family Take (lst :: [a]) (i :: Nat) :: [a] where ...
- type family StripPrefix (lst :: [a]) (pre :: [a]) :: [a] where ...
- type family Last (lst :: [a]) :: a where ...
- type family DropLast (lst :: [a]) :: [a] where ...
- type family Reverse (lst :: [a]) :: [a] where ...
- type family Map (lst :: [a]) (f :: a -> b) :: [b] where ...
- type family Concat (xs :: [a]) (ys :: [a]) :: [a] where ...
- type family Replicate (n :: Nat) (x :: a) :: [a] where ...
- data List e tp where
- list :: [ExpQ] -> ExpQ
- nil :: List e '[]
- list1 :: e t1 -> List e '[t1]
- list2 :: e t1 -> e t2 -> List e '[t1, t2]
- list3 :: e t1 -> e t2 -> e t3 -> List e '[t1, t2, t3]
- reifyList :: (forall r'. a -> (forall tp. e tp -> r') -> r') -> [a] -> (forall tp. List e tp -> r) -> r
- access :: Monad m => List e lst -> Natural idx -> (e (Index lst idx) -> m (a, e tp)) -> m (a, List e (Insert lst idx tp))
- access' :: Monad m => List e lst -> Natural idx -> (e (Index lst idx) -> m (a, e (Index lst idx))) -> m (a, List e lst)
- head :: List e lst -> e (Head lst)
- tail :: List e lst -> List e (Tail lst)
- index :: List e lst -> Natural idx -> e (Index lst idx)
- indexDyn :: Integral i => List e tps -> i -> (forall tp. e tp -> a) -> a
- insert :: List e lst -> Natural idx -> e tp -> List e (Insert lst idx tp)
- remove :: List e lst -> Natural idx -> List e (Remove lst idx)
- mapM :: Monad m => (forall x. e x -> m (e' x)) -> List e lst -> m (List e' lst)
- mapIndexM :: Monad m => (forall n. Natural n -> e (Index lst n) -> m (e' (Index lst n))) -> List e lst -> m (List e' lst)
- traverse :: Applicative f => (forall x. e x -> f (e' x)) -> List e lst -> f (List e' lst)
- cons :: e x -> List e xs -> List e (x ': xs)
- append :: List e xs -> e x -> List e (Append xs x)
- length :: List e lst -> Natural (Length lst)
- drop :: List e lst -> Natural i -> List e (Drop lst i)
- take :: List e lst -> Natural i -> List e (Take lst i)
- last :: List e lst -> e (Last lst)
- dropLast :: List e lst -> List e (DropLast lst)
- stripPrefix :: GEq e => List e lst -> List e pre -> Maybe (List e (StripPrefix lst pre))
- reverse :: List e lst -> List e (Reverse lst)
- map :: List e lst -> (forall x. e x -> e (f x)) -> List e (Map lst f)
- unmap :: List p lst -> List e (Map lst f) -> (forall x. e (f x) -> e x) -> List e lst
- unmapM :: Monad m => List p lst -> List e (Map lst f) -> (forall x. e (f x) -> m (e x)) -> m (List e lst)
- mapM' :: Monad m => List e lst -> (forall x. e x -> m (e (f x))) -> m (List e (Map lst f))
- concat :: List e xs -> List e ys -> List e (Concat xs ys)
- replicate :: Natural n -> e x -> List e (Replicate n x)
- toList :: Monad m => (forall x. e x -> m a) -> List e lst -> m [a]
- toListIndex :: Monad m => (forall n. Natural n -> e (Index lst n) -> m a) -> List e lst -> m [a]
- foldM :: Monad m => (forall x. s -> e x -> m s) -> s -> List e lst -> m s
- zipWithM :: Monad m => (forall x. e1 x -> e2 x -> m (e3 x)) -> List e1 lst -> List e2 lst -> m (List e3 lst)
- zipToListM :: Monad m => (forall x. e1 x -> e2 x -> m a) -> List e1 lst -> List e2 lst -> m [a]
- mapAccumM :: Monad m => (forall x. s -> e x -> m (s, e' x)) -> s -> List e xs -> m (s, List e' xs)
Documentation
type family StripPrefix (lst :: [a]) (pre :: [a]) :: [a] where ... Source #
StripPrefix xs '[] = xs | |
StripPrefix (x ': xs) (x ': ys) = StripPrefix xs ys |
Strongly typed heterogenous lists.
A List e '[tp1,tp2,tp3] contains 3 elements of types e tp1, e tp2 and e tp3 respectively.
As an example, the following list contains two types:
>>>
int ::: bool ::: Nil :: List Repr '[IntType,BoolType]
[IntRepr,BoolRepr]
HasMonad (m (List Type e tp)) Source # | |
GCompare a e => GCompare [a] (List a e) Source # | |
GEq a e => GEq [a] (List a e) Source # | |
GShow a e => GShow [a] (List a e) Source # | |
GEq a e => Eq (List a e lst) Source # | |
GCompare a e => Ord (List a e lst) Source # | |
GShow a e => Show (List a e lst) Source # | |
HasMonad (List Type e tp) Source # | |
type MonadResult (m (List Type e tp)) Source # | |
type MatchMonad (m (List Type e tp)) m' Source # | |
type MonadResult (List Type e tp) Source # | |
type MatchMonad (List Type e tp) m Source # | |
reifyList :: (forall r'. a -> (forall tp. e tp -> r') -> r') -> [a] -> (forall tp. List e tp -> r) -> r Source #
Get a static representation of a dynamic list.
For example, to convert a list of strings into a list of types:
>>>
reifyList (\name f -> case name of { "int" -> f int ; "bool" -> f bool }) ["bool","int"] show
"[BoolRepr,IntRepr]"
access :: Monad m => List e lst -> Natural idx -> (e (Index lst idx) -> m (a, e tp)) -> m (a, List e (Insert lst idx tp)) Source #
access' :: Monad m => List e lst -> Natural idx -> (e (Index lst idx) -> m (a, e (Index lst idx))) -> m (a, List e lst) Source #
mapIndexM :: Monad m => (forall n. Natural n -> e (Index lst n) -> m (e' (Index lst n))) -> List e lst -> m (List e' lst) Source #
stripPrefix :: GEq e => List e lst -> List e pre -> Maybe (List e (StripPrefix lst pre)) Source #
unmapM :: Monad m => List p lst -> List e (Map lst f) -> (forall x. e (f x) -> m (e x)) -> m (List e lst) Source #
toListIndex :: Monad m => (forall n. Natural n -> e (Index lst n) -> m a) -> List e lst -> m [a] Source #
zipWithM :: Monad m => (forall x. e1 x -> e2 x -> m (e3 x)) -> List e1 lst -> List e2 lst -> m (List e3 lst) Source #