Now that I have a version of ghc with type classes, I have had a go at implementing records based on the ideas I mentioned on this list a few months ago. The code of my first attempt is available at http:// homepage.ntlworld.com/b.hilken/files/Records.hs

I am releasing this to get feedback. I think Haskell needs a records system of this kind of generality, and this code at least allows you to play around.

From the comment section of the file:
-----------------------

    Record construction:

        EmptyRec        is the empty record.
N =: x is the record with one field labelled N carrying data x. t +: u is the union of records t and u. Any overlap of labels gives a static error.

    Record destruction:

t .: N is the value of field N in record t. A lack of field N gives a static error. t -: N is record t with field N deleted. A lack of field N gives a static error.

    Record update:

t |: u is the record with fields from u where it has them, t otherwise. If u has any fields not in t, or of different types from t, there is a static error.
                        Note that the result has the same type as t.

    All these records have types:

        EmptyRec        is the type of the empty record.
N :=: a is the type of a record with one field labelled N carrying data of type a. r :+: s is the union of record types r and s. Any overlap of labels gives a static error. r :.: N is the type of field N in a record of type r. A lack of field N gives a static error. r :-: N is record type r with field N deleted. A lack of field N gives a static error.

    Finally some classes to govern the polymorphism:

r `Contains` N means that r is a record type with a field labelled N. r `Disjoint` s means that r and s are record types with no fields in common. r `Subrecord` s means that r and s are record types, and every field of r also occurs in s (with the same type).

    The types of the basic operators are as follows:

        (=:) :: n -> a -> n :=: a
        (+:) :: r `Disjoint` s => r -> s -> r :+: s
        (.:) :: r `Contains` n => r -> n -> r :.: n
        (-:) :: r `Contains` n => r -> n -> r :-: n
        (|:) :: r `Subrecord` s => s -> r -> s

----------------------------------

Note that these records are a lot more expressive than the Hugs system, as you can not only extend records by adding fields, but also take unions of arbitrary (disjoint) records.

Record update is designed for functions with lots of named optional arguments. If you define

        f opts = ... options.:Optj ...
                where
                options = (Opt1 =: val1 +: ... +: Optn =: valn) |: opts

then the user can write (for example):

        f (Optk =: u +: Optl =: v)

to set just two of the options, leaving the rest as default. This also cannot be done in the Hugs system.


The main disadvantage of the current implementation is that you have to tell the compiler in which order to store the fields, by defining one of the following:

   type instance NameCmp N M = NameLT
   type instance NameCmp N N = NameEQ
   type instance NameCmp N M = NameGT

for each pair of labels N & M in such a way as to give a linear order on labels. You need n^2 definitions, where n is the number of labels. I would do this in Template Haskell, but it won't yet allow you to declare type instances. Maybe some compiler support?

Error messages tend to be cryptic. They mostly complain of missing instances, and can run to several pages. There is really no way to improve this without building it all in to the compiler!


All comments gratefully received, including suggestions on syntax, choice of operators, implementation, explanation, etc.


Barney.


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

Reply via email to