module Data.HList.HZip where
import Data.HList.HList
import Data.HList.FakePrelude
class HZipR (MapFst z) (MapSnd z) ~ z => HUnZip z where
type MapFst z :: [*]
type MapSnd z :: [*]
hZip2 :: HList (MapFst z) -> HList (MapSnd z) -> HList z
hUnzip2 :: HList z -> (HList (MapFst z), HList (MapSnd z))
instance HUnZip '[] where
type MapFst '[] = '[]
type MapSnd '[] = '[]
hZip2 :: HList (MapFst '[]) -> HList (MapSnd '[]) -> HList '[]
hZip2 HList (MapFst '[])
_ HList (MapSnd '[])
_ = HList '[]
HNil
hUnzip2 :: HList '[] -> (HList (MapFst '[]), HList (MapSnd '[]))
hUnzip2 HList '[]
_ = (HList '[]
HNil, HList '[]
HNil)
instance (z ~ (x,y), HUnZip zs) => HUnZip (z ': zs) where
type MapFst (z ': zs) = ( Fst z ': MapFst zs )
type MapSnd (z ': zs) = ( Snd z ': MapSnd zs )
hZip2 :: HList (MapFst (z : zs))
-> HList (MapSnd (z : zs)) -> HList (z : zs)
hZip2 (HCons x
x HList (MapFst zs)
xs) (HCons y
y HList (MapSnd zs)
ys) = forall x (xs :: [*]). x -> HList xs -> HList (x : xs)
HCons (x
x,y
y) (forall (z :: [*]).
HUnZip z =>
HList (MapFst z) -> HList (MapSnd z) -> HList z
hZip2 HList (MapFst zs)
xs HList (MapSnd zs)
ys)
hUnzip2 :: HList (z : zs)
-> (HList (MapFst (z : zs)), HList (MapSnd (z : zs)))
hUnzip2 (HCons ~(x
x,y
y) HList zs
zs) = let ~(HList (MapFst zs)
xs,HList (MapSnd zs)
ys) = forall (z :: [*]).
HUnZip z =>
HList z -> (HList (MapFst z), HList (MapSnd z))
hUnzip2 HList zs
zs in (x
x forall x (xs :: [*]). x -> HList xs -> HList (x : xs)
`HCons` HList (MapFst zs)
xs, y
y forall x (xs :: [*]). x -> HList xs -> HList (x : xs)
`HCons` HList (MapSnd zs)
ys)
type family HZipR (x::[*]) (y::[*]) :: [*]
type instance HZipR '[] '[] = '[]
type instance HZipR (x ': xs) (y ': ys) = (x,y) ': HZipR xs ys
type family Fst a
type instance Fst (a,b) = a
type family Snd a
type instance Snd (a,b) = b
hTranspose :: HList (HList a : l) -> HList c
hTranspose HList (HList a : l)
x = forall f v (l :: [*]) r. HFoldr f v l r => f -> v -> HList l -> r
hFoldr HZipF
HZipF (forall (n :: HNat) e (es :: [*]).
HReplicateFD n e es =>
Proxy n -> e -> HList es
hReplicate (forall (l :: [*]) (n :: HNat). HLengthEq l n => HList l -> Proxy n
hLength (forall e (l :: [*]). HList (e : l) -> e
hHead HList (HList a : l)
x)) HList '[]
HNil) HList (HList a : l)
x
class HZip3 x y l | x y -> l, l -> x y where
hZip3 :: HList x -> HList y -> HList l
instance HZip3 '[] '[] '[] where
hZip3 :: HList '[] -> HList '[] -> HList '[]
hZip3 HList '[]
_ HList '[]
_ = HList '[]
HNil
instance (HList (x ': y) ~ z, HZip3 xs ys zs) => HZip3 (x ': xs) (HList y ': ys) (z ': zs) where
hZip3 :: HList (x : xs) -> HList (HList y : ys) -> HList (z : zs)
hZip3 (HCons x
x HList xs
xs) (HCons HList y
y HList ys
ys) = forall x (xs :: [*]). x -> HList xs -> HList (x : xs)
HCons x
x HList y
y forall x (xs :: [*]). x -> HList xs -> HList (x : xs)
`HCons` forall (x :: [*]) (y :: [*]) (l :: [*]).
HZip3 x y l =>
HList x -> HList y -> HList l
hZip3 HList xs
xs HList ys
ys
data HZipF = HZipF
instance (
HZip3 a b c,
x ~ (HList a, HList b),
y ~ HList c) => ApplyAB HZipF x y
where applyAB :: HZipF -> x -> y
applyAB HZipF
_ (HList a
x,HList b
y) = forall (x :: [*]) (y :: [*]) (l :: [*]).
HZip3 x y l =>
HList x -> HList y -> HList l
hZip3 HList a
x HList b
y