HList-0.2.1: Heterogeneous lists

Data.HList.GhcRecord

Documentation

hUnproxyLabel :: (HUpdateAtHNat n (LVPair l a) t l', HFind l ls n, RecordLabels t ls, HasField l t (Proxy a)) => l -> a -> Record t -> Record l'Source

class NarrowM a b res | a b -> res whereSource

Methods

narrowM :: Record a -> Record b -> resSource

Instances

NarrowM a HNil (HJust (Record HNil)) 
(H2ProjectByLabels (HCons l HNil) a rin rout, NarrowM' rin rout b res) => NarrowM a (HCons (LVPair l v) b) res 

class NarrowM' rin rout b res | rin rout b -> res whereSource

Methods

narrowM' :: rin -> rout -> b -> resSource

Instances

NarrowM' HNil rout b HNothing 
(NarrowM rout b res', NarrowM'' f res' res) => NarrowM' (HCons f HNil) rout b res 

class NarrowM'' f r r' | f r -> r' whereSource

Methods

narrowM'' :: f -> r -> r'Source

class Narrow a b whereSource

Methods

narrow :: Record a -> Record bSource

Instances

Narrow a HNil 
(Narrow rout r', H2ProjectByLabels (HCons l HNil) r (HCons (LVPair l v) HNil) rout) => Narrow r (HCons (LVPair l v) r') 

class LubNarrow a b c | a b -> c whereSource

Methods

lubNarrow :: a -> b -> (c, c)Source

Instances

(RecordLabels a la, RecordLabels b lb, HTIntersect la lb lc, H2ProjectByLabels lc a c aout, H2ProjectByLabels lc b c bout, HRLabelSet c) => LubNarrow (Record a) (Record b) (Record c) 

data NilLub Source

Instances

ConsLub e NilLub [e] 

class ConsLub h t l | h t -> l whereSource

Methods

consLub :: h -> t -> lSource

Instances

ConsLub e NilLub [e] 
LubNarrow e0 e1 e2 => ConsLub e0 [e1] [e2] 

class HLub l e | l -> e whereSource

Methods

hLub :: l -> [e]Source

Instances

(HLub (HCons h (HCons h'' t)) e', HLub (HCons h' (HCons h'' t)) e'', LubNarrow e' e'' e, HLub (HCons e (HCons h'' t)) e) => HLub (HCons h (HCons h' (HCons h'' t))) e 
LubNarrow h h' e => HLub (HCons h (HCons h' HNil)) e 

class RecordEquiv r1 r2 res | r1 r2 -> res whereSource

Methods

equivR :: Record r1 -> Record r2 -> resSource

Instances

(NarrowM r1 r2 r12, NarrowM r2 r1 r21, RecordEquiv' (Record r1 -> r12) (Record r2 -> r21) res) => RecordEquiv r1 r2 res 

class RecordEquiv' pj1 pj2 res | pj1 pj2 -> res whereSource

Methods

equivR' :: pj1 -> pj2 -> resSource

Instances

RecordEquiv' (r1 -> HNothing) pj2 HNothing 
RecordEquiv' (r1 -> HJust r2) (r2 -> HNothing) HNothing 
RecordEquiv' (r1 -> HJust r2) (r2 -> HJust r1) (HJust (r1 -> r2, r2 -> r1))