mgeneric-0.0.0.0: Generics with multiple parameters

Safe HaskellNone
LanguageHaskell2010

Data.MZipWith

Documentation

type family Dom f Source

Equations

Dom (a -> b) = a 

type family Codom f Source

Equations

Codom (a -> b) = b 

type family Doms fs :: [*] Source

Equations

Doms [] = [] 
Doms ((a -> b) : as) = a : Doms as 

type family Codoms fs :: [*] Source

Equations

Codoms [] = [] 
Codoms ((a -> b) : as) = b : Codoms as 

type family LCodoms n fs Source

Equations

LCodoms NZ fs = fs 
LCodoms (NS n) fs = LCodoms n (Codoms fs) 

type family Map f as :: [*] Source

Equations

Map f [] = [] 
Map f (a : as) = f a : Map f as 

type family ZipInput n f Source

Equations

ZipInput NZ a = Maybe a 
ZipInput (NS n) (a -> b) = a -> ZipInput n b 

type family ZipInputs n fs Source

Equations

ZipInputs n [] = [] 
ZipInputs n (f : fs) = ZipInput n f : ZipInputs n fs 

type family ZipWithType' n f fs :: * Source

Equations

ZipWithType' NZ f fs = f :$: fs 
ZipWithType' (NS n) f fs = (f :$: Doms fs) -> ZipWithType' n f (Codoms fs) 

type family ZipWithType n f fs :: * Source

Equations

ZipWithType NZ f fs = Maybe (f :$: fs) 
ZipWithType (NS n) f fs = (f :$: Doms fs) -> ZipWithType n f (Codoms fs) 

type family ZipWithTypeUn n f fs :: * Source

Equations

ZipWithTypeUn NZ f fs = Maybe (In f fs) 
ZipWithTypeUn (NS n) f fs = In f (Doms fs) -> ZipWithTypeUn n f (Codoms fs) 

type family ZipWithTypeField n f fs :: * Source

Equations

ZipWithTypeField NZ f fs = Maybe (InField f fs) 
ZipWithTypeField (NS n) f fs = InField f (Doms fs) -> ZipWithTypeField n f (Codoms fs) 

class MZipWithG n f rf fs where Source

Methods

mzipWithPG :: Proxy n -> Proxy f -> Proxy rf -> Proxy fs -> ZipWithTypeUn n rf fs -> ZipWithType n f fs Source

Instances

((~) [*] fs (Pars ((:$:) k f fs)), (~) (Un *) rf (Rep ((:$:) k f fs)), MGeneric ((:$:) k f fs)) => MZipWithG k NZ f rf fs 
(MZipWithG k n f rf (Codoms fs), (~) (Un *) rf (Rep ((:$:) k f (Doms fs))), (~) [*] (Doms fs) (Pars ((:$:) k f (Doms fs))), MGeneric ((:$:) k f (Doms fs))) => MZipWithG k (NS n) f rf fs 

class MZipWith n f fs where Source

Minimal complete definition

Nothing

Methods

mzipWithP :: Proxy n -> Proxy f -> Proxy fs -> HList (ZipInputs n fs) -> ZipWithType n f fs Source

Instances

(MZipWithG * n () (Rep ((:$:) * () (LCodoms n ([] *)))) ([] *), GMZipWith n (Rep ((:$:) * () (LCodoms n ([] *)))) ([] *)) => MZipWith * n () ([] *) 
(MZipWithG * n Ordering (Rep ((:$:) * Ordering (LCodoms n ([] *)))) ([] *), GMZipWith n (Rep ((:$:) * Ordering (LCodoms n ([] *)))) ([] *)) => MZipWith * n Ordering ([] *) 
(MZipWithG * n Bool (Rep ((:$:) * Bool (LCodoms n ([] *)))) ([] *), GMZipWith n (Rep ((:$:) * Bool (LCodoms n ([] *)))) ([] *)) => MZipWith * n Bool ([] *) 
(MZipWithG (* -> * -> * -> * -> * -> * -> * -> * -> * -> *) n (,,,,,,,,) (Rep ((:$:) (* -> * -> * -> * -> * -> * -> * -> * -> * -> *) (,,,,,,,,) (LCodoms n ((:) * f ((:) * g ((:) * h ((:) * i ((:) * j ((:) * k ((:) * l ((:) * m ((:) * o ([] *))))))))))))) ((:) * f ((:) * g ((:) * h ((:) * i ((:) * j ((:) * k ((:) * l ((:) * m ((:) * o ([] *)))))))))), GMZipWith n (Rep ((:$:) (* -> * -> * -> * -> * -> * -> * -> * -> * -> *) (,,,,,,,,) (LCodoms n ((:) * f ((:) * g ((:) * h ((:) * i ((:) * j ((:) * k ((:) * l ((:) * m ((:) * o ([] *))))))))))))) ((:) * f ((:) * g ((:) * h ((:) * i ((:) * j ((:) * k ((:) * l ((:) * m ((:) * o ([] *))))))))))) => MZipWith (* -> * -> * -> * -> * -> * -> * -> * -> * -> *) n (,,,,,,,,) ((:) * f ((:) * g ((:) * h ((:) * i ((:) * j ((:) * k ((:) * l ((:) * m ((:) * o ([] *)))))))))) 
(MZipWithG (* -> * -> * -> * -> * -> * -> * -> * -> *) n (,,,,,,,) (Rep ((:$:) (* -> * -> * -> * -> * -> * -> * -> * -> *) (,,,,,,,) (LCodoms n ((:) * f ((:) * g ((:) * h ((:) * i ((:) * j ((:) * k ((:) * l ((:) * m ([] *)))))))))))) ((:) * f ((:) * g ((:) * h ((:) * i ((:) * j ((:) * k ((:) * l ((:) * m ([] *))))))))), GMZipWith n (Rep ((:$:) (* -> * -> * -> * -> * -> * -> * -> * -> *) (,,,,,,,) (LCodoms n ((:) * f ((:) * g ((:) * h ((:) * i ((:) * j ((:) * k ((:) * l ((:) * m ([] *)))))))))))) ((:) * f ((:) * g ((:) * h ((:) * i ((:) * j ((:) * k ((:) * l ((:) * m ([] *)))))))))) => MZipWith (* -> * -> * -> * -> * -> * -> * -> * -> *) n (,,,,,,,) ((:) * f ((:) * g ((:) * h ((:) * i ((:) * j ((:) * k ((:) * l ((:) * m ([] *))))))))) 
(MZipWithG (* -> * -> * -> * -> * -> * -> * -> *) n (,,,,,,) (Rep ((:$:) (* -> * -> * -> * -> * -> * -> * -> *) (,,,,,,) (LCodoms n ((:) * f ((:) * g ((:) * h ((:) * i ((:) * j ((:) * k ((:) * l ([] *))))))))))) ((:) * f ((:) * g ((:) * h ((:) * i ((:) * j ((:) * k ((:) * l ([] *)))))))), GMZipWith n (Rep ((:$:) (* -> * -> * -> * -> * -> * -> * -> *) (,,,,,,) (LCodoms n ((:) * f ((:) * g ((:) * h ((:) * i ((:) * j ((:) * k ((:) * l ([] *))))))))))) ((:) * f ((:) * g ((:) * h ((:) * i ((:) * j ((:) * k ((:) * l ([] *))))))))) => MZipWith (* -> * -> * -> * -> * -> * -> * -> *) n (,,,,,,) ((:) * f ((:) * g ((:) * h ((:) * i ((:) * j ((:) * k ((:) * l ([] *)))))))) 
(MZipWithG (* -> * -> * -> * -> * -> * -> *) n (,,,,,) (Rep ((:$:) (* -> * -> * -> * -> * -> * -> *) (,,,,,) (LCodoms n ((:) * f ((:) * g ((:) * h ((:) * i ((:) * j ((:) * k ([] *)))))))))) ((:) * f ((:) * g ((:) * h ((:) * i ((:) * j ((:) * k ([] *))))))), GMZipWith n (Rep ((:$:) (* -> * -> * -> * -> * -> * -> *) (,,,,,) (LCodoms n ((:) * f ((:) * g ((:) * h ((:) * i ((:) * j ((:) * k ([] *)))))))))) ((:) * f ((:) * g ((:) * h ((:) * i ((:) * j ((:) * k ([] *)))))))) => MZipWith (* -> * -> * -> * -> * -> * -> *) n (,,,,,) ((:) * f ((:) * g ((:) * h ((:) * i ((:) * j ((:) * k ([] *))))))) 
(MZipWithG (* -> * -> * -> * -> * -> *) n (,,,,) (Rep ((:$:) (* -> * -> * -> * -> * -> *) (,,,,) (LCodoms n ((:) * f ((:) * g ((:) * h ((:) * i ((:) * j ([] *))))))))) ((:) * f ((:) * g ((:) * h ((:) * i ((:) * j ([] *)))))), GMZipWith n (Rep ((:$:) (* -> * -> * -> * -> * -> *) (,,,,) (LCodoms n ((:) * f ((:) * g ((:) * h ((:) * i ((:) * j ([] *))))))))) ((:) * f ((:) * g ((:) * h ((:) * i ((:) * j ([] *))))))) => MZipWith (* -> * -> * -> * -> * -> *) n (,,,,) ((:) * f ((:) * g ((:) * h ((:) * i ((:) * j ([] *)))))) 
(MZipWithG (* -> * -> * -> * -> *) n (,,,) (Rep ((:$:) (* -> * -> * -> * -> *) (,,,) (LCodoms n ((:) * f ((:) * g ((:) * h ((:) * i ([] *)))))))) ((:) * f ((:) * g ((:) * h ((:) * i ([] *))))), GMZipWith n (Rep ((:$:) (* -> * -> * -> * -> *) (,,,) (LCodoms n ((:) * f ((:) * g ((:) * h ((:) * i ([] *)))))))) ((:) * f ((:) * g ((:) * h ((:) * i ([] *)))))) => MZipWith (* -> * -> * -> * -> *) n (,,,) ((:) * f ((:) * g ((:) * h ((:) * i ([] *))))) 
(MZipWithG (* -> * -> * -> *) n (,,) (Rep ((:$:) (* -> * -> * -> *) (,,) (LCodoms n ((:) * f ((:) * g ((:) * h ([] *))))))) ((:) * f ((:) * g ((:) * h ([] *)))), GMZipWith n (Rep ((:$:) (* -> * -> * -> *) (,,) (LCodoms n ((:) * f ((:) * g ((:) * h ([] *))))))) ((:) * f ((:) * g ((:) * h ([] *))))) => MZipWith (* -> * -> * -> *) n (,,) ((:) * f ((:) * g ((:) * h ([] *)))) 
(MZipWithG (* -> * -> * -> *) n Test (Rep ((:$:) (* -> * -> * -> *) Test (LCodoms n ((:) * f ((:) * g ((:) * h ([] *))))))) ((:) * f ((:) * g ((:) * h ([] *)))), GMZipWith n (Rep ((:$:) (* -> * -> * -> *) Test (LCodoms n ((:) * f ((:) * g ((:) * h ([] *))))))) ((:) * f ((:) * g ((:) * h ([] *))))) => MZipWith (* -> * -> * -> *) n Test ((:) * f ((:) * g ((:) * h ([] *)))) 
(MZipWithG (* -> * -> *) n (,) (Rep ((:$:) (* -> * -> *) (,) (LCodoms n ((:) * f ((:) * g ([] *)))))) ((:) * f ((:) * g ([] *))), GMZipWith n (Rep ((:$:) (* -> * -> *) (,) (LCodoms n ((:) * f ((:) * g ([] *)))))) ((:) * f ((:) * g ([] *)))) => MZipWith (* -> * -> *) n (,) ((:) * f ((:) * g ([] *))) 
(MZipWithG (* -> * -> *) n Either (Rep ((:$:) (* -> * -> *) Either (LCodoms n ((:) * f ((:) * g ([] *)))))) ((:) * f ((:) * g ([] *))), GMZipWith n (Rep ((:$:) (* -> * -> *) Either (LCodoms n ((:) * f ((:) * g ([] *)))))) ((:) * f ((:) * g ([] *)))) => MZipWith (* -> * -> *) n Either ((:) * f ((:) * g ([] *))) 
(MZipWithG (* -> *) n First (Rep ((:$:) (* -> *) First (LCodoms n ((:) * f ([] *))))) ((:) * f ([] *)), GMZipWith n (Rep ((:$:) (* -> *) First (LCodoms n ((:) * f ([] *))))) ((:) * f ([] *))) => MZipWith (* -> *) n First ((:) * f ([] *)) 
(MZipWithG (* -> *) n Last (Rep ((:$:) (* -> *) Last (LCodoms n ((:) * f ([] *))))) ((:) * f ([] *)), GMZipWith n (Rep ((:$:) (* -> *) Last (LCodoms n ((:) * f ([] *))))) ((:) * f ([] *))) => MZipWith (* -> *) n Last ((:) * f ([] *)) 
(MZipWithG (* -> *) n Sum (Rep ((:$:) (* -> *) Sum (LCodoms n ((:) * f ([] *))))) ((:) * f ([] *)), GMZipWith n (Rep ((:$:) (* -> *) Sum (LCodoms n ((:) * f ([] *))))) ((:) * f ([] *))) => MZipWith (* -> *) n Sum ((:) * f ([] *)) 
(MZipWithG (* -> *) n Product (Rep ((:$:) (* -> *) Product (LCodoms n ((:) * f ([] *))))) ((:) * f ([] *)), GMZipWith n (Rep ((:$:) (* -> *) Product (LCodoms n ((:) * f ([] *))))) ((:) * f ([] *))) => MZipWith (* -> *) n Product ((:) * f ([] *)) 
(MZipWithG (* -> *) n Maybe (Rep ((:$:) (* -> *) Maybe (LCodoms n ((:) * f ([] *))))) ((:) * f ([] *)), GMZipWith n (Rep ((:$:) (* -> *) Maybe (LCodoms n ((:) * f ([] *))))) ((:) * f ([] *))) => MZipWith (* -> *) n Maybe ((:) * f ([] *)) 
(MZipWithG (* -> *) n [] (Rep ((:$:) (* -> *) [] (LCodoms n ((:) * f ([] *))))) ((:) * f ([] *)), GMZipWith n (Rep ((:$:) (* -> *) [] (LCodoms n ((:) * f ([] *))))) ((:) * f ([] *))) => MZipWith (* -> *) n [] ((:) * f ([] *)) 

class GMZipWith n f fs where Source

Methods

mzipWithG :: Proxy n -> Proxy f -> Proxy fs -> HList (ZipInputs n fs) -> ZipWithTypeUn n f fs Source

Instances

GMTZipWith n fs => GMZipWith n (UT *) fs 
GMZipWith n (UV *) fs 
(GFMZipWith n f fs, GMZipWithF n f fs) => GMZipWith n (UF * f) fs 
(GMZipWith n u fs, GMZipWith n v fs, GPiMZipWith n u v fs) => GMZipWith n ((:**:) * u v) fs 
(GMZipWith (NS n) u fs, GMZipWith (NS n) v fs, GMLZipWith n u v (Codoms fs), GMRZipWith n u v (Codoms fs)) => GMZipWith (NS n) ((:++:) * u v) fs 

class GMTZipWith n fs where Source

Methods

mzipWithGT :: Proxy n -> Proxy fs -> ZipWithTypeUn n UT fs Source

Instances

GMTZipWith NZ fs 
GMTZipWith n (Codoms fs) => GMTZipWith (NS n) fs 

class GMZipWithFail n u fs where Source

Methods

mzipWithFail :: Proxy n -> Proxy u -> Proxy fs -> ZipWithTypeUn n u fs Source

Instances

class GMLZipWith n u v fs where Source

Methods

mzipWithGL :: Proxy n -> Proxy u -> Proxy v -> Proxy fs -> ZipWithTypeUn n u fs -> ZipWithTypeUn n (u :++: v) fs Source

Instances

GMLZipWith NZ u v fs 
(GMLZipWith n u v (Codoms fs), GMZipWithFail n ((:++:) * u v) (Codoms fs)) => GMLZipWith (NS n) u v fs 

class GMRZipWith n u v fs where Source

Methods

mzipWithGR :: Proxy n -> Proxy u -> Proxy v -> Proxy fs -> ZipWithTypeUn n v fs -> ZipWithTypeUn n (u :++: v) fs Source

Instances

GMRZipWith NZ u v fs 
(GMRZipWith n u v (Codoms fs), GMZipWithFail n ((:++:) * u v) (Codoms fs)) => GMRZipWith (NS n) u v fs 

class GPiMZipWith n u v fs where Source

Methods

mzipWithGPi :: Proxy n -> Proxy u -> Proxy v -> Proxy fs -> ZipWithTypeUn n u fs -> ZipWithTypeUn n v fs -> ZipWithTypeUn n (u :**: v) fs Source

Instances

GPiMZipWith NZ u v fs 
GPiMZipWith n u v (Codoms fs) => GPiMZipWith (NS n) u v fs 

class GMZipWithF n f fs where Source

Methods

mzipWithGFF :: Proxy n -> Proxy f -> Proxy fs -> ZipWithTypeField n f fs -> ZipWithTypeUn n (UF f) fs Source

Instances

GMZipWithF NZ f fs 
GMZipWithF n f (Codoms fs) => GMZipWithF (NS n) f fs 

class GFMZipWith n f fs where Source

Methods

mzipWithGF :: Proxy n -> Proxy f -> Proxy fs -> HList (ZipInputs n fs) -> ZipWithTypeField n f fs Source

Instances

(GFPMZipWith n m fs, HLookup m n fs) => GFMZipWith n (FP * m) fs 
(GFAMZipWith k n f as fs, MZipWith k n f (ExpandFieldFunction n as fs), AdaptFieldFunction n as fs) => GFMZipWith n ((:@:) * k f as) fs 

class GFPMZipWith n m fs where Source

Methods

mzipWithGFP :: Proxy n -> Proxy m -> Proxy fs -> (ZipInputs n fs :!: m) -> ZipWithTypeField n (FP m) fs Source

Instances

(~) * (Maybe ((:!:) fs m)) ((:!:) (ZipInputs NZ fs) m) => GFPMZipWith NZ m fs 
((~) * ((:!:) (ZipInputs (NS n) fs) m) ((:!:) (Doms fs) m -> (:!:) (ZipInputs n (Codoms fs)) m), GFPMZipWith n m (Codoms fs)) => GFPMZipWith (NS n) m fs 

class HLookup n m fs where Source

Methods

hlookup :: Proxy n -> Proxy m -> Proxy fs -> HList (ZipInputs m fs) -> ZipInputs m fs :!: n Source

Instances

HLookup NZ m ((:) * a as) 
HLookup n m as => HLookup (NS n) m ((:) * a as) 

type family ExpandFieldFunction n f ps :: [*] Source

Equations

ExpandFieldFunction n [] ps = [] 
ExpandFieldFunction n (FP m : fs) ps = (ps :!: m) : ExpandFieldFunction n fs ps 
ExpandFieldFunction n ((f :@: as) : fs) ps = ZipWithType' n f (ExpandFieldFunction n as ps) : ExpandFieldFunction n fs ps 

class AdaptFieldFunction n f ps where Source

Methods

adaptFieldFunction :: Proxy n -> Proxy f -> Proxy ps -> HList (ZipInputs n ps) -> HList (ZipInputs n (ExpandFieldFunction n f ps)) Source

Instances

AdaptFieldFunction n ([] (Field *)) ps 
(MZipWith k n f (ExpandFieldFunction n bs ps), (~) * (ZipInput n (ZipWithType' k n f (ExpandFieldFunction n bs ps))) (ZipWithType k n f (ExpandFieldFunction n bs ps)), AdaptFieldFunction n bs ps, AdaptFieldFunction n as ps) => AdaptFieldFunction n ((:) (Field *) ((:@:) * k f bs) as) ps 
(HLookup m n ps, (~) * (ZipInput n ((:!:) ps m)) ((:!:) (ZipInputs n ps) m), AdaptFieldFunction n as ps) => AdaptFieldFunction n ((:) (Field *) (FP * m) as) ps 

class GFAMZipWith n f as fs where Source

Methods

mzipWithGFA :: Proxy n -> Proxy f -> Proxy as -> Proxy fs -> ZipWithType n f (ExpandFieldFunction n as fs) -> ZipWithTypeField n (f :@: as) fs Source

Instances

(~) [*] (ExpandField as fs) (ExpandFieldFunction NZ as fs) => GFAMZipWith k NZ f as fs 
((~) [*] (ExpandFieldFunction n as (Codoms fs)) (Codoms (ExpandFieldFunction (NS n) as fs)), (~) [*] (Doms (ExpandFieldFunction (NS n) as fs)) (ExpandField as (Doms fs)), GFAMZipWith k n f as (Codoms fs)) => GFAMZipWith k (NS n) f as fs