Extensible Records

Claus Reinke claus.reinke at talk21.com
Sun Nov 11 10:53:12 EST 2007


>Whatever system GHC settles on  
> is almost certain to become part of the Haskell standard, and this  
> particular system has some deep limitations which could not be got  
> round without ripping it all out and starting again.

i'd like to have "extensible records", but i'd rather like to decompose
this complex language feature into its components, and then have
better support for each of those components, which will be simpler,
could be combined to support different record system variants, and 
are likely to have other applications.

in light of this, what library-based record proposals have to offer
are light-weight case studies of useability and feature composition.

once we know which kind of record system we want, we can then
think about which parts of it need better language and implementation
support. even before we converge on any specific system, there
might be features that are shared by all contending proposals.

some time ago (was that really 2 years? trac claims it was), i 
suggested that any record system with first-class labels needs
language support for type sharing: if i import modules A and B,
each of which introduces a record-label X, i need some way of
telling the type system that A.X ~ B.X (Trex solved that problem
by not requiring label declarations at all, but Trex labels weren't
first-class objects, either).

i made a haskell prime ticket for it (which was duly classified
as "maybe" and then ignored;-), to which i also attached an
implementation of records that, in contrast to other record
libraries, does not depend on label ordering, as an illustration:

    http://hackage.haskell.org/trac/haskell-prime/ticket/92
    http://hackage.haskell.org/trac/haskell-prime/attachment/ticket/92/Data.Record.hs

the code was inspired by Daan's system, i think, because not
removing label overlap made the type class hacking a lot easier,
but went slightly beyond in supporting record concatenation

(i've been waiting for type functions to support overlap
resolution, so that i can port the code; the fact that this is
still future work supports the argument that haskell'2006
should have appeared with a functional dependencies
addendum instead of waiting for better things to happen?-):

   poor man's records using nested tuples and declared labels:

   apart from record extension (,), we've got field selection (#?), 
   field removal (#-), field update (#!), field renaming (#@),
   symmetric record concatenation (##), .. anything missing?

   see main at the bottom for examples of use.

   submitted to support proposal for first class labels in Haskell'.

   Claus Reinke, February 2006

i just downloaded the old Data.Record code and it still loads
and runs in a recent ghc head, giving examples of all operations
(these days, one might want to clean up the syntax with some 
infix constructors, but at the time i was still hoping to get it to 
work in hugs as well..):

    *Data.Record> main
    
    records
    
    r1 : ((A,True),((B,'a'),((C,1),())))
    r2 : ((A,False),((B,'b'),((C,2),((A,True),((B,'a'),((C,1),()))))))
    r3 : ((D,"hi there"),((B,["who's calling"]),()))
    
    symmetric record concatenation
    
    r4a = r1 ## r3:
            ((A,True),((B,'a'),((C,1),((D,"hi there"),((B,["who's calling"]),())))))
    r4b = r3 ## r1:
            ((D,"hi there"),((B,["who's calling"]),((A,True),((B,'a'),((C,1),())))))
    
    record selection
    
    
    x1 r = (r #? B, r #? C, r #? A)
    
    x1 r1: ('a',1,True)
    x1 r2: ('b',2,False)
    x1 r4a: ('a',1,True)
    x1 r4b: (["who's calling"],1,True)
    
    x2 r = (r #? B, r #? D)
    
    x2 r4a: ('a',"hi there")
    x2 r4b: (["who's calling"],"hi there")
    
    record field removal
    
    
    x3 r = r #- D #- B
    
    x3 r1: ((A,True),((C,1),()))
    x3 r2: ((A,False),((C,2),((A,True),((B,'a'),((C,1),())))))
    x3 r3: ()
    x3 r4a: ((A,True),((C,1),((B,["who's calling"]),())))
    x3 r4b: ((A,True),((B,'a'),((C,1),())))
    
    record field update
    
    
    (r2 #! B) "dingbats":
            ((B,"dingbats"),((A,False),((C,2),((A,True),((B,'a'),((C,1),()))))))
    
    record field renaming
    
    
    (r2 #@ D) C:
            ((D,2),((A,False),((B,'b'),((A,True),((B,'a'),((C,1),()))))))

> > f opts x = let vals = {Opt1 =: default1, ... } |: opts in
> > ... vals ... x ...
> 
> where '{Opt1 =: default1, ... }' is some fixed record of default  
> values, and '|:' is record overwrite. The type of f should be
> 
> > f :: (a `Subrecord` {Opt1 :=: t1, ...}) => a -> b -> c

in Hugs' Trex that would be:

Hugs.Trex> :t let f opts x = (opt1="default"|opts) in f
let {...} in f :: a\opt1 => Rec a -> b -> Rec (opt1 :: [Char] | a)

but that still doesn't give you things like record concatenation.
in principle, the record-concatenation-for-free trick works with
Trex, but it falls apart if you need to define type classes involving
record types. because then you need to be specific about the
types, making those labels explicit. (btw, what is "Flex-like"?)

claus



More information about the Glasgow-haskell-users mailing list