HList-0.3.0: Heterogeneous lists

Safe HaskellNone

Data.HList.HZip

Contents

Description

The HList library

(C) 2004, Oleg Kiselyov, Ralf Laemmel, Keean Schupke

Zipping and unzipping for (conceptually) lists of pairs.

Provides two alternative implementations

Synopsis

zip

functional dependency

class HZip x y l | x y -> l, l -> x y whereSource

Methods

hZip :: HList x -> HList y -> HList lSource

hUnzip :: HList l -> (HList x, HList y)Source

Instances

HZip ([] *) ([] *) ([] *) 
(~ * (x, y) z, HZip xs ys zs) => HZip (: * x xs) (: * y ys) (: * z zs) 

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

Associated Types

type MapFst z :: [*]Source

type MapSnd z :: [*]Source

Methods

hZip2 :: HList (MapFst z) -> HList (MapSnd z) -> HList zSource

hUnzip2 :: HList z -> (HList (MapFst z), HList (MapSnd z))Source

Instances

HUnZip ([] *) 
(~ * z (x, y), HUnZip zs) => HUnZip (: * z zs) 

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?

type family Fst a Source

type family Snd a Source

transpose

hTranspose :: (HReplicate (HLength a) (HList ([] *)), HFoldr HZipF (HList (HReplicateR (HLength a) (HList ([] *)))) l (HList b), HZip3 a b c) => 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]]

helpers

class HZip3 x y l | x y -> l, l -> x y whereSource

same as HZip but HCons the elements of x onto y. This might be doable as a hMap f (hZip x y), but that one doesn't propagate types as easily it seems.

Methods

hZip3 :: HList x -> HList y -> HList lSource

Instances

HZip3 ([] *) ([] *) ([] *) 
(~ * (HList (: * x y)) z, HZip3 xs ys zs) => HZip3 (: * x xs) (: * (HList y) ys) (: * z zs) 

data HZipF Source

Constructors

HZipF 

Instances

(HZip3 a b c, ~ * x (HList a, HList b), ~ * y (HList c)) => ApplyAB HZipF x y