Safe Haskell | None |
---|
The HList library
(C) 2004, Oleg Kiselyov, Ralf Laemmel, Keean Schupke
Zipping and unzipping for (conceptually) lists of pairs.
Provides two alternative implementations
- class HZip x y l | x y -> l, l -> x y where
- class HZipR (MapFst z) (MapSnd z) ~ z => HUnZip z where
- type family HZipR x y :: [*]
- type family Fst a
- type family Snd a
- hTranspose :: (HReplicate (HLength * uf) (HList ([] *)), HFoldr HZipF (HList uf) l (HList b), HZip3 a b c, ~ HNat (HLength * a) (HLength * uf), ~ [*] (HReplicateR * (HLength * uf) (HList ([] *))) uf) => HList (: * (HList a) l) -> HList c
- class HZip3 x y l | x y -> l, l -> x y where
- data HZipF = HZipF
zip
functional dependency
type family
hZip2
can be written as a standalone function, with an appropriate
type family to calculate the result type. However, that does not seem to
be the case for hUnzip2
, so to re-use some type functions the two are
in the same class.
class HZipR (MapFst z) (MapSnd z) ~ z => HUnZip z whereSource
HZipR in the superclass constraint doesn't hurt, but it doesn't seem to be necessary
type family HZipR x y :: [*]Source
calculates something like:
[a] -> [b] -> [(a,b)]
can be used to give another type for hZip2
hZip2 :: HList a -> HList b -> HList (HZipR a b)
utility type functions
do they belong somewhere else?
transpose
hTranspose :: (HReplicate (HLength * uf) (HList ([] *)), HFoldr HZipF (HList uf) l (HList b), HZip3 a b c, ~ HNat (HLength * a) (HLength * uf), ~ [*] (HReplicateR * (HLength * uf) (HList ([] *))) uf) => HList (: * (HList a) l) -> HList cSource
this transpose requires equal-length HLists inside a HList:
>>>
import Data.HList.HListPrelude
>>>
let ex = (1 .*. 2 .*. HNil) .*. ('a' .*. 'b' .*. HNil) .*. ( 3 .*. 5 .*. HNil) .*. HNil
The original list:
>>>
ex
H[H[1, 2], H['a', 'b'], H[3, 5]]
And transposed:
>>>
hTranspose ex
H[H[1, 'a', 3], H[2, 'b', 5]]