
Hello, Records in Haskell are somewhat of a contentious issue and many proposals have been put forth to address the shortcomings of the current record system [1]. Below, I introduce a small library relying on several GHC extensions, crucially Implicit Parameters and Constraint Kinds, which implements an extensible record system. While by no means production-ready, it is remarkably close to how I think an extensible record system should function. Record access is very convenient (reminiscent of Pascal's with statement), while record update is somewhat cumbersome (but could potentially be improved using Template Haskell). Two caveats: * Type inference for records does not work, so type signatures have to be provided. * When more than one binding for an implicit parameter is in scope, it is not always clear which one takes precedence. However, I think it is safe to assume that if the innermost binding is a let/where binding, it will carry the day. In all other cases, it is probably safest to rely on explicit type signatures to resolve the ambiguity.
{-# LANGUAGE ImplicitParams #-} {-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE RankNTypes #-}
The record type is simply the dictionary type, which is more commonly used to reify type class dictionaries. Here, we use it to record a number of implicit parameter bindings, i.e. if implicit parameters of types `fields' are in scope, then the data constructor `Rec' will create a dictionary from them, provided an appropriate type signature is given.
data Record fields where Rec :: fields => Record fields
The `?' operator will bring the implicit parameter bindings previously captured by `Rec' into scope.
infixr 1 ? (?) :: Record fields -> (fields => r) -> r Rec ? e = e
This is the complete library. Examples follow below. ======================================================================== Type synonyms to replace the awkward syntax for implicit parameter constraints.
type X a = ?x::a type Y a = ?y::a type Z a = ?z::a
As a first example, construct a record with fields ?x and ?y, both of type Int.
xy :: Record (X Int, Y Int) xy = let ?x = 1; ?y = 2 in Rec
To access the fields of the record, we can use the `?' operator. Expressions involving any of the fields can appear to the right of the operator. * xy ? ?x ==> 1 * xy ? ?x + ?y ==> 3 The next example illustrates record update
xy' :: Record (X Int, Y Int) xy' = xy ? let ?y = -2 in Rec
* xy' ? ?y ==> -2 Type signatures are required, but can be placed directly after `Rec'.
xz = let ?x = -1; ?z = 3 in Rec :: Record (X Int, Z Int)
Record Restriction
y :: Record (Y Int) y = xy ? Rec
We can combine records as follows, but the result may be implementation- dependent if both records share fields.
xyz, xyz' :: Record (X Int, Y Int, Z Int) xyz = xz ? xy ? Rec
* xyz ? ?x ==> -1 So it is probably better to disambiguate.
xyz' = xz ? y ? Rec
* xyz' ? ?x ==> -1 ======================================================================== As an application, we use records to build a rudimentary object system. A class is a record which can access its own fields, which are supplied as an argument.
type Class fields = Record fields -> Record fields
Originally I tried the type 'fields => Record fields', which leads to problems when tying the knot. Given a class, we can get a record for property and method access by using a fixed point combinator.
runClass :: Class fields -> Record fields runClass inst = inst (runClass inst)
Type signatures for our next example.
type N = ?n::Int type AbstractFact = (?fact::Int, ?factHelper::Int -> Int -> Int) type ConcreteFact = (AbstractFact, N)
This is an abstract class that computes the factorial of its abstract property `?n'. Notice how `?n' is not included in the function's return type.
abstractFact :: Record ConcreteFact -> Record AbstractFact abstractFact r = Rec where ?fact = r ? ?factHelper 1 ?n ?factHelper = r ? \p k -> if k == 1 then p else ?factHelper (p*k) (k-1)
It is important that `r' only be opened inside the definitions of the methods, otherwise `runClass' will cause an infinite loop. To go from an abstract class to a concrete class, all we need to do is provide the missing property.
concreteFact :: Int -> Class ConcreteFact concreteFact n r = abstractFact r ? let ?n = n in Rec
Quick sanity check
testFact :: Class ConcreteFact testFact = concreteFact 10
* runClass testFact ? ?fact ==> 3628800 Example of overloading.
overrideFact :: Class ConcreteFact overrideFact r = testFact r ? let ?fact = fact in Rec where fact = r ? product [1.. ?n]
It is tempting to use the following definition overrideFact r = testFact r ? let ?fact = product [1.. ?n] in Rec However, this will use `?n' from the current environment and not respond to `?n' being overridden in a subclass. The final example concerns multiple inheritance. We first define a class for computing Fibonacci numbers, similar to the one for the factorial above.
type Fib = (?fib::Int, N)
fib :: Int -> Class Fib fib n r = Rec where ?n = n ?fib = let fibs = 0:zipWith (+) fibs (1:fibs) in r ? fibs !! ?n
A multiple-inheritance combinator
diamond :: Class c1 -> Class c2 -> Class (c1,c2) diamond c1 c2 r = c1 (r ? Rec) ? c2 (r ? Rec) ? Rec
testFactFib :: Class (ConcreteFact, Fib) testFactFib = diamond testFact (fib 5)
This is C++-style inheritance: We now have two copies of the field `?n'. * runClass testFactFib ? ?fact ==> 3628800 * runClass testFactFib ? ?fib ==> 5 However, if we were to update `?n' in a subclass, both the factorial and the Fibonacci class would both use the new value. Alternatively, we can force the class to use a single value for `?n' by making sure `?n' only occurs once in the list of fields, but it's anyone's guess which value GHC will pick for `?n'.
testFactFib' :: Class (AbstractFact, Fib) testFactFib' r = testFactFib (r ? Rec) ? Rec
* runClass testFactFib' ? ?fact ==> 120 * runClass testFactFib' ? ?fib ==> 5 Thomas [1] http://hackage.haskell.org/trac/ghc/wiki/Records