HList-0.3.0: Heterogeneous lists

Safe HaskellNone

Data.HList.Variant

Description

The HList library

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

Variants, i.e., labelled sums.

One approach to their implementation would be to consider both the favoured label and the corresponding value as dynamics upon variant construction. Since we are too lazy to programme some Typeable instances for non-ghc systems (NB: in GHC, Typeable is derivable), we rather model variants as (opaque) records with maybies for the values. Only one value will actually hold non-Nothing, as guaranteed by the constructor.

See VariantP.hs for a different approach to open sums.

Synopsis

Documentation

newtype Variant mr Source

Variant types on the basis of label-maybe pairs.

Constructors

Variant mr 

Instances

Show (Variant v)

Variants are opaque

data HMaybeF Source

Turn proxy sequence into sequence of Nothings

Constructors

HMaybeF 

Instances

(~ * (LVPair k l (Proxy * t)) a, ~ * b (LVPair k l (Maybe t))) => ApplyAB HMaybeF a b 

hMaybied :: (HMapAux HMaybeF as' bs', SameLength [*] [*] bs' as', SameLength [*] [*] as' bs') => HList as' -> HList bs'Source

mkVariant :: (HFind k l (RecordLabels k r) n, HMapAux HMaybeF as' r, SameLength [*] [*] r as', SameLength [*] [*] as' r, HUpdateAtHNat n (LVPair k l (Maybe a)) r, ~ [*] (HUpdateAtHNatR n (LVPair k l (Maybe a)) r) r) => Label k l -> a -> Record as' -> Variant (HList r)Source

Public constructor it seems we can blame hUpdateAtLabel (not HMap) for needing the asTypeOf?

unVariant :: HasField k l (Record r) v => Label k l -> Variant (HList r) -> vSource

Public destructor