Records in Haskell - updating Higher-Ranked fields

AntC anthony_clayden at clear.net.nz
Wed Mar 28 02:18:33 CEST 2012


Gábor Lehel <illissius <at> gmail.com> writes:
> 
> ..., but DORF actually requires less type system magic than
> SORF, and also already has a working prototype implementation, ...
> 
> ... My main complaint against DORF is
> that having to write fieldLabel declarations for every field you want
> to use is onerous. ...
> 

    (Here's a possible way to reduce the need for declarations,
     for non-sharing fields; also avoid the fieldLabel new decl.)

SPJ introduced some fancy type-handling for higher-ranked fields. But still it 
only helped in accessing a H-R field, not updating it.

If we accept that updating H-R fields in liberated-namespace records is not 
possible, can we simplify the implementation? I think so. Here's what I'd call 
a well-principled work-round (not a hack, but then neither a solution).

(I'm showing it in DORF-like style, but I think it would work equally in SORF 
style with Stringy Kinds. The advantage of showing DORF is that we can try it -
- which I've done.)

You write:
    data HR = HR{ objectId :: ObjectId              -- type Pun
                , rev :: forall a. [a] -> [a] }     -- SPJ's example
             sharing (ObjectId) deriving (...)      -- new syntax
         -- this decl is not sharing `rev`, so no further code needed

         -- HR is sharing objectId, so you need a field Label in scope:
         -- probably you're already declaring newtypes/data
    newtype ObjectId = ObjectId Int                 -- declaring a field
          deriving (Has, ... )                      -- `Has` makes it a label

Field access can be polymorphic:
    f :: HR -> ([Bool], [Char])
    f r = (r.rev [True], r.rev "hello")

Record update looks like:
            ... myHR{ rev = Rev reverse } ...       -- annoying pun
But perhaps we could support sugar for it:
            ... myHR{ Rev reverse } ...             -- fewer keystrokes!

The HR decl desugars to:
    newtype Rev = Rev (forall a. [a] -> [a])        -- newtype punning
    data HR = HR{ objectId :: ObjectId, rev :: Rev }
    rev :: HR -> (forall a. [a] -> [a])             -- monotype field selector
    rev r = let (Rev fn) = get r (undefined :: Rev) in fn
    instance Has HR Rev        where
        get HR{ rev } _ = rev                       -- have to wrap the fn
        set (Rev fn) HR{ .. } = HR{ rev = (Rev fn) }
    type instance FieldTy HR Rev = Rev              -- have to wrap this
                                                    -- else update don't work

So I've simplified `Has` to two type arguments (like the more naieve form SPJ 
considers then rejects). And used the field's type itself as the index (so 
that we're punning on the field name):
    class Has r fld       where
        get :: r -> fld -> FieldTy r fld
        set :: fld -> r -> SetTy r fld              -- for type change update

For the record type's `sharing` fields we desugar to:
    instance Has HR ObjectId   where
        get HR{ objectId } _ = objectId             -- yeah dull, dull
        set x HR{ .. }       = HR{ objectId = x, .. }

and the `deriving (Has)` on the newtype or data desugars to:
    objectId :: {Has r ObjectId} => r -> ObjectId   -- overloaded record 
    objectId r = get r (undefined :: ObjectId)      --         selector
    type instance FieldTy r ObjectId = ObjectId     -- not parametric

AntC




More information about the Glasgow-haskell-users mailing list