HList-0.5.2.0: Heterogeneous lists
Safe HaskellNone
LanguageHaskell2010

Data.HList.Label3

Description

The HList library

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

A model of labels as needed for extensible records. As before, all the information about labels is recorded in their type, so the labels of records may be purely phantom. In general, Labels are exclusively type-level entities and have no run-time representation.

Record labels are triplets of type-level naturals, namespace, and description. The namespace part helps avoid confusions between labels from different Haskell modules. The description is an arbitrary nullary type constructor.

For the sake of printing, the description is required to be the instance of Show. One must make sure that the show functions does not examine the value, as descr is purely phantom. Here's an example of the good Label description:

    data MyLabelDescr; instance Show MyLabelDescr where show _ = "descr"

which are automated by makeLabels3 from Data.HList.MakeLabel.

This model even allows the labels in a record to belong to different namespaces. To this end, the model employs the predicate for type equality.

Synopsis

Documentation

>>> let label3 = Label :: Label (Lbl HZero () ())
>>> let label6 = Label :: Label "6"

data Lbl (x :: HNat) (ns :: *) (desc :: *) Source #

Instances

Instances details
(HEqBy HLeFn n m b, ns ~ ns') => HEqBy HLeFn (Lbl n ns desc :: Type) (Lbl m ns' desc' :: Type) b Source #

Data.HList.Label3 labels can only be compared if they belong to the same namespace.

Instance details

Defined in Data.HList.HSort

Label t ~ Label (Lbl ix ns n) => SameLabels (Label t :: Type) (Lbl ix ns n :: Type) Source # 
Instance details

Defined in Data.HList.Label3

Show desc => ShowLabel (Lbl x ns desc :: Type) Source #

Equality on labels (descriptions are ignored) Use generic instance

Show label

Instance details

Defined in Data.HList.Label3

Methods

showLabel :: Label (Lbl x ns desc) -> String Source #

Show desc => Show (Label (Lbl x ns desc)) Source # 
Instance details

Defined in Data.HList.Label3

Methods

showsPrec :: Int -> Label (Lbl x ns desc) -> ShowS #

show :: Label (Lbl x ns desc) -> String #

showList :: [Label (Lbl x ns desc)] -> ShowS #

(to ~ LabeledTo x, ToSym (to p q) x) => HExtend (to p q) (Proxy (Lbl n ns desc ': xs)) Source #

if the proxy has Data.HList.Label3.Lbl, then everything has to be wrapped in Label to make the kinds match up.

Instance details

Defined in Data.HList.Labelable

Associated Types

type HExtendR (to p q) (Proxy (Lbl n ns desc ': xs)) Source #

Methods

(.*.) :: to p q -> Proxy (Lbl n ns desc ': xs) -> HExtendR (to p q) (Proxy (Lbl n ns desc ': xs)) Source #

HExtend (Label (Lbl n ns desc)) (Proxy (x ': xs)) Source #

Mixing two label kinds means we have to include Label:

>>> let r = label3 .*. label6 .*. emptyProxy
>>> :t r
r :: Proxy '[Label (Lbl 'HZero () ()), Label "6"]
Instance details

Defined in Data.HList.Label3

Associated Types

type HExtendR (Label (Lbl n ns desc)) (Proxy (x ': xs)) Source #

Methods

(.*.) :: Label (Lbl n ns desc) -> Proxy (x ': xs) -> HExtendR (Label (Lbl n ns desc)) (Proxy (x ': xs)) Source #

HExtend (Label (Lbl n ns desc)) (Proxy (Lbl n' ns' desc' ': xs)) Source #

If possible, Label is left off:

>>> let q = label3 .*. label3 .*. emptyProxy
>>> :t q
q :: Proxy '[Lbl 'HZero () (), Lbl 'HZero () ()]
Instance details

Defined in Data.HList.Label3

Associated Types

type HExtendR (Label (Lbl n ns desc)) (Proxy (Lbl n' ns' desc' ': xs)) Source #

Methods

(.*.) :: Label (Lbl n ns desc) -> Proxy (Lbl n' ns' desc' ': xs) -> HExtendR (Label (Lbl n ns desc)) (Proxy (Lbl n' ns' desc' ': xs)) Source #

type ZipTagged (Lbl ix ns n ': ts :: [Type]) (v ': vs) Source # 
Instance details

Defined in Data.HList.Label3

type ZipTagged (Lbl ix ns n ': ts :: [Type]) (v ': vs) = Tagged (Lbl ix ns n) v ': ZipTagged ts vs
type HExtendR (to p q) (Proxy (Lbl n ns desc ': xs)) Source # 
Instance details

Defined in Data.HList.Labelable

type HExtendR (to p q) (Proxy (Lbl n ns desc ': xs))
type HExtendR (Label (Lbl n ns desc)) (Proxy (Lbl n' ns' desc' ': xs)) Source # 
Instance details

Defined in Data.HList.Label3

type HExtendR (Label (Lbl n ns desc)) (Proxy (Lbl n' ns' desc' ': xs)) = Proxy (Lbl n ns desc ': (Lbl n' ns' desc' ': xs))
type HExtendR (Label (Lbl n ns desc)) (Proxy (x ': xs)) Source # 
Instance details

Defined in Data.HList.Label3

type HExtendR (Label (Lbl n ns desc)) (Proxy (x ': xs)) = Proxy (Label (Lbl n ns desc) ': MapLabel (x ': xs))

Public constructors for labels

firstLabel :: ns -> desc -> Label (Lbl HZero ns desc) Source #

Construct the first label

nextLabel :: Label (Lbl x ns desc) -> desc' -> Label (Lbl (HSucc x) ns desc') Source #

Construct the next label

type family MapLabel (xs :: [k]) :: [*] Source #

similar to Data.HList.Record.Labels1, but avoids producing Label (Label x)

Instances

Instances details
type MapLabel ('[] :: [k]) Source # 
Instance details

Defined in Data.HList.Label3

type MapLabel ('[] :: [k]) = '[] :: [Type]
type MapLabel (x ': xs :: [k]) Source # 
Instance details

Defined in Data.HList.Label3

type MapLabel (x ': xs :: [k]) = AddLabel x ': MapLabel xs

type family AddLabel (x :: k) :: * where ... Source #

Equations

AddLabel (Label x) = Label x 
AddLabel x = Label x 

Orphan instances

HExtend (Label y) (Proxy (x ': xs)) Source # 
Instance details

Associated Types

type HExtendR (Label y) (Proxy (x ': xs)) Source #

Methods

(.*.) :: Label y -> Proxy (x ': xs) -> HExtendR (Label y) (Proxy (x ': xs)) Source #

HExtend (Label y) (Proxy (x ': xs)) Source # 
Instance details

Associated Types

type HExtendR (Label y) (Proxy (x ': xs)) Source #

Methods

(.*.) :: Label y -> Proxy (x ': xs) -> HExtendR (Label y) (Proxy (x ': xs)) Source #

HExtend (Label y) (Proxy (x ': xs)) Source # 
Instance details

Associated Types

type HExtendR (Label y) (Proxy (x ': xs)) Source #

Methods

(.*.) :: Label y -> Proxy (x ': xs) -> HExtendR (Label y) (Proxy (x ': xs)) Source #

HExtend (Label y) (Proxy (x ': xs)) Source #

Mixing two label kinds means we have to include Label:

>>> let s = label6 .*. label3 .*. emptyProxy
>>> :t s
s :: Proxy '[Label "6", Label (Lbl 'HZero () ())]
Instance details

Associated Types

type HExtendR (Label y) (Proxy (x ': xs)) Source #

Methods

(.*.) :: Label y -> Proxy (x ': xs) -> HExtendR (Label y) (Proxy (x ': xs)) Source #