Since everyone else is speaking out about records I'll throw in something about my efforts. I'll also throw in some commentary about the various issues involved as I go. Although I was responsible for the implementation, others made valuable contributions to the design. Warren Burton, Mark Jones, and Randy Hudson all contributed to this work. >From the start, there are two basic ways to go: either expand the type system to support extensible records directly (as Mark Jones and Barney Hilken have discussed) or to simply layer records on top of the existing type system. For the sake of simplicity, I have chosen the latter approach. Syntax Syntactic issues are always difficult to address since they are often issues of taste and style. We have derived our syntax from similar Haskell constructs. Since records are similar to tuples, we chose to use (label = value, ...) style syntax in both the expression language and the pattern language. A very important issue is how to manage the namespace of labels. In general, there is no agreement on this issue among language designers so this should will certainly merit further debate. We have chosen to place labels in the namespace of values. The primary reason for this is that we use these names as selector functions. This avoids using a special syntax for record selection (`foo x' instead of `x.foo' or '#foo x' or ...). We feel this is more in the Haskell style of having a minimum of extra syntax and using function application whenever possible. (On the other hand, this means that you have to use more verbose labels - labeling a field `x' isn't a good idea). The syntax of a record declaration itself is also borrowed from another Haskell construct. Class declarations are quite similar to records: they give a name to a set of components, each of which has a type and maybe a default value. Also, classes allow inheritance via super-classes. Hence, we declare records (we use the word `structure' instead of record, mainly to avoid being connected with true extensible records) like this: structure Foo where fooX , fooY :: Int With inheritance and defaults: structure Foo => ColoredFoo where fooColor :: Color fooColor = const Green -- a default value for the color Finally, the other big syntactic issue is whether to perform some sort of name mangling to create functions derived from the basic label names or to use special syntactic settings of existing names. For example, a function which changes the `fooX' component of a `Foo' structure could be named `changeFooX' and this name would be created by the declaration of Foo, or we could use some special syntax, such as `(fooX=)', in which only the original label is named. We have chosen the latter approach. Type Issues and Inheritance Without inheritance, records are essentially sugarings for ordinary algebraic data types. Adding inheritance makes records far more useful but leads to problems with the type system. While we have stopped short of full extensible records, type classes supply most of the expressiveness we need. One difference between this work and other approaches is that we attach typings to the labels. That is, each label is declared in a structure declaration with a fixed type. A more ML style could be achieved by simply assigning each label type `a'. Our implementation is more in the spirit of object-oriented programming in which these labels name structure components. We use record (structure) names as type qualifiers rather than label names. To avoid any special syntax we use structure names directly as classes. Thus, with respect to the previous structure declaration, f x = fooX x would have the type f :: Foo a => a -> Int So instead of labels (structure component names) appearing as qualifiers, we package up all the labels for a structure into a single qualifier, the structure name. Also, the structure name serves as an ordinary type name in signatures and instance declaration. The only problem with using the underlying type class system to implement records is inheriting from a polymorphic structure is not generally possible, even with constructor classes. For example, in structure S1 a where s1 :: a structure S1 a => S2 a b where s2 :: b we generate code something like: data S1 a = S1 a -- A data type for S1 class S1 t where -- A class for all types which contain S1 s1 :: t a -> a -- This uses constructor classes instance S1(S1) where s1 (S1 x) = x data S2 a b = S2 a b class S2 t where s2 :: t a b -> b instance S1(S2 ? b) where -- Not legal; we need the type \a -> S2 a b s1 (S1 x y) = x This doesn't work because constructor classes supply only one way to decompose a type, based on the currying of type application. While this can be fixed by changing the type system, we have not done so. For non-polymorphic inheritance, there is no problem. This problem is certainly solvable - extensible record types are one such solution. Other Aspects of Records There is a lot more to a good implementation of records. Allowing default values for fields in a record is crucial to good software engineering - this allows a new field to be added without having to explicitly change every place where a the structure is created. We also deal with undefined slots in structures, type coercion of structures, and structure updating. Structure updating is quite useful - we use labeled tuple syntax to accomplish this: (fooX = 2) is a function which (non-destructively) changes the value of the fooX component to 2. We also derive special Text functions for reading and printing structures using structure syntax. The paper describing our record system is almost ready - I'll announce once it's complete. Almost everything is implemented and will be in the next release of Yale Haskell which should be ready for release in a couple of weeks. John Peterson Yale Haskell Project