Safe Haskell | None |
---|---|
Language | Haskell2010 |
Heterogeneous list
Synopsis
- data family HList (l :: [Type])
- hHead :: HList (e ': l) -> e
- hTail :: HList (e ': l) -> HList l
- hLength :: forall xs. KnownNat (Length xs) => HList xs -> Word
- hAppend :: HAppendList l1 l2 => HList l1 -> HList l2 -> HList (Concat l1 l2)
- class HFoldr' f v (l :: [Type]) r where
- class HFoldl' f (z :: Type) xs (r :: Type) where
- class HTuple v where
- class Apply f a b where
- apply :: f -> a -> b
- class HZipList x y l | x y -> l, l -> x y
- hZipList :: HZipList x y l => HList x -> HList y -> HList l
- class HFoldr f v (l :: [Type]) r
- hFoldr :: HFoldr f v l r => f -> v -> HList l -> r
- class HFoldl f (z :: Type) xs (r :: Type)
- hFoldl :: HFoldl f z xs r => f -> z -> HList xs -> r
- class HReverse xs sx | xs -> sx, sx -> xs where
Documentation
data family HList (l :: [Type]) infixr 2 Source #
Heterogeneous list
Instances
(Eq x, Eq (HList xs)) => Eq (HList (x ': xs)) Source # | |
Eq (HList ('[] :: [Type])) Source # | |
(Ord x, Ord (HList xs)) => Ord (HList (x ': xs)) Source # | |
Defined in Haskus.Utils.HList compare :: HList (x ': xs) -> HList (x ': xs) -> Ordering # (<) :: HList (x ': xs) -> HList (x ': xs) -> Bool # (<=) :: HList (x ': xs) -> HList (x ': xs) -> Bool # (>) :: HList (x ': xs) -> HList (x ': xs) -> Bool # (>=) :: HList (x ': xs) -> HList (x ': xs) -> Bool # max :: HList (x ': xs) -> HList (x ': xs) -> HList (x ': xs) # min :: HList (x ': xs) -> HList (x ': xs) -> HList (x ': xs) # | |
Ord (HList ('[] :: [Type])) Source # | |
Defined in Haskus.Utils.HList | |
(Show e, Show (HList l)) => Show (HList (e ': l)) Source # | |
Show (HList ('[] :: [Type])) Source # | |
data HList ('[] :: [Type]) Source # | |
Defined in Haskus.Utils.HList | |
data HList (x ': xs) Source # | |
Defined in Haskus.Utils.HList |
class HFoldr' f v (l :: [Type]) r where Source #
Like HFoldr but only use types, not values!
It allows us to foldr over a list of types, without any associated hlist of values.
class HFoldl' f (z :: Type) xs (r :: Type) where Source #
Like HFoldl but only use types, not values!
It allows us to foldl over a list of types, without any associated hlist of values.
Instances
Convert between hlists and tuples
hToTuple :: HList v -> Tuple v Source #
Convert an heterogeneous list into a tuple
hFromTuple :: Tuple v -> HList v Source #
Convert a tuple into an heterogeneous list
Instances
HTuple ('[] :: [Type]) Source # | |
HTuple '[a, b, c, d, e, f, g, h, i, j, k, l] Source # | |
HTuple '[a, b, c, d, e, f, g, h, i, j, k] Source # | |
HTuple '[a, b, c, d, e, f, g, h, i, j] Source # | |
HTuple '[a, b, c, d, e, f, g, h, i] Source # | |
HTuple '[a, b, c, d, e, f, g, h] Source # | |
HTuple '[a, b, c, d, e, f, g] Source # | |
HTuple '[a, b, c, d, e, f] Source # | |
HTuple '[a, b, c, d, e] Source # | |
HTuple '[a, b, c, d] Source # | |
HTuple '[a, b, c] Source # | |
HTuple '[a, b] Source # | |
HTuple '[a] Source # | |
class Apply f a b where Source #
Apply the function identified by the data type f from type a to type b.
class HZipList x y l | x y -> l, l -> x y Source #
hZipList, hUnzipList