http://hackage.haskell.org/trac/ghc/wiki/ExtensibleRecords

I'm happy to see a Wiki page to summarise and contrast different approaches; that seems like a constructive >thing to do. (Email discussions tend to evaporate and then be repeated.) A useful thing to do would be to >give a series of use-cases, or examples, showing the kinds of thing one would like to be able to do. Then you >can classify the approaches by what examples they can handle.

i've added a link to the current version of my Data.Record
(previously listed as "Poor Man's Records), which supports
just about all operations that have been mentioned so far,
including scoped labels, Has/Lacks, or the generalised
extension-safe operations and predicates Barney prefers.

and we still do not need the order on the field labels that
plagues most other extensible record libraries (i'm quite
amazed myself, and expect bug reports!-).

i've also added the three language and implementation
features i consider most important to make library-based
extensible records useable in practice (none of which
happen to be specific to records, btw;-).

in trying to be comprehensive (mostly to explore the
limitations of my approach), my code is not as simple
and clean as the type families version. i don't want to
duplicate the in-file comments on the wiki page for
maintenance reasons, but i append them below, for
the curious.

claus

{-
  poor man's extensible and concatenable records

  supporting both scoped and unique label records

    class Label label  | record field labels
    label := value     | record fields

  predicates:

    rec `Lacks` label  | lacks predicate: record lacks field label
    rA `Disjoint` rB   | record disjointness: records share no field labels

  scoped records operations:

    field :# rec       | record extension
    rec #? label       | field selection
    rec #- label       | field removal
   (rec #! label) val  | field update: update field label with value
   (rec #@ old) new    | field renaming: rename existing field label old to new
    recA ## recB       | symmetric record concatenation
    recA #^ recB       | left-biased record field type intersection
    recA #^^ recB      | left-biased record field label intersection
    recA #& recB       | record projection: for each recB field, select 
matching recA field

  other record operations:

    field !:# rec      | strict record extension: no duplicate field labels
    rec !#- label      | strict field removal: remove existing field label from 
rec
   (rec !#! label) val | strict field update: update existing field label with 
value
    recA !## recB      | symmetric disjoint record concatenation
    recA !#& recB      | strict record projection: permute recA to match recB

  types:

     class Label l where label :: l
     class Has label rec lbool | label rec -> lbool
     class Lacks rec label
     class Disjoint recA recB

     label :: (Label l) => l
     (:=) :: label -> value -> label := value

     (:#) :: field -> record -> field :# record
     (!:#) :: (Lacks rec label) => (label := val) -> rec -> (label := val) :# 
rec

     (#?) :: (Select label val rec) => rec -> label -> val

     (#-) :: (Remove label rec rec') => rec -> label -> rec'
     (!#-) :: (Has label rec LTrue, Remove label rec rec') => rec -> label -> 
rec'

     (#!) :: (Remove label rec rec') => rec -> label -> value -> (label := 
value) :# rec'
     (!#!) :: (Has label rec LTrue, Remove label rec rec')
           => rec -> label -> value -> (label := value) :# rec'

     (#@) :: (Remove label1 rec rec', Select label1 val rec)
          => rec -> label -> label1 -> (label := val) :# rec'

     (##) :: (Concat recA recB recAB) => recA -> recB -> recAB
     (!##) :: (recA `Disjoint` recB, Concat recA recB recAB) => recA -> recB -> 
recAB

     (#^) :: (Intersect recA recB recAB) => recA -> recB -> recAB
     (#^^) :: (Intersect' recA recB recAB) => recA -> recB -> recAB

     (#&) :: (Project recA recB) => recA -> recB -> recB
     (!#&) :: (Project' recA recB) => recA -> recB -> recB

  see main at the bottom for examples of use.

  please let me know of any practically relevant missing operations

  Claus Reinke

  February 2006:
    submitted to support proposal for first class labels in Haskell'

  November 2007:
   added many more operations and predicates, replaced pairs with
   symbolic constructors, added strict operations
-}

_______________________________________________
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

Reply via email to