HList-0.5.1.0: Heterogeneous lists
Safe HaskellNone
LanguageHaskell2010

Data.HList.RecordPuns

Description

 
Synopsis

Documentation

>>> :set -XQuasiQuotes -XViewPatterns
patterns
>>> let y = Label :: Label "y"
>>> let x = Label :: Label "x"
>>> [pun| x y |] <- return (x .=. 3 .*. y .=. "hi" .*. emptyRecord)
>>> print (x,y)
(3,"hi")
expressions

Compare with the standard way to construct records above

>>> let x = 3; y = "hi"
>>> [pun|x y|]
Record{x=3,y="hi"}
nesting

Nesting is supported. Variables inside { } and ( ) are one level deeper, like the built-in syntax. Furthermore the outer { } can be left out because [pun|{x}|] is more cluttered than [pun|x|]. More concretely the pattern:

let [pun| ab@{ a b } y z c{d} |] = x

is short for:

let ab = x.ab
    a = x.ab.a
    b = x.ab.b
    y = x.y
    z = x.z
    -- c is not bound
    d = x.c.d

Where here . is a left-associative field lookup (as it is in other languages).

The pun quasiquoter can also be used in an expression context:

let mkX ab a b y z d = [pun| ab@{ a b } y z c{d} |]
    x = mkX ab b y z d

Here mkX includes ab a b y z d. ab needs to be a record, and if it has fields called a or b they are overridden by the values of a and b (via hLeftUnion = .<++.) . In other words,

let mkX ab_ a b y z d = let ab = [pun| a b |] .<++. ab_
                              in [pun| ab y z c{d} |]

For patterns, any order and additional fields are allowed if { } is used, just as in built-in record syntax. But it is often necessary to restrict the order and number of fields, such as if the record is a hRearrange of a hLeftUnion. So use ( ) instead:

let [pun| (x _ y{}) |] = list
-- desugars to something like:
Record ((Tagged x :: Tagged "x" s1) `HCons`
        (Tagged _ :: Tagged t   s2) `HCons`
        (Tagged _ :: Tagged "y" s3) `HCons`
         HNil) = list

Note that this also introduces the familiar wild card pattern (_), and shows again how to ensure a label is present but not bind a variable to it.

For comparison, here are three equivalent ways to define variables x and y

let [pun| x y{} |] = r
let [pun|{ x y{} }|] = r -- or this
let x = r .!. (Label :: Label "x")
    y = constrainType (r .!. (Label :: Label "y"))
    constrainType :: Record t -> Record t
    constrainType = id

See also examples/pun.hs. In {} patterns, pun can work with Variant too.

pun :: QuasiQuoter Source #

requires labels to be promoted strings (kind Symbol), as provided by Data.HList.Label6 (ie. the label for foo is Label :: Label "foo"), or Data.HList.Labelable