haskus-utils-data-1.4: Haskus data utility modules
Safe HaskellNone
LanguageHaskell2010

Haskus.Utils.HList

Description

Heterogeneous list

Synopsis

Documentation

data family HList (l :: [Type]) infixr 2 Source #

Heterogeneous list

Instances

Instances details
(Eq x, Eq (HList xs)) => Eq (HList (x ': xs)) Source # 
Instance details

Defined in Haskus.Utils.HList

Methods

(==) :: HList (x ': xs) -> HList (x ': xs) -> Bool #

(/=) :: HList (x ': xs) -> HList (x ': xs) -> Bool #

Eq (HList ('[] :: [Type])) Source # 
Instance details

Defined in Haskus.Utils.HList

Methods

(==) :: HList '[] -> HList '[] -> Bool #

(/=) :: HList '[] -> HList '[] -> Bool #

(Ord x, Ord (HList xs)) => Ord (HList (x ': xs)) Source # 
Instance details

Defined in Haskus.Utils.HList

Methods

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 # 
Instance details

Defined in Haskus.Utils.HList

Methods

compare :: HList '[] -> HList '[] -> Ordering #

(<) :: HList '[] -> HList '[] -> Bool #

(<=) :: HList '[] -> HList '[] -> Bool #

(>) :: HList '[] -> HList '[] -> Bool #

(>=) :: HList '[] -> HList '[] -> Bool #

max :: HList '[] -> HList '[] -> HList '[] #

min :: HList '[] -> HList '[] -> HList '[] #

(Show e, Show (HList l)) => Show (HList (e ': l)) Source # 
Instance details

Defined in Haskus.Utils.HList

Methods

showsPrec :: Int -> HList (e ': l) -> ShowS #

show :: HList (e ': l) -> String #

showList :: [HList (e ': l)] -> ShowS #

Show (HList ('[] :: [Type])) Source # 
Instance details

Defined in Haskus.Utils.HList

Methods

showsPrec :: Int -> HList '[] -> ShowS #

show :: HList '[] -> String #

showList :: [HList '[]] -> ShowS #

data HList ('[] :: [Type]) Source # 
Instance details

Defined in Haskus.Utils.HList

data HList ('[] :: [Type]) = HNil
data HList (x ': xs) Source # 
Instance details

Defined in Haskus.Utils.HList

data HList (x ': xs) = x `HCons` (HList xs)

hHead :: HList (e ': l) -> e Source #

Head

hTail :: HList (e ': l) -> HList l Source #

Tail

hLength :: forall xs. KnownNat (Length xs) => HList xs -> Word Source #

Length

hAppend :: HAppendList l1 l2 => HList l1 -> HList l2 -> HList (Concat l1 l2) Source #

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.

Methods

hFoldr' :: f -> v -> HList l -> r Source #

Instances

Instances details
v ~ v' => HFoldr' f v ('[] :: [Type]) v' Source # 
Instance details

Defined in Haskus.Utils.HList

Methods

hFoldr' :: f -> v -> HList '[] -> v' Source #

(Apply f (e, r) r', HFoldr' f v l r) => HFoldr' f v (e ': l) r' Source # 
Instance details

Defined in Haskus.Utils.HList

Methods

hFoldr' :: f -> v -> HList (e ': l) -> r' Source #

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.

Methods

hFoldl' :: f -> z -> HList xs -> r Source #

Instances

Instances details
z ~ z' => HFoldl' f z ('[] :: [Type]) z' Source # 
Instance details

Defined in Haskus.Utils.HList

Methods

hFoldl' :: f -> z -> HList '[] -> z' Source #

(zx ~ (z, x), Apply f zx z', HFoldl' f z' xs r) => HFoldl' f z (x ': xs) r Source # 
Instance details

Defined in Haskus.Utils.HList

Methods

hFoldl' :: f -> z -> HList (x ': xs) -> r Source #

class HTuple v where Source #

Convert between hlists and tuples

Methods

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

Instances details
HTuple ('[] :: [Type]) Source # 
Instance details

Defined in Haskus.Utils.HList

Methods

hToTuple :: HList '[] -> Tuple '[] Source #

hFromTuple :: Tuple '[] -> HList '[] Source #

HTuple '[a, b, c, d, e, f, g, h, i, j, k, l] Source # 
Instance details

Defined in Haskus.Utils.HList

Methods

hToTuple :: HList '[a, b, c, d, e, f, g, h, i, j, k, l] -> Tuple '[a, b, c, d, e, f, g, h, i, j, k, l] Source #

hFromTuple :: Tuple '[a, b, c, d, e, f, g, h, i, j, k, l] -> HList '[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 # 
Instance details

Defined in Haskus.Utils.HList

Methods

hToTuple :: HList '[a, b, c, d, e, f, g, h, i, j, k] -> Tuple '[a, b, c, d, e, f, g, h, i, j, k] Source #

hFromTuple :: Tuple '[a, b, c, d, e, f, g, h, i, j, k] -> HList '[a, b, c, d, e, f, g, h, i, j, k] Source #

HTuple '[a, b, c, d, e, f, g, h, i, j] Source # 
Instance details

Defined in Haskus.Utils.HList

Methods

hToTuple :: HList '[a, b, c, d, e, f, g, h, i, j] -> Tuple '[a, b, c, d, e, f, g, h, i, j] Source #

hFromTuple :: Tuple '[a, b, c, d, e, f, g, h, i, j] -> HList '[a, b, c, d, e, f, g, h, i, j] Source #

HTuple '[a, b, c, d, e, f, g, h, i] Source # 
Instance details

Defined in Haskus.Utils.HList

Methods

hToTuple :: HList '[a, b, c, d, e, f, g, h, i] -> Tuple '[a, b, c, d, e, f, g, h, i] Source #

hFromTuple :: Tuple '[a, b, c, d, e, f, g, h, i] -> HList '[a, b, c, d, e, f, g, h, i] Source #

HTuple '[a, b, c, d, e, f, g, h] Source # 
Instance details

Defined in Haskus.Utils.HList

Methods

hToTuple :: HList '[a, b, c, d, e, f, g, h] -> Tuple '[a, b, c, d, e, f, g, h] Source #

hFromTuple :: Tuple '[a, b, c, d, e, f, g, h] -> HList '[a, b, c, d, e, f, g, h] Source #

HTuple '[a, b, c, d, e, f, g] Source # 
Instance details

Defined in Haskus.Utils.HList

Methods

hToTuple :: HList '[a, b, c, d, e, f, g] -> Tuple '[a, b, c, d, e, f, g] Source #

hFromTuple :: Tuple '[a, b, c, d, e, f, g] -> HList '[a, b, c, d, e, f, g] Source #

HTuple '[a, b, c, d, e, f] Source # 
Instance details

Defined in Haskus.Utils.HList

Methods

hToTuple :: HList '[a, b, c, d, e, f] -> Tuple '[a, b, c, d, e, f] Source #

hFromTuple :: Tuple '[a, b, c, d, e, f] -> HList '[a, b, c, d, e, f] Source #

HTuple '[a, b, c, d, e] Source # 
Instance details

Defined in Haskus.Utils.HList

Methods

hToTuple :: HList '[a, b, c, d, e] -> Tuple '[a, b, c, d, e] Source #

hFromTuple :: Tuple '[a, b, c, d, e] -> HList '[a, b, c, d, e] Source #

HTuple '[a, b, c, d] Source # 
Instance details

Defined in Haskus.Utils.HList

Methods

hToTuple :: HList '[a, b, c, d] -> Tuple '[a, b, c, d] Source #

hFromTuple :: Tuple '[a, b, c, d] -> HList '[a, b, c, d] Source #

HTuple '[a, b, c] Source # 
Instance details

Defined in Haskus.Utils.HList

Methods

hToTuple :: HList '[a, b, c] -> Tuple '[a, b, c] Source #

hFromTuple :: Tuple '[a, b, c] -> HList '[a, b, c] Source #

HTuple '[a, b] Source # 
Instance details

Defined in Haskus.Utils.HList

Methods

hToTuple :: HList '[a, b] -> Tuple '[a, b] Source #

hFromTuple :: Tuple '[a, b] -> HList '[a, b] Source #

HTuple '[a] Source # 
Instance details

Defined in Haskus.Utils.HList

Methods

hToTuple :: HList '[a] -> Tuple '[a] Source #

hFromTuple :: Tuple '[a] -> HList '[a] Source #

class Apply f a b where Source #

Apply the function identified by the data type f from type a to type b.

Methods

apply :: f -> a -> b Source #

class HZipList x y l | x y -> l, l -> x y Source #

Minimal complete definition

hZipList, hUnzipList

Instances

Instances details
HZipList ('[] :: [Type]) ('[] :: [Type]) ('[] :: [Type]) Source # 
Instance details

Defined in Haskus.Utils.HList

Methods

hZipList :: HList '[] -> HList '[] -> HList '[] Source #

hUnzipList :: HList '[] -> (HList '[], HList '[])

((x, y) ~ z, HZipList xs ys zs) => HZipList (x ': xs) (y ': ys) (z ': zs) Source # 
Instance details

Defined in Haskus.Utils.HList

Methods

hZipList :: HList (x ': xs) -> HList (y ': ys) -> HList (z ': zs) Source #

hUnzipList :: HList (z ': zs) -> (HList (x ': xs), HList (y ': ys))

hZipList :: HZipList x y l => HList x -> HList y -> HList l Source #

class HFoldr f v (l :: [Type]) r Source #

Minimal complete definition

hFoldr

Instances

Instances details
v ~ v' => HFoldr f v ('[] :: [Type]) v' Source # 
Instance details

Defined in Haskus.Utils.HList

Methods

hFoldr :: f -> v -> HList '[] -> v' Source #

(Apply f (e, r) r', HFoldr f v l r) => HFoldr f v (e ': l) r' Source # 
Instance details

Defined in Haskus.Utils.HList

Methods

hFoldr :: f -> v -> HList (e ': l) -> r' Source #

hFoldr :: HFoldr f v l r => f -> v -> HList l -> r Source #

class HFoldl f (z :: Type) xs (r :: Type) Source #

Minimal complete definition

hFoldl

Instances

Instances details
z ~ z' => HFoldl f z ('[] :: [Type]) z' Source # 
Instance details

Defined in Haskus.Utils.HList

Methods

hFoldl :: f -> z -> HList '[] -> z' Source #

(zx ~ (z, x), Apply f zx z', HFoldl f z' xs r) => HFoldl f z (x ': xs) r Source # 
Instance details

Defined in Haskus.Utils.HList

Methods

hFoldl :: f -> z -> HList (x ': xs) -> r Source #

hFoldl :: HFoldl f z xs r => f -> z -> HList xs -> r Source #

class HReverse xs sx | xs -> sx, sx -> xs where Source #

Methods

hReverse :: HList xs -> HList sx Source #

Instances

Instances details
(HRevApp xs ('[] :: [Type]) sx, HRevApp sx ('[] :: [Type]) xs) => HReverse xs sx Source # 
Instance details

Defined in Haskus.Utils.HList

Methods

hReverse :: HList xs -> HList sx Source #