generic-labels-0.1.0.1: Generically extract and replace collections of record fields
Safe HaskellNone
LanguageHaskell2010

Data.Label

Description

This module provides syntax for labelling values with symbolic field names.

Given val :: a , we can specify a label by using the syntax #field := val , which has type "field" := a .

For instance, we can pass a record of three arguments with the syntax:

myRecord :: ( "field1" := Int, "field2" := Bool, "field3" := Float )
myRecord = ( field2 := True, #field3 := 7.7 )

This is a simple triple of labelled types, so the order matters.

However, this library provides functionality which will automatically handle re-ordering fields when needed, see Data.Generic.Labels.

Synopsis

Documentation

newtype (lbl :: Symbol) := (a :: Type) infix 1 Source #

A type with a Label.

With OverloadedLabels:

 ( #bar := Just c ) :: ( "bar" := Maybe Char )

Constructors

Labelled 

Fields

Bundled Patterns

pattern (:=) :: Label lbl -> a -> lbl := a infix 1

Add a Label to a type.

With OverloadedLabels:

 ( #bar := Just c ) :: ( "bar" := Maybe Char )

Instances

Instances details
GLens' (HasTotalLabelPSym lbl) (args :*: opts) all => GAdapt args opts (M1 m meta (Rec0 (lbl := all))) Source #

This instance is INCOHERENT because we assume that no type variable (say all0) will later be instantiated to a labelled type lbl := all.

The end result is that, when we have both a built-in Haskell record field name as well as an explicit label, we prioritise the built-in record field name over the label.

Instance details

Defined in Data.Generic.Labels.Internal

Methods

gAdapt :: args p -> opts p -> M1 m meta (Rec0 (lbl := all)) p Source #

(Generic args, Generic all, optFld ~ S1 ('MetaSel ('Just lbl) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 o), GAdapt (Rep args) optFld (Rep all)) => UncheckedAdapt args (lbl := o) all Source # 
Instance details

Defined in Data.Generic.Labels

Methods

uncheckedAdapt :: args -> (lbl := o) -> all Source #

(KnownSymbol lbl, Show a) => Show (lbl := a) Source # 
Instance details

Defined in Data.Label

Methods

showsPrec :: Int -> (lbl := a) -> ShowS #

show :: (lbl := a) -> String #

showList :: [lbl := a] -> ShowS #

(Generic opt, Generic all, argFld ~ S1 ('MetaSel ('Just lbl) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a), GAdapt argFld (Rep opt) (Rep all)) => UncheckedAdapt (lbl := a) opt all Source # 
Instance details

Defined in Data.Generic.Labels

Methods

uncheckedAdapt :: (lbl := a) -> opt -> all Source #

a ~ b => UncheckedAdapt (lbl := a) opt (lbl := b) Source # 
Instance details

Defined in Data.Generic.Labels

Methods

uncheckedAdapt :: (lbl := a) -> opt -> lbl := b Source #

(Generic all, argFld ~ S1 ('MetaSel ('Just lbl1) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a), optFld ~ S1 ('MetaSel ('Just lbl2) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 o), GAdapt argFld optFld (Rep all)) => UncheckedAdapt (lbl1 := a) (lbl2 := o) all Source # 
Instance details

Defined in Data.Generic.Labels

Methods

uncheckedAdapt :: (lbl1 := a) -> (lbl2 := o) -> all Source #

(a ~ b, o ~ b) => UncheckedAdapt (lbl := a) (lbl := o) (lbl := b) Source # 
Instance details

Defined in Data.Generic.Labels

Methods

uncheckedAdapt :: (lbl := a) -> (lbl := o) -> lbl := b Source #

data Label (lbl :: Symbol) Source #

Proxy-like label type, used to pass the label name at the type-level.

With OverloadedLabels:

 #foo :: Label "foo"

Constructors

Label 

Instances

Instances details
lbl' ~ lbl => IsLabel lbl (Label lbl') Source # 
Instance details

Defined in Data.Label

Methods

fromLabel :: Label lbl' #

KnownSymbol lbl => Show (Label lbl) Source # 
Instance details

Defined in Data.Label

Methods

showsPrec :: Int -> Label lbl -> ShowS #

show :: Label lbl -> String #

showList :: [Label lbl] -> ShowS #