Yes, I have unreleased (yet) TH code for generating globally unique
labels, and lifting records.... you can do:

$(ttypelift [| data Record = Record {
   field1 :: Int,
   field2 :: String } |] )

and it lifts this to an HList style record with labels

field1
field2

Labels are assigned unique type level values by converting the
string of the label name to a numeric value which is encoded by
type level natural numbers.

   Keean.


Benjamin Franksen wrote:

I think that the best solution is to define record labels as types, or rather type proxies, like for instance in the HList library. This fixes the most important deficiencies of Haskell98 records:

- labels are now first class values
- labels no longer need to be globally unique, but only unique per record
- operations to get or set a field are normal (overloaded) functions (and
 can be given operator aliases, if desired)

This library class defines the operations on a record:

        class RecordField r l t | r l -> t where
          getField :: l -> r -> t
          putField :: l -> t -> r -> r

        updateField :: (Field r l t) => l -> (t -> t) -> r -> r
        updateField lbl fun rec = putField lbl (fun $ getField lbl rec) rec

The record declaration

        data R = R {
            field1 :: T1,
            field2 :: T2
          }

would be syntactic sugar for

        data R = R T1 T2

        data Label_field1

        field1 :: Label_field1
        field1 = undefined

        instance RecordField R Label_field1 T1 where
          getField (Rec x _) _ = x
          putField (Rec _ y) _ v = Rec v x

        -- analogous definitions for field2 left out

Note that the compiler would leave out the definition of Label_field1 and field1 if these are already in scope.

Alexanders example



fun rec = rec // $(u field1 fn) . $(a field2 val)



resp.



fun rec = rec // u_field1 fn . a_field2 val



could now be written thus

        fun = updateField field1 fn . putField field2 val

without any need for additional syntax or infix operator splices.

I wonder if something similar could be done with TH. The labels would need to have a different name (e.g. l_field1, l_field2), so they don't collide with their Haskell98 definitions, but otherwise everything should be as above. I am thinking of something like

        $(generateLabels R)

(I am not very familiar with TH, so this could be wrong syntax or otherwise impossible to do.)

Ben
_______________________________________________
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell



_______________________________________________ Haskell mailing list Haskell@haskell.org http://www.haskell.org/mailman/listinfo/haskell

Reply via email to