thoughts on the record update problem

There are actually four problems with overloaded record update, not three as mentioned on the SORF page. This is an attempt to solve them. The SORF update mechanism. ------------------------------ SORF suggests adding a member set to the class Has which does the actual updating just as get does the selecting. So set :: Has r f t => t -> r -> r and r {n1 = x1, n2 = x2} is translated as set @ "n2" x2 (set @ "n1" x1) The Problems. ----------------- 1. It's not clear how to define set for virtual record selectors. For example, we might define data Complex = Complex {re :: Float, im :: Float} instance Has Complex "arg" Float where get r = atan2 r.im r.re but if we want to set "arg", what should be kept constant? The obvious answer is "mod", but we haven't even defined it, and there are plenty of cases where there is no obvious answer. 2. If the data type has one or more parameters, updates can change the type of the record. Set can never do this, because of its type. What is more, if several fields depend on the parameter, for example data Twice a = Twice {first :: a, second :: a} any update of "first" which changes the type must also update "second" at the same time to keep the type correct. No hacked version of set can do this. 3. The Haskel implementation of impredicative polymorphism (from the Boxy Types paper) isn't strong enough to cope with higher rank field types in instances of set. 4. The translation of multiple updates into multiple applications of set is not the same as the definition of updates in the Haskel report, where updates are simultaneous not sequential. This would be less efficient, and in the case of virtual record selectors, it wouldn't be equal, and is arguably incorrect. Point 3 could possibly be fixed by improving the strength of the type system, but SPJ says this is a hard problem, and no-one else seems ready to tackle it. Points 1, 2 & 4 suggest that any solution must deal not with individual fields but with sets of fields that can sensibly be updated together. The Proposed Solution. -------------------------- This is an extension to SORF. I don't know if the same approach could be applied to other label systems. 1. Introduce a new form of class declaration: class Rcls r where r {n1 :: t1, n2 :: t2} is translated as class (Has r n1 t1, Has r n2 t2) => Rcls r where setRcls :: t1 -> t2 -> r -> r setRcls is used internally but hidden from the user. 2. Instances of record classes can use a special form of default. So data Rec = Rec {n1 :: t1, n2 :: t2} instance Rcls Rec is translated as instance Rcls Rec where setRcls x1 y1 (Rec _ _) = Rec x1 y1 provided all the fields in the class occur in the data type with the correct types. In general, the definition of the update function is the same as the Haskel98 translation of update, solving problem 4. 3. The syntax of record updates must be changed to include the class: r {Rcls| n1 = x1, n2 = x2} is translated as setRcls x1 x2 r Updating a subset of the fields is allowed, so r {Rcls| n1 = x1} is translated as setRcls x1 (r.n2) r 4. Non default instances use the syntax: instance Rcls Rec where r {Rcls| n1 = x1, n2 = x2} = ...x1..x2.. which is translated as instance Rcls Rec where setRcls x1 y1 r = ...x1..x2.. in order to allow virtual selectors. This solves problem 1, because updates are grouped together in a meaningful way. An extended example is given below. 5. Record classes can have parameters, so class TwiceClass r where r a {first :: a, second :: a} data Twice a = Twice {first :: a, second :: a} instance TwiceClass Twice translates as class TwiceClass r where setTwiceClass :: a -> a -> r b -> r a data Twice a = Twice {first :: a, second :: a} instance TwiceClass Twice where setTwiceClass x y (Twice _ _) = Twice x y which allows updates to change the type correctly. This solves problem 2. 6. Problem 3 *almost* works. The translation of class HRClass r where r {rev :: forall a. [a] -> [a]} is class Has r "rev" (forall a. [a] -> [a]) => HRClass r where setHRClass :: (forall a.[a] -> [a]) -> r -> r which is fine as far as updating is concerned, but the context is not (currently) allowed by ghc. I have no idea whether allowing polymorphic types in contexts would be a hard problem for ghc or not. None of my attempted work-rounds have been entirely satisfactory, but I might have missed something. Comments ------------- 1. This makes the "special syntax for Has" pretty useless. When you have a set of labels you want to use together, you usually want to use update as well as selection, so it's better to define a record class, and use that. 2. The record classes can also be used for controlling the scope of polymorphic functions. For example, if you want to use a label "name" with the assumption that it refers to the name of a person, define a class class Person r where r {name :: String} and only create instances where the assumption is correct. Any functions polymorphic over the class Person can only be applied to instances you have declared. You can later use the same label for the name of a product class Product r where r {name :: String} but it's a different class with its own instances and the type checker will complain if you apply Person code to Product types. 3. It feels a bit odd to have the class which controls selection functions (Has) automatically defined, once for all, but the classes which control update functions must be defined by the programmer, and instances declared manually. However, I haven't found any way to make any kind of multiple Has class work. Example -------------- The following example illustrates some of the things that are possible with this approach. We want to represent complex numbers as pairs of Floats: data Complex1 = Complex1 {real :: Float, imag :: Float} in order to update records, we define a class: class Cartesian c where c {real :: Float, imag :: Float} instance Cartesian Complex1 but we also want to access complex numbers by modulus and argument, so we define virtual selectors: class Polar c where c {mod :: Float, arg :: Float} instance Has Complex1 "mod" Float where get (Complex1 x y) = sqrt (x * x + y * y) instance Has Complex1 "arg" Float where get (Complex1 x y) = atan2 y x instance Polar Complex1 where _ {Polar| mod = r, arg = th} = Complex1 (r * cos th) (r * sin th) Note that we can update x and y by {Cartesian| real = x, imag = y} or r and theta by {Polar| mod = r, arg = theta} but we cant mix them: there is no way to simultaneously update x and theta, unless we define a new class to do that. We can change the representation to cache mod and arg without changing the classes: data Complex2 = Complex2 {real :: Float, imag :: Float, mod :: Float, arg :: Float} now both update functions are virtual, though none of the selectors are: instance Cartesian Complex2 where _ {Cartesian| real = x, imag = y} = Complex2 x y (sqrt (x * x + y * y)) (atan2 y x) instance Polar Complex2 where _ {Polar| mod = r, arg = th} = Complex2 (r * cos th) (r * sin th) r th Alternatively, we might want to use whichever representation was last updated: data Complex3 = Complex3a {real :: Float, imag :: Float} | Complex3b {mod :: Float, arg :: Float} now everything is virtual: instance Has Complex3 "real" Float where get (Complex3a x y) = x get (Complex3b r th) = r * cos th instance Has Complex3 "imag" Float where get (Complex3a x y) = y get (Complex3b r th) = r * sin th instance Cartesian Complex3 where _ {Cartesian| real = x, imag = y} = Complex3a x y instance Has Complex3 "mod" Float where get (Complex3a x y) = sqrt (x * x + y * y) get (Complex3b r th) = r instance Has Complex3 "arg" Float where get (Complex3a x y) = atan2 y x get (Complex3b r th) = th instance Polar Complex3 where _ {Polar| mod = r, arg = th} = Complex3b r th Sorry this is so long! Barney.

Thanks so much for stepping up and attempting a solution at our big
problem, Barney!
I would ask everyone restrict their comments on this for now solely as
to figuring out whether it makes updates work. There has been a lively
debate about ideal details on a record implementation, but until
updates are solved it is all a moot point.
On Mon, Mar 5, 2012 at 10:36 AM, Barney Hilken
There are actually four problems with overloaded record update, not three as mentioned on the SORF page. This is an attempt to solve them.
The SORF update mechanism. ------------------------------
SORF suggests adding a member set to the class Has which does the actual updating just as get does the selecting. So
set :: Has r f t => t -> r -> r
and r {n1 = x1, n2 = x2} is translated as
set @ "n2" x2 (set @ "n1" x1)
The Problems. -----------------
1. It's not clear how to define set for virtual record selectors. For example, we might define
data Complex = Complex {re :: Float, im :: Float}
instance Has Complex "arg" Float where get r = atan2 r.im r.re
but if we want to set "arg", what should be kept constant? The obvious answer is "mod", but we haven't even defined it, and there are plenty of cases where there is no obvious answer.
2. If the data type has one or more parameters, updates can change the type of the record. Set can never do this, because of its type. What is more, if several fields depend on the parameter, for example
data Twice a = Twice {first :: a, second :: a}
any update of "first" which changes the type must also update "second" at the same time to keep the type correct. No hacked version of set can do this.
3. The Haskel implementation of impredicative polymorphism (from the Boxy Types paper) isn't strong enough to cope with higher rank field types in instances of set.
4. The translation of multiple updates into multiple applications of set is not the same as the definition of updates in the Haskel report, where updates are simultaneous not sequential. This would be less efficient, and in the case of virtual record selectors, it wouldn't be equal, and is arguably incorrect.
Point 3 could possibly be fixed by improving the strength of the type system, but SPJ says this is a hard problem, and no-one else seems ready to tackle it. Points 1, 2 & 4 suggest that any solution must deal not with individual fields but with sets of fields that can sensibly be updated together.
The Proposed Solution. --------------------------
This is an extension to SORF. I don't know if the same approach could be applied to other label systems.
1. Introduce a new form of class declaration:
class Rcls r where r {n1 :: t1, n2 :: t2}
is translated as
class (Has r n1 t1, Has r n2 t2) => Rcls r where setRcls :: t1 -> t2 -> r -> r
setRcls is used internally but hidden from the user.
2. Instances of record classes can use a special form of default. So
data Rec = Rec {n1 :: t1, n2 :: t2}
instance Rcls Rec
is translated as
instance Rcls Rec where setRcls x1 y1 (Rec _ _) = Rec x1 y1
provided all the fields in the class occur in the data type with the correct types. In general, the definition of the update function is the same as the Haskel98 translation of update, solving problem 4.
3. The syntax of record updates must be changed to include the class:
r {Rcls| n1 = x1, n2 = x2}
is translated as
setRcls x1 x2 r
Updating a subset of the fields is allowed, so
r {Rcls| n1 = x1}
is translated as
setRcls x1 (r.n2) r
4. Non default instances use the syntax:
instance Rcls Rec where r {Rcls| n1 = x1, n2 = x2} = ...x1..x2..
which is translated as
instance Rcls Rec where setRcls x1 y1 r = ...x1..x2..
in order to allow virtual selectors. This solves problem 1, because updates are grouped together in a meaningful way. An extended example is given below.
5. Record classes can have parameters, so
class TwiceClass r where r a {first :: a, second :: a} data Twice a = Twice {first :: a, second :: a} instance TwiceClass Twice
translates as
class TwiceClass r where setTwiceClass :: a -> a -> r b -> r a data Twice a = Twice {first :: a, second :: a} instance TwiceClass Twice where setTwiceClass x y (Twice _ _) = Twice x y
which allows updates to change the type correctly. This solves problem 2.
6. Problem 3 *almost* works. The translation of
class HRClass r where r {rev :: forall a. [a] -> [a]}
is
class Has r "rev" (forall a. [a] -> [a]) => HRClass r where setHRClass :: (forall a.[a] -> [a]) -> r -> r
which is fine as far as updating is concerned, but the context is not (currently) allowed by ghc. I have no idea whether allowing polymorphic types in contexts would be a hard problem for ghc or not. None of my attempted work-rounds have been entirely satisfactory, but I might have missed something.
Comments -------------
1. This makes the "special syntax for Has" pretty useless. When you have a set of labels you want to use together, you usually want to use update as well as selection, so it's better to define a record class, and use that.
2. The record classes can also be used for controlling the scope of polymorphic functions. For example, if you want to use a label "name" with the assumption that it refers to the name of a person, define a class
class Person r where r {name :: String}
and only create instances where the assumption is correct. Any functions polymorphic over the class Person can only be applied to instances you have declared. You can later use the same label for the name of a product
class Product r where r {name :: String}
but it's a different class with its own instances and the type checker will complain if you apply Person code to Product types.
3. It feels a bit odd to have the class which controls selection functions (Has) automatically defined, once for all, but the classes which control update functions must be defined by the programmer, and instances declared manually. However, I haven't found any way to make any kind of multiple Has class work.
Example --------------
The following example illustrates some of the things that are possible with this approach. We want to represent complex numbers as pairs of Floats:
data Complex1 = Complex1 {real :: Float, imag :: Float}
in order to update records, we define a class:
class Cartesian c where c {real :: Float, imag :: Float}
instance Cartesian Complex1
but we also want to access complex numbers by modulus and argument, so we define virtual selectors:
class Polar c where c {mod :: Float, arg :: Float}
instance Has Complex1 "mod" Float where get (Complex1 x y) = sqrt (x * x + y * y)
instance Has Complex1 "arg" Float where get (Complex1 x y) = atan2 y x
instance Polar Complex1 where _ {Polar| mod = r, arg = th} = Complex1 (r * cos th) (r * sin th)
Note that we can update x and y by {Cartesian| real = x, imag = y} or r and theta by {Polar| mod = r, arg = theta} but we cant mix them: there is no way to simultaneously update x and theta, unless we define a new class to do that.
We can change the representation to cache mod and arg without changing the classes:
data Complex2 = Complex2 {real :: Float, imag :: Float, mod :: Float, arg :: Float}
now both update functions are virtual, though none of the selectors are:
instance Cartesian Complex2 where _ {Cartesian| real = x, imag = y} = Complex2 x y (sqrt (x * x + y * y)) (atan2 y x)
instance Polar Complex2 where _ {Polar| mod = r, arg = th} = Complex2 (r * cos th) (r * sin th) r th
Alternatively, we might want to use whichever representation was last updated:
data Complex3 = Complex3a {real :: Float, imag :: Float} | Complex3b {mod :: Float, arg :: Float}
now everything is virtual:
instance Has Complex3 "real" Float where get (Complex3a x y) = x get (Complex3b r th) = r * cos th
instance Has Complex3 "imag" Float where get (Complex3a x y) = y get (Complex3b r th) = r * sin th
instance Cartesian Complex3 where _ {Cartesian| real = x, imag = y} = Complex3a x y
instance Has Complex3 "mod" Float where get (Complex3a x y) = sqrt (x * x + y * y) get (Complex3b r th) = r
instance Has Complex3 "arg" Float where get (Complex3a x y) = atan2 y x get (Complex3b r th) = th
instance Polar Complex3 where _ {Polar| mod = r, arg = th} = Complex3b r th
Sorry this is so long!
Barney.
_______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

This worries me:
3. The syntax of record updates must be changed to include the class:
r {Rcls| n1 = x1, n2 = x2}
And if I understand correctly this proposal is still uncertain on some
edge cases.
I think it is time to close down the records discussion on the mail
list and ask for an implementation
The implementer should use any means at their disposal, probably by
adding a new construct to the language. However, for now any new
constructs or other implementation details should be kept internal so
that we can maintain flexibility going forward.
A lot of smart people are expending a huge amount of mental effort
discussing how to shoehorn this problem into the existing Haskell
machinery and the fine details of the best way to do it even though
there is still no truly satisfactory solution. I would really like to
see this effort instead go into an implementation.
On Mon, Mar 5, 2012 at 10:59 AM, Greg Weber
Thanks so much for stepping up and attempting a solution at our big problem, Barney!
I would ask everyone restrict their comments on this for now solely as to figuring out whether it makes updates work. There has been a lively debate about ideal details on a record implementation, but until updates are solved it is all a moot point.
On Mon, Mar 5, 2012 at 10:36 AM, Barney Hilken
wrote: There are actually four problems with overloaded record update, not three as mentioned on the SORF page. This is an attempt to solve them.
The SORF update mechanism. ------------------------------
SORF suggests adding a member set to the class Has which does the actual updating just as get does the selecting. So
set :: Has r f t => t -> r -> r
and r {n1 = x1, n2 = x2} is translated as
set @ "n2" x2 (set @ "n1" x1)
The Problems. -----------------
1. It's not clear how to define set for virtual record selectors. For example, we might define
data Complex = Complex {re :: Float, im :: Float}
instance Has Complex "arg" Float where get r = atan2 r.im r.re
but if we want to set "arg", what should be kept constant? The obvious answer is "mod", but we haven't even defined it, and there are plenty of cases where there is no obvious answer.
2. If the data type has one or more parameters, updates can change the type of the record. Set can never do this, because of its type. What is more, if several fields depend on the parameter, for example
data Twice a = Twice {first :: a, second :: a}
any update of "first" which changes the type must also update "second" at the same time to keep the type correct. No hacked version of set can do this.
3. The Haskel implementation of impredicative polymorphism (from the Boxy Types paper) isn't strong enough to cope with higher rank field types in instances of set.
4. The translation of multiple updates into multiple applications of set is not the same as the definition of updates in the Haskel report, where updates are simultaneous not sequential. This would be less efficient, and in the case of virtual record selectors, it wouldn't be equal, and is arguably incorrect.
Point 3 could possibly be fixed by improving the strength of the type system, but SPJ says this is a hard problem, and no-one else seems ready to tackle it. Points 1, 2 & 4 suggest that any solution must deal not with individual fields but with sets of fields that can sensibly be updated together.
The Proposed Solution. --------------------------
This is an extension to SORF. I don't know if the same approach could be applied to other label systems.
1. Introduce a new form of class declaration:
class Rcls r where r {n1 :: t1, n2 :: t2}
is translated as
class (Has r n1 t1, Has r n2 t2) => Rcls r where setRcls :: t1 -> t2 -> r -> r
setRcls is used internally but hidden from the user.
2. Instances of record classes can use a special form of default. So
data Rec = Rec {n1 :: t1, n2 :: t2}
instance Rcls Rec
is translated as
instance Rcls Rec where setRcls x1 y1 (Rec _ _) = Rec x1 y1
provided all the fields in the class occur in the data type with the correct types. In general, the definition of the update function is the same as the Haskel98 translation of update, solving problem 4.
3. The syntax of record updates must be changed to include the class:
r {Rcls| n1 = x1, n2 = x2}
is translated as
setRcls x1 x2 r
Updating a subset of the fields is allowed, so
r {Rcls| n1 = x1}
is translated as
setRcls x1 (r.n2) r
4. Non default instances use the syntax:
instance Rcls Rec where r {Rcls| n1 = x1, n2 = x2} = ...x1..x2..
which is translated as
instance Rcls Rec where setRcls x1 y1 r = ...x1..x2..
in order to allow virtual selectors. This solves problem 1, because updates are grouped together in a meaningful way. An extended example is given below.
5. Record classes can have parameters, so
class TwiceClass r where r a {first :: a, second :: a} data Twice a = Twice {first :: a, second :: a} instance TwiceClass Twice
translates as
class TwiceClass r where setTwiceClass :: a -> a -> r b -> r a data Twice a = Twice {first :: a, second :: a} instance TwiceClass Twice where setTwiceClass x y (Twice _ _) = Twice x y
which allows updates to change the type correctly. This solves problem 2.
6. Problem 3 *almost* works. The translation of
class HRClass r where r {rev :: forall a. [a] -> [a]}
is
class Has r "rev" (forall a. [a] -> [a]) => HRClass r where setHRClass :: (forall a.[a] -> [a]) -> r -> r
which is fine as far as updating is concerned, but the context is not (currently) allowed by ghc. I have no idea whether allowing polymorphic types in contexts would be a hard problem for ghc or not. None of my attempted work-rounds have been entirely satisfactory, but I might have missed something.
Comments -------------
1. This makes the "special syntax for Has" pretty useless. When you have a set of labels you want to use together, you usually want to use update as well as selection, so it's better to define a record class, and use that.
2. The record classes can also be used for controlling the scope of polymorphic functions. For example, if you want to use a label "name" with the assumption that it refers to the name of a person, define a class
class Person r where r {name :: String}
and only create instances where the assumption is correct. Any functions polymorphic over the class Person can only be applied to instances you have declared. You can later use the same label for the name of a product
class Product r where r {name :: String}
but it's a different class with its own instances and the type checker will complain if you apply Person code to Product types.
3. It feels a bit odd to have the class which controls selection functions (Has) automatically defined, once for all, but the classes which control update functions must be defined by the programmer, and instances declared manually. However, I haven't found any way to make any kind of multiple Has class work.
Example --------------
The following example illustrates some of the things that are possible with this approach. We want to represent complex numbers as pairs of Floats:
data Complex1 = Complex1 {real :: Float, imag :: Float}
in order to update records, we define a class:
class Cartesian c where c {real :: Float, imag :: Float}
instance Cartesian Complex1
but we also want to access complex numbers by modulus and argument, so we define virtual selectors:
class Polar c where c {mod :: Float, arg :: Float}
instance Has Complex1 "mod" Float where get (Complex1 x y) = sqrt (x * x + y * y)
instance Has Complex1 "arg" Float where get (Complex1 x y) = atan2 y x
instance Polar Complex1 where _ {Polar| mod = r, arg = th} = Complex1 (r * cos th) (r * sin th)
Note that we can update x and y by {Cartesian| real = x, imag = y} or r and theta by {Polar| mod = r, arg = theta} but we cant mix them: there is no way to simultaneously update x and theta, unless we define a new class to do that.
We can change the representation to cache mod and arg without changing the classes:
data Complex2 = Complex2 {real :: Float, imag :: Float, mod :: Float, arg :: Float}
now both update functions are virtual, though none of the selectors are:
instance Cartesian Complex2 where _ {Cartesian| real = x, imag = y} = Complex2 x y (sqrt (x * x + y * y)) (atan2 y x)
instance Polar Complex2 where _ {Polar| mod = r, arg = th} = Complex2 (r * cos th) (r * sin th) r th
Alternatively, we might want to use whichever representation was last updated:
data Complex3 = Complex3a {real :: Float, imag :: Float} | Complex3b {mod :: Float, arg :: Float}
now everything is virtual:
instance Has Complex3 "real" Float where get (Complex3a x y) = x get (Complex3b r th) = r * cos th
instance Has Complex3 "imag" Float where get (Complex3a x y) = y get (Complex3b r th) = r * sin th
instance Cartesian Complex3 where _ {Cartesian| real = x, imag = y} = Complex3a x y
instance Has Complex3 "mod" Float where get (Complex3a x y) = sqrt (x * x + y * y) get (Complex3b r th) = r
instance Has Complex3 "arg" Float where get (Complex3a x y) = atan2 y x get (Complex3b r th) = th
instance Polar Complex3 where _ {Polar| mod = r, arg = th} = Complex3b r th
Sorry this is so long!
Barney.
_______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

This worries me:
3. The syntax of record updates must be changed to include the class:
r {Rcls| n1 = x1, n2 = x2}
This is really the core of the proposal. If my understanding of the problem is at all accurate, the whole reason we have trouble is that update is dependent on the class, and the Haskel98 syntax doesn't give you enough information to determine what the class is. You could always add an ad-hoc rule which says something like "if there is only one record class in scope which uses all the labels in the update, assume that one" but it would lead to horribly fragile code.
And if I understand correctly this proposal is still uncertain on some edge cases.
According to SPJ, the new version of impredicative polymorphism should allow us to use polymorphic types in contexts, which fixes the only problem I know of. Unfortunately, we can't yet experiment with it, since we won't know the details until the Haskel Symposium. If you have any other "edge cases", please let me know what they are!
I think it is time to close down the records discussion on the mail list and ask for an implementation The implementer should use any means at their disposal, probably by adding a new construct to the language. However, for now any new constructs or other implementation details should be kept internal so that we can maintain flexibility going forward. A lot of smart people are expending a huge amount of mental effort discussing how to shoehorn this problem into the existing Haskell machinery and the fine details of the best way to do it even though there is still no truly satisfactory solution. I would really like to see this effort instead go into an implementation.
This attitude is one I can't even begin to understand. How can you implement something before understanding it? What are you going to implement? Trying to "close down discussion" when no conclusion has been reached is not the action of a healthy community! Barney.

I think it is time to close down the records discussion on the mail list and ask for an implementation The implementer should use any means at their disposal, probably by adding a new construct to the language. However, for now any new constructs or other implementation details should be kept internal so that we can maintain flexibility going forward. A lot of smart people are expending a huge amount of mental effort discussing how to shoehorn this problem into the existing Haskell machinery and the fine details of the best way to do it even though there is still no truly satisfactory solution. I would really like to see this effort instead go into an implementation.
This attitude is one I can't even begin to understand. How can you implement something before understanding it? What are you going to implement? Trying to "close down discussion" when no conclusion has been reached is not the action of a healthy community!
Barney.
This discussion has largely centered around trying to come up with a hack that desugars to Haskell's existing language constructs. What you are proposing right now may be the most workable solution of that category, but Java programmers still have it far better. The main fruit of this discussion is this realization. There is an alternative to a desugaring hack: add a real record construct to the language. I don't see how any more discussion on this mail list is going to make this happen. And there is nothing to discuss if we hide the implementation details (besides some details of the exposed interface). What we need now are implementers to do actual work on this. Let them choose the path they want rather than be handicapped by us and they can decide if further discussion is needed.

On Thu, Mar 8, 2012 at 1:00 PM, Greg Weber
This discussion has largely centered around trying to come up with a hack that desugars to Haskell's existing language constructs.
There is an alternative to a desugaring hack: add a real record construct to the language.
I am not sure what distinction you are making between "real record construct" and "desugaring hack". As far as I can see, all major proposals currently desugar to type classes... not as a "hack" but because type classes *are* how Haskell does type-directed resolution. I don't think there are any ground rules set against proposing a system that doesn't use type classes. If you wanted, you could certainly propose a system that defines brand new and potentially very different semantics for a desired record system from scratch, and has nothing to do with type classes. I tend to think it would be a poor idea, both because it would be a large amount of work to be sure the semantics are even nailed down well, and because then the progress of abstraction over that new construct would happen independently from the existing progress of abstraction over type classes, and we'd end up with a more complex and warty language as a result. In any case, I'm in agreement that "stop arguing about semantics and just implement something" is a very bad idea. We aren't arguing about implementation choices here; we're arguing about pretty fundamental questions of semantics of records and labels, and the way to settle fundamental questions about the record system we hope to be using in 10 years time is not based on who has time after work for GHC hacking this month. -- Chris Smith

On Thu, Mar 8, 2012 at 12:37 PM, Chris Smith
On Thu, Mar 8, 2012 at 1:00 PM, Greg Weber
wrote: This discussion has largely centered around trying to come up with a hack that desugars to Haskell's existing language constructs.
There is an alternative to a desugaring hack: add a real record construct to the language.
I am not sure what distinction you are making between "real record construct" and "desugaring hack". As far as I can see, all major proposals currently desugar to type classes... not as a "hack" but because type classes *are* how Haskell does type-directed resolution. I don't think there are any ground rules set against proposing a system that doesn't use type classes. If you wanted, you could certainly propose a system that defines brand new and potentially very different semantics for a desired record system from scratch, and has nothing to do with type classes. I tend to think it would be a poor idea, both because it would be a large amount of work to be sure the semantics are even nailed down well, and because then the progress of abstraction over that new construct would happen independently from the existing progress of abstraction over type classes, and we'd end up with a more complex and warty language as a result.
In any case, I'm in agreement that "stop arguing about semantics and just implement something" is a very bad idea. We aren't arguing about implementation choices here; we're arguing about pretty fundamental questions of semantics of records and labels, and the way to settle fundamental questions about the record system we hope to be using in 10 years time is not based on who has time after work for GHC hacking this month.
-- Chris Smith
Just because Haskell currently resolves its types through type-classes does not mean we are forced to stop at type-classes for every aspect of the implementation. Moreover, with our best proposal here we are left in the peculiar position of declaring victory of resolving through type-classes without annotations, but now requiring a new form of type annotation for all record updates. It would make more sense just to not go full force on the type-class resolution and instead require a normal type annotation. The semantics that will be exposed to users have already been largely decide upon. If we like, we can continue to debate the fine details of the semantics we would like to expose. The problem is that we have been mixing the semantics with the implementation details and using it as an excuse to hold up any implementation.

On Thu, Mar 8, 2012 at 2:09 PM, Greg Weber
The semantics that will be exposed to users have already been largely decide upon.
Admittedly I haven't had time to carefully read some parts of this thread, and if that claim is true, then of course implementation should be the major concern. But it seems unlikely that claim is true, since in the very same email you express what looks like a pretty serious concern about the semantics that will be exposed to users (namely, the need for a new kind of type annotation). -- Chris Smith

Since it is impossible for anyone to have read and kept in their mind
all the discussion that has gone I will fill you in as I know it. We
would like the syntax of record updates to be the same as they are
today. That is separate from this proposal. This proposal is the only
solution so far that works for updates with the desugaring hack and it
requires a special form of type annotations instead of using the
syntax we would like. Does that make sense? I take it that you agree
that we should separate the discussion of semantics from
implementation: this is a perfect example of why.
On Thu, Mar 8, 2012 at 1:14 PM, Chris Smith
On Thu, Mar 8, 2012 at 2:09 PM, Greg Weber
wrote: The semantics that will be exposed to users have already been largely decide upon.
Admittedly I haven't had time to carefully read some parts of this thread, and if that claim is true, then of course implementation should be the major concern. But it seems unlikely that claim is true, since in the very same email you express what looks like a pretty serious concern about the semantics that will be exposed to users (namely, the need for a new kind of type annotation).
-- Chris Smith

Just because Haskell currently resolves its types through type-classes does not mean we are forced to stop at type-classes for every aspect of the implementation.
No, we are not forced to use type classes for everything. But it makes the language much cleaner, more flexible, easier to learn and easier to implement if we use existing structures rather than creating new ones.
Moreover, with our best proposal here we are left in the peculiar position of declaring victory of resolving through type-classes without annotations, but now requiring a new form of type annotation for all record updates. It would make more sense just to not go full force on the type-class resolution and instead require a normal type annotation.
If you have a notation for this which actually solves the update problems, you should say what it is. I haven't seen any such suggestion which really works.
The semantics that will be exposed to users have already been largely decide upon.
Please tell us what this agreed semantics is, so that we know what we have agreed to!
If we like, we can continue to debate the fine details of the semantics we would like to expose. The problem is that we have been mixing the semantics with the implementation details and using it as an excuse to hold up any implementation.
What? I have seen no discussion of implementation details at all. The translations I gave in my proposal could be used as the basis for an implementation, but the point of them was to give an unambiguous semantics for the new language features. I read the translations given by others in the same way: as semantics, not implementation. I assume that implementers would use some equivalent but more efficient method depending on the internals of ghc. Barney.
participants (3)
-
Barney Hilken
-
Chris Smith
-
Greg Weber