HList-0.5.0.0: Heterogeneous lists

Safe HaskellNone
LanguageHaskell2010

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

moved to Data.HList.HList to avoid an orphan instance

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 where Source #

HZipR in the superclass constraint doesn't hurt, but it doesn't seem to be necessary

Minimal complete definition

hZip2, hUnzip2

Associated Types

type MapFst z :: [*] Source #

type MapSnd z :: [*] Source #

Methods

hZip2 :: HList (MapFst z) -> HList (MapSnd z) -> HList z Source #

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

Instances

HUnZip ([] *) Source # 

Associated Types

type MapFst ([*] :: [*]) :: [*] Source #

type MapSnd ([*] :: [*]) :: [*] Source #

Methods

hZip2 :: HList (MapFst [*]) -> HList (MapSnd [*]) -> HList [*] Source #

hUnzip2 :: HList [*] -> (HList (MapFst [*]), HList (MapSnd [*])) Source #

((~) * z (x, y), HUnZip zs) => HUnZip ((:) * z zs) Source # 

Associated Types

type MapFst ((* ': z) zs :: [*]) :: [*] Source #

type MapSnd ((* ': z) zs :: [*]) :: [*] Source #

Methods

hZip2 :: HList (MapFst ((* ': z) zs)) -> HList (MapSnd ((* ': z) zs)) -> HList ((* ': z) zs) Source #

hUnzip2 :: HList ((* ': z) zs) -> (HList (MapFst ((* ': z) zs)), HList (MapSnd ((* ': z) zs))) Source #

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)

Instances

type HZipR ([] *) ([] *) Source # 
type HZipR ([] *) ([] *) = [] *
type HZipR ((:) * x xs) ((:) * y ys) Source # 
type HZipR ((:) * x xs) ((:) * y ys) = (:) * (x, y) (HZipR xs ys)

utility type functions

do they belong somewhere else?

type family Fst a Source #

Instances

type Fst (a, b) Source # 
type Fst (a, b) = a

type family Snd a Source #

Instances

type Snd (a, b) Source # 
type Snd (a, b) = b

transpose

hTranspose :: (HLengthEq2 HNat a n, HLengthEq1 HNat a n, SameLength' * * (HReplicateR * n ()) a, HReplicateFD n (HList ([] *)) es, HFoldr HZipF (HList es) l (HList b), HZip3 a b c) => HList ((:) * (HList a) l) -> HList c Source #

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 where Source #

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.

Minimal complete definition

hZip3

Methods

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

Instances

HZip3 ([] *) ([] *) ([] *) Source # 

Methods

hZip3 :: HList [*] -> HList [*] -> HList [*] Source #

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

Methods

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

data HZipF Source #

Constructors

HZipF 

Instances

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

Methods

applyAB :: HZipF -> x -> y Source #