haskus-utils-0.8.0.0: Haskus utility modules

Safe HaskellSafe
LanguageHaskell2010

Haskus.Utils.HList

Description

Heterogeneous list utils

Synopsis

Documentation

data family HList (l :: [*]) Source #

Heterogeneous list

Instances

(Eq x, Eq (HList xs)) => Eq (HList ((:) * x xs)) Source # 

Methods

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

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

Eq (HList ([] *)) Source # 

Methods

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

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

(Ord x, Ord (HList xs)) => Ord (HList ((:) * x xs)) Source # 

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 ([] *)) Source # 

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 # 

Methods

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

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

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

Show (HList ([] *)) Source # 

Methods

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

show :: HList [*] -> String #

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

data HList ([] *) Source # 
data HList ([] *) = HNil
data HList ((:) * x xs) Source # 
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 :: [*]) 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.

Minimal complete definition

hFoldr'

Methods

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

Instances

(~) * v v' => HFoldr' f v ([] *) v' Source # 

Methods

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

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

Methods

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

class HFoldl' f (z :: *) xs (r :: *) where Source #

Like HFoldl but only use types, not values!

It allows us to foldr over a list of types, without any associated hlist of values.

Minimal complete definition

hFoldl'

Methods

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

Instances

(~) * z z' => HFoldl' f z ([] *) z' Source # 

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 # 

Methods

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

class HTuple' v t | v -> t, t -> v where Source #

Convert between hlists and tuples

Minimal complete definition

hToTuple', hFromTuple'

Methods

hToTuple' :: HList v -> t Source #

Convert an heterogeneous list into a tuple

hFromTuple' :: t -> HList v Source #

Convert a tuple into an heterogeneous list

Instances

HTuple' ([] *) () Source # 

Methods

hToTuple' :: HList [*] -> () Source #

hFromTuple' :: () -> HList [*] Source #

HTuple' ((:) * a ([] *)) (Single a) Source # 

Methods

hToTuple' :: HList ((* ': a) [*]) -> Single a Source #

hFromTuple' :: Single a -> HList ((* ': a) [*]) Source #

HTuple' ((:) * a ((:) * b ([] *))) (a, b) Source # 

Methods

hToTuple' :: HList ((* ': a) ((* ': b) [*])) -> (a, b) Source #

hFromTuple' :: (a, b) -> HList ((* ': a) ((* ': b) [*])) Source #

HTuple' ((:) * a ((:) * b ((:) * c ([] *)))) (a, b, c) Source # 

Methods

hToTuple' :: HList ((* ': a) ((* ': b) ((* ': c) [*]))) -> (a, b, c) Source #

hFromTuple' :: (a, b, c) -> HList ((* ': a) ((* ': b) ((* ': c) [*]))) Source #

HTuple' ((:) * a ((:) * b ((:) * c ((:) * d ([] *))))) (a, b, c, d) Source # 

Methods

hToTuple' :: HList ((* ': a) ((* ': b) ((* ': c) ((* ': d) [*])))) -> (a, b, c, d) Source #

hFromTuple' :: (a, b, c, d) -> HList ((* ': a) ((* ': b) ((* ': c) ((* ': d) [*])))) Source #

HTuple' ((:) * a ((:) * b ((:) * c ((:) * d ((:) * e ([] *)))))) (a, b, c, d, e) Source # 

Methods

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

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

HTuple' ((:) * a ((:) * b ((:) * c ((:) * d ((:) * e ((:) * f ([] *))))))) (a, b, c, d, e, f) Source # 

Methods

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

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

HTuple' ((:) * a ((:) * b ((:) * c ((:) * d ((:) * e ((:) * f ((:) * g ([] *)))))))) (a, b, c, d, e, f, g) Source # 

Methods

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

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

HTuple' ((:) * a ((:) * b ((:) * c ((:) * d ((:) * e ((:) * f ((:) * g ((:) * h ([] *))))))))) (a, b, c, d, e, f, g, h) Source # 

Methods

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

hFromTuple' :: (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 ((:) * h ((:) * i ([] *)))))))))) (a, b, c, d, e, f, g, h, i) Source # 

Methods

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

hFromTuple' :: (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 ((:) * i ((:) * j ([] *))))))))))) (a, b, c, d, e, f, g, h, i, j) Source # 

Methods

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

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

class Apply f a b where Source #

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

Minimal complete definition

apply

Methods

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

Instances

((~) * x (Flow m xs), (~) * y (Flow m ys), (~) * z (Flow m zs), Popable a xs, Liftable ys zs, Liftable (Filter a xs) zs, (~) [*] zs (Union (Filter a xs) ys), Monad m) => Apply (Choice a) (x, y) z Source # 

Methods

apply :: Choice a -> (x, y) -> z Source #

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

Minimal complete definition

hZipList, hUnzipList

Methods

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

Instances

HZipList ([] *) ([] *) ([] *) Source # 

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 # 

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 :: [*]) r where Source #

Minimal complete definition

hFoldr

Methods

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

Instances

(~) * v v' => HFoldr f v ([] *) v' Source # 

Methods

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

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

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 :: *) xs (r :: *) where Source #

Minimal complete definition

hFoldl

Methods

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

Instances

(~) * z z' => HFoldl f z ([] *) z' Source # 

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 # 

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 #

Minimal complete definition

hReverse

Methods

hReverse :: HList xs -> HList sx Source #

Instances

(HRevApp xs ([] *) sx, HRevApp sx ([] *) xs) => HReverse xs sx Source # 

Methods

hReverse :: HList xs -> HList sx Source #