StricterLabelledFieldSyntax

Hi all, I've made a ticket and proposal page for making the labelled field syntax stricter, e.g. making this illegal: data A = A {x :: Int} y :: Maybe A y = Just A {x = 5} and requiring this instead: data A = A {x :: Int} y :: Maybe A y = Just (A {x = 5}) http://hackage.haskell.org/trac/haskell-prime/ticket/132 http://hackage.haskell.org/trac/haskell-prime/wiki/StricterLabelledFieldSynt... Thanks Ian

Ian Lynagh wrote:
Hi all,
I've made a ticket and proposal page for making the labelled field syntax stricter, e.g. making this illegal:
data A = A {x :: Int}
y :: Maybe A y = Just A {x = 5}
and requiring this instead:
data A = A {x :: Int}
y :: Maybe A y = Just (A {x = 5})
and, as currently, "(f some expression) {x=5}" still requires those parentheses also? Although depending on the surroundings, after this proposal, it might need to become "((f some expression) {x=5})" -Isaac

On Sat, Jul 25, 2009 at 09:45:18PM -0400, Isaac Dupree wrote:
Ian Lynagh wrote:
Hi all,
I've made a ticket and proposal page for making the labelled field syntax stricter, e.g. making this illegal:
data A = A {x :: Int}
y :: Maybe A y = Just A {x = 5}
and requiring this instead:
data A = A {x :: Int}
y :: Maybe A y = Just (A {x = 5})
and, as currently, "(f some expression) {x=5}" still requires those parentheses also? Although depending on the surroundings, after this proposal, it might need to become "((f some expression) {x=5})"
Yes, exactly. I've added this to the wiki page: No additional programs are accepted by this change, and no programs have their behaviour changed. This change only rejects some programs that were previously accepted. Thanks Ian

I've made a ticket and proposal page for making the labelled field syntax stricter
I'm definitely in favor of this change. I only have an issue with calling it "stricter." Maybe it's just me, but strictness doesn't provoke the expected image in this case. More like lower precedence. Would it be useful to add an example with the appropriate parentheses? Sean

On Sun, Jul 26, 2009 at 09:40:40AM +0200, Sean Leather wrote:
I've made a ticket and proposal page for making the labelled field syntax stricter
I'm definitely in favor of this change. I only have an issue with calling it "stricter." Maybe it's just me, but strictness doesn't provoke the expected image in this case. More like lower precedence.
I'm happy with it being given a different name.
Would it be useful to add an example with the appropriate parentheses?
I'm not sure I understand what sort of an example you want. Isn't Just (A {x = 5}) one? Thanks Ian

On Sun, Jul 26, 2009 at 13:41, Ian Lynagh wrote:
On Sun, Jul 26, 2009 at 09:40:40AM +0200, Sean Leather wrote:
I've made a ticket and proposal page for making the labelled field syntax stricter
I'm definitely in favor of this change. I only have an issue with calling it "stricter." Maybe it's just me, but strictness doesn't provoke the expected image in this case. More like lower precedence.
I'm happy with it being given a different name.
I don't know... I can't say I'm good at coming up with names. To me, the syntax is not actually stricter, just that the precedence for labeled field construction, update, & pattern is lower. What is the effective new precedence with this change? Previously, it was 11 (or simply "higher than 10"). Is it now equivalent to function application (10)?
Would it be useful to add an example with the appropriate parentheses?
I'm not sure I understand what sort of an example you want. Isn't Just (A {x = 5}) one?
I think an example should be added to the report itself with a mention of the change from the previous edition. (Any reasonable example will do.) Looking through the proposal's "Report Delta," I didn't see such a change, though perhaps it escaped me. Sean

On Sun, Jul 26, 2009 at 03:46:41PM +0200, Sean Leather wrote:
On Sun, Jul 26, 2009 at 13:41, Ian Lynagh wrote:
Would it be useful to add an example with the appropriate parentheses?
I'm not sure I understand what sort of an example you want. Isn't Just (A {x = 5}) one?
I think an example should be added to the report itself with a mention of the change from the previous edition. (Any reasonable example will do.) Looking through the proposal's "Report Delta," I didn't see such a change, though perhaps it escaped me.
Ah, I see what you mean. In my opinion the report should just define the language that it defines. One should be able to take the report and implement the language, without being distracted by all the differences between it and other language definitions. I'm assuming that the polished addenda will be kept and linked from the language reports page, for people who want to see what's changed, or who want to add support for the changes to an older implementation. I think that even an example of where parentheses are needed would be noise in the report. I don't think the report generally gives examples for this sort of thing, e.g. I don't think there's an example to demonstrate that this is invalid without parentheses: id if True then 'a' else 'b' If there is a consensus that examples like this should be added then I will add them, though. Thanks Ian

Sean Leather wrote:
To me, the syntax is not actually stricter, just that the precedence for labeled field construction, update, & pattern is lower. What is the effective new precedence with this change? Previously, it was 11 (or simply "higher than 10"). Is it now equivalent to function application (10)?
maybe it's equivalent "infix 10" (not infixr/infixl) so that it doesn't associate with function application (or itself) at all, either left- or right- ly. I didn't understand by reading the patch to the report... Ian Lynagh wrote:
I think that even an example of where parentheses are needed would be noise in the report. I don't think the report generally gives examples for this sort of thing, e.g. I don't think there's an example to demonstrate that this is invalid without parentheses: id if True then 'a' else 'b'
Well that's also something that in my opinion there *should* be an example for, because IMHO there's no obvious reason why it's banned (whereas most of the Report's syntax repeats things that should be obvious and necessary to anyone who knows Haskell). -Isaac

Hello,
I am strongly against this change. The record notation works just
fine and has been doing so for a long time. The notation is really
not that confusing and, given how records work in Haskell, makes
perfect sense (and the notation has nothing to do with the precedence
of application because there are no applications involved). In short,
I am not sure what problem is addressed by this change, while a very
real problem (backwards incompatibility) would be introduced.
-Iavor
On Sun, Jul 26, 2009 at 8:52 PM, Isaac
Dupree
Sean Leather wrote:
To me, the syntax is not actually stricter, just that the precedence for labeled field construction, update, & pattern is lower. What is the effective new precedence with this change? Previously, it was 11 (or simply "higher than 10"). Is it now equivalent to function application (10)?
maybe it's equivalent "infix 10" (not infixr/infixl) so that it doesn't associate with function application (or itself) at all, either left- or right- ly. I didn't understand by reading the patch to the report...
Ian Lynagh wrote:
I think that even an example of where parentheses are needed would be noise in the report. I don't think the report generally gives examples for this sort of thing, e.g. I don't think there's an example to demonstrate that this is invalid without parentheses: id if True then 'a' else 'b'
Well that's also something that in my opinion there *should* be an example for, because IMHO there's no obvious reason why it's banned (whereas most of the Report's syntax repeats things that should be obvious and necessary to anyone who knows Haskell).
-Isaac _______________________________________________ Haskell-prime mailing list Haskell-prime@haskell.org http://www.haskell.org/mailman/listinfo/haskell-prime

Iavor Diatchki wrote:
Hello, I am strongly against this change. The record notation works just fine and has been doing so for a long time. The notation is really not that confusing and, given how records work in Haskell, makes perfect sense (and the notation has nothing to do with the precedence of application because there are no applications involved). In short, I am not sure what problem is addressed by this change, while a very real problem (backwards incompatibility) would be introduced. -Iavor
a different approach to things that look funny, has been to implement a warning message in GHC. Would that be a good alternative? -Isaac

Hello,
On Sun, Jul 26, 2009 at 10:01 PM, Isaac
Dupree
Iavor Diatchki wrote:
Hello, I am strongly against this change. The record notation works just fine and has been doing so for a long time. The notation is really not that confusing and, given how records work in Haskell, makes perfect sense (and the notation has nothing to do with the precedence of application because there are no applications involved). In short, I am not sure what problem is addressed by this change, while a very real problem (backwards incompatibility) would be introduced. -Iavor
a different approach to things that look funny, has been to implement a warning message in GHC. Would that be a good alternative?
Not for me. I use the notation as is, and so my code would start generating warnings without any valid reason, I think. What would such a warning warn against, anyway? -Iavor

On Sun, Jul 26, 2009 at 10:16:28PM +0300, Iavor Diatchki wrote:
On Sun, Jul 26, 2009 at 10:01 PM, Isaac Dupree
wrote: Iavor Diatchki wrote:
I am strongly against this change. The record notation works just fine and has been doing so for a long time. The notation is really not that confusing and, given how records work in Haskell, makes perfect sense (and the notation has nothing to do with the precedence of application because there are no applications involved). In short, I am not sure what problem is addressed by this change, while a very real problem (backwards incompatibility) would be introduced. -Iavor
a different approach to things that look funny, has been to implement a warning message in GHC. Would that be a good alternative?
Not for me. I use the notation as is, and so my code would start generating warnings without any valid reason, I think. What would such a warning warn against, anyway?
For context, I looked at the alsa package. All of the (roughly 10) would-be-rejected cases looked like one of the two examples below. I don't really have anything new to say: Some people think these are clear, others find them confusing. Hopefully we'll find a consensus and make a decision. throwAlsa :: String -> Errno -> IO a throwAlsa fun err = do d <- strerror err throwDyn AlsaException { exception_location = fun , exception_description = d , exception_code = err } peek p = do cl <- #{peek snd_seq_addr_t, client} p po <- #{peek snd_seq_addr_t, port} p return Addr { addr_client = cl, addr_port = po } Thanks Ian

Personally I hate the fact that
f Z {x=3}
parses as
f (Z {a=3})
because even though (as Iavor says) there is only one function application involved, it *looks* as if there are two.
Equally personally, I think that the presence or absence of white space is a powerful signal to programmers, and it's a shame to deny ourselves use of it. So I'd be quite happy with *requiring* there to be no space, thus Z{ x=3 }. If that's tricky to lex, so be it. (Though a token "BRACE_WITH_NO_PRECEDING_WHITESPACE" might do the job.) But this would be a very non-backward-compatible change.
Simon
| -----Original Message-----
| From: haskell-prime-bounces@haskell.org [mailto:haskell-prime-
| bounces@haskell.org] On Behalf Of Ian Lynagh
| Sent: 26 July 2009 21:53
| To: haskell-prime@haskell.org
| Subject: Re: StricterLabelledFieldSyntax
|
| On Sun, Jul 26, 2009 at 10:16:28PM +0300, Iavor Diatchki wrote:
| >
| > On Sun, Jul 26, 2009 at 10:01 PM, Isaac
| > Dupree

Hello,
There are some examples where the current notation is nicer
(subjectively so, of course :-) with the white space. Mostly, when
the record fields do not fit on a single line. I tend to write things
like this:
ParseError
{ errorPosition = ..
, errorDescription = ..
}
alternatively:
ParseError {
errorPosition = ..,
errorDescription = ..
}
I think that it would be very odd if these did not work because the
brace had to be next to the constructor without white space. The only
alternative I can see would be to have _two_ different notations for
creating records one with the space that requires parens, and one
without that does not require parens but (at least to me) this looks
like a cludge, and is much more complex than the current situation.
-Iavor
On Sat, Aug 1, 2009 at 2:58 PM, Simon Peyton-Jones
Personally I hate the fact that f Z {x=3} parses as f (Z {a=3}) because even though (as Iavor says) there is only one function application involved, it *looks* as if there are two.
Equally personally, I think that the presence or absence of white space is a powerful signal to programmers, and it's a shame to deny ourselves use of it. So I'd be quite happy with *requiring* there to be no space, thus Z{ x=3 }. If that's tricky to lex, so be it. (Though a token "BRACE_WITH_NO_PRECEDING_WHITESPACE" might do the job.) But this would be a very non-backward-compatible change.
Simon
| -----Original Message----- | From: haskell-prime-bounces@haskell.org [mailto:haskell-prime- | bounces@haskell.org] On Behalf Of Ian Lynagh | Sent: 26 July 2009 21:53 | To: haskell-prime@haskell.org | Subject: Re: StricterLabelledFieldSyntax | | On Sun, Jul 26, 2009 at 10:16:28PM +0300, Iavor Diatchki wrote: | > | > On Sun, Jul 26, 2009 at 10:01 PM, Isaac | > Dupree
wrote: | > > Iavor Diatchki wrote: | > >> | > >> I am strongly against this change. The record notation works just | > >> fine and has been doing so for a long time. The notation is really | > >> not that confusing and, given how records work in Haskell, makes | > >> perfect sense (and the notation has nothing to do with the precedence | > >> of application because there are no applications involved). In short, | > >> I am not sure what problem is addressed by this change, while a very | > >> real problem (backwards incompatibility) would be introduced. | > >> -Iavor | > > | > > a different approach to things that look funny, has been to implement a | > > warning message in GHC. Would that be a good alternative? | > | > Not for me. I use the notation as is, and so my code would start | > generating warnings without any valid reason, I think. What would | > such a warning warn against, anyway? | | For context, I looked at the alsa package. All of the (roughly 10) | would-be-rejected cases looked like one of the two examples below. I | don't really have anything new to say: Some people think these are | clear, others find them confusing. Hopefully we'll find a consensus and | make a decision. | | | throwAlsa :: String -> Errno -> IO a | throwAlsa fun err = do d <- strerror err | throwDyn AlsaException | { exception_location = fun | , exception_description = d | , exception_code = err | } | | peek p = do cl <- #{peek snd_seq_addr_t, client} p | po <- #{peek snd_seq_addr_t, port} p | return Addr { addr_client = cl, addr_port = po } | | | Thanks | Ian | | _______________________________________________ | Haskell-prime mailing list | Haskell-prime@haskell.org | http://www.haskell.org/mailman/listinfo/haskell-prime _______________________________________________ Haskell-prime mailing list Haskell-prime@haskell.org http://www.haskell.org/mailman/listinfo/haskell-prime

On 01/08/2009 12:58, Simon Peyton-Jones wrote:
Personally I hate the fact that f Z {x=3} parses as f (Z {a=3}) because even though (as Iavor says) there is only one function application involved, it *looks* as if there are two.
Equally personally, I think that the presence or absence of white space is a powerful signal to programmers, and it's a shame to deny ourselves use of it. So I'd be quite happy with *requiring* there to be no space, thus Z{ x=3 }. If that's tricky to lex, so be it. (Though a token "BRACE_WITH_NO_PRECEDING_WHITESPACE" might do the job.) But this would be a very non-backward-compatible change.
On this point - I agree that whitespace-sensitive syntax presents no problem to programmers, and is often quite natural. However, I think it presents enough other problems that it should be avoided where possible. I'm thinking of - being friendly to automatic program generation - being friendly to parsers, and tools that grok Haskell - making code robust to modification that changes whitespace - making the grammar (in the report) simpler all of these things are hurt by whitespace-sensitive syntax. IMO, we should think very carefully before introducing any. Cheers, Simon
Simon
| -----Original Message----- | From: haskell-prime-bounces@haskell.org [mailto:haskell-prime- | bounces@haskell.org] On Behalf Of Ian Lynagh | Sent: 26 July 2009 21:53 | To: haskell-prime@haskell.org | Subject: Re: StricterLabelledFieldSyntax | | On Sun, Jul 26, 2009 at 10:16:28PM +0300, Iavor Diatchki wrote: |> |> On Sun, Jul 26, 2009 at 10:01 PM, Isaac |> Dupree
wrote: |> > Iavor Diatchki wrote: |> >> |> >> I am strongly against this change. The record notation works just |> >> fine and has been doing so for a long time. The notation is really |> >> not that confusing and, given how records work in Haskell, makes |> >> perfect sense (and the notation has nothing to do with the precedence |> >> of application because there are no applications involved). In short, |> >> I am not sure what problem is addressed by this change, while a very |> >> real problem (backwards incompatibility) would be introduced. |> >> -Iavor |> > |> > a different approach to things that look funny, has been to implement a |> > warning message in GHC. Would that be a good alternative? |> |> Not for me. I use the notation as is, and so my code would start |> generating warnings without any valid reason, I think. What would |> such a warning warn against, anyway? | | For context, I looked at the alsa package. All of the (roughly 10) | would-be-rejected cases looked like one of the two examples below. I | don't really have anything new to say: Some people think these are | clear, others find them confusing. Hopefully we'll find a consensus and | make a decision. | | | throwAlsa :: String -> Errno -> IO a | throwAlsa fun err = do d<- strerror err | throwDyn AlsaException | { exception_location = fun | , exception_description = d | , exception_code = err | } | | peek p = do cl<- #{peek snd_seq_addr_t, client} p | po<- #{peek snd_seq_addr_t, port} p | return Addr { addr_client = cl, addr_port = po } | | | Thanks | Ian | | _______________________________________________ | Haskell-prime mailing list | Haskell-prime@haskell.org | http://www.haskell.org/mailman/listinfo/haskell-prime _______________________________________________ Haskell-prime mailing list Haskell-prime@haskell.org http://www.haskell.org/mailman/listinfo/haskell-prime

all of these things are hurt by whitespace-sensitive syntax. IMO, we should think very carefully before introducing any.
Haskell already has plenty of whitespace sensitivity. The layout rule is a pretty major part of the tradition. Other places: * (Just.foo) differs from (Just . foo) * --| differs from -- | * With NegativeSyntax, (-1) would differ from (- 1) * In TemplateHaskell, $x differs from $ x * In TemplateHaskell, [d| differs from [ d | * With UnboxedTypes, (# differs from ( # * With UnboxedTypes, 3# differs from 3 # Regards, Malcolm

On 03/08/2009 10:44, Malcolm Wallace wrote:
all of these things are hurt by whitespace-sensitive syntax. IMO, we should think very carefully before introducing any.
Haskell already has plenty of whitespace sensitivity. The layout rule is a pretty major part of the tradition. Other places:
* (Just.foo) differs from (Just . foo) * --| differs from -- | * With NegativeSyntax, (-1) would differ from (- 1) * In TemplateHaskell, $x differs from $ x * In TemplateHaskell, [d| differs from [ d | * With UnboxedTypes, (# differs from ( # * With UnboxedTypes, 3# differs from 3 #
Yes, I know. There's also numbers: 1.0, 1e3, 0xFF. And strictly speaking keywords are also in violation: "where by" vs. "whereby", although I wouldn't go so far as to suggest we change that, of course. Only the first two items in your list are actually in Haskell, incedentally, and I argued against the others. The problem is it's hard to find spare syntax, especially for brackets, without either adding whitespace-sensitivity or using non-ASCII characters. The layout rule doesn't count, at least for the kind of whitespace-sensitivity I'm worried about, which is the presence/absence of whitespace rather than the quantity or composition of it. Cheers, Simon

Ian Lynagh
http://hackage.haskell.org/trac/haskell-prime/wiki/StricterLabelledFieldSynt...
I approve of the principle -- the binding level is confusing, but I would far rather make a bigger change, so that rather than being confusable with the binding level of function application, it /has/ the binding level of function application. ie, instead of a{x=42} one would have to write {x=42}a, and "f {x=42} a" would parse as "(f {x=42}) a" -- and be an error because labelled field assignments aren't currently proper functions (but under this change they could be thought of as a restricted kind of function). This would allow a future change that made them first class citizen; "{x=42}" would have type something like (Num a => forall D. D{x::a} -> D{x::a}) (if you can work out the intent of a syntax made up on the spur of the moment). Working out the ramifications of a type system that allowed that is a job for later, but it would be worthwhile to make it possible. Would it be proper to create a counterproposal for this syntax? ReversedLabelledFieldSyntax? -- Jón Fairbairn Jon.Fairbairn@cl.cam.ac.uk

On Sun, Jul 26, 2009 at 09:21:06AM +0100, Jon Fairbairn wrote:
Ian Lynagh
writes: http://hackage.haskell.org/trac/haskell-prime/wiki/StricterLabelledFieldSynt...
I approve of the principle -- the binding level is confusing, but I would far rather make a bigger change, so that rather than being confusable with the binding level of function application, it /has/ the binding level of function application. ie, instead of a{x=42} one would have to write {x=42}a
This would allow a future change [...]
Would it be proper to create a counterproposal for this syntax? ReversedLabelledFieldSyntax?
I would claim that, of the existing Haskell code, StricterLabelledFieldSyntax only rejects unclear ("bad") code, and requiring it be changed (to be made clearer) is a good thing. Your proposal would reject /all/ labelled field code, "good" and "bad" alike. That's a much harder sell, especially without the "future change" being fleshed out or agreed upon. All just my opinion, of course! The only way to find out for sure is to make the proposal and see what happens. Thanks Ian

Hi
Would it be proper to create a counterproposal for this syntax? ReversedLabelledFieldSyntax?
I would claim that, of the existing Haskell code, StricterLabelledFieldSyntax only rejects unclear ("bad") code, and requiring it be changed (to be made clearer) is a good thing.
I haven't seen anyone else claim to use the current more liberal syntax for fields, but I know that I do rather extensively. I would consider: Just A {a = 1} To be confusing, but if you simply omit the space: Just A{a = 1} I now find that perfectly clear and unambiguous. I realise this isn't necessarily a discussion of the merits of the feature, but I don't consider this removal as clear cut as some people are suggesting. Thanks Neil

On Sun, Jul 26, 2009 at 03:24:03PM +0100, Neil Mitchell wrote:
I haven't seen anyone else claim to use the current more liberal syntax for fields, but I know that I do rather extensively. I would consider:
Just A {a = 1}
To be confusing, but if you simply omit the space:
Just A{a = 1}
I now find that perfectly clear and unambiguous.
I did consider allowing that, perhaps by making "Foo{" a single token, but I couldn't see a clean way to do it. Personally, I prefer rejecting it anyway. Thanks Ian

I haven't seen anyone else claim to use the current more liberal syntax for fields, but I know that I do rather extensively. I would consider:
Just A {a = 1}
To be confusing, but if you simply omit the space:
Just A{a = 1}
I now find that perfectly clear and unambiguous.
I did consider allowing that, perhaps by making "Foo{" a single token, but I couldn't see a clean way to do it.
Just to be explicit, I think Just A{...} is clear for me, but really wouldn't want the parser to depend on the presence or absence of spaces - that's just not very Haskell like. Thanks, Neil

Neil Mitchell
Hi
Would it be proper to create a counterproposal for this syntax? ReversedLabelledFieldSyntax?
I would claim that, of the existing Haskell code, StricterLabelledFieldSyntax only rejects unclear ("bad") code, and requiring it be changed (to be made clearer) is a good thing.
I haven't seen anyone else claim to use the current more liberal syntax for fields, but I know that I do rather extensively. I would consider:
Just A {a = 1}
To be confusing, but if you simply omit the space:
Just A{a = 1}
I now find that perfectly clear and unambiguous. I realise this isn't necessarily a discussion of the merits of the feature, but I don't consider this removal as clear cut as some people are suggesting.
for what it's worth, I do take advantage of the current syntax for functions with default parameters: f defaults{some_option = non_default_value} and like you, I don't put a space. I've long thought that compilers should issue warnings for layout that conflicts with precedence -- everyone knows that 2+2 * 8 means 2 + (2*8), but I'd guess it takes a /tiny/ bit longer to read correctly, and for less familiar operators the misleading layout is more likely a source of misreadings. -- Jón Fairbairn Jon.Fairbairn@cl.cam.ac.uk

Jon Fairbairn wrote:
Ian Lynagh
writes: http://hackage.haskell.org/trac/haskell-prime/wiki/StricterLabelledFieldSynt...
I approve of the principle -- the binding level is confusing, but I would far rather make a bigger change, so that rather than being confusable with the binding level of function application, it /has/ the binding level of function application. ie, instead of a{x=42} one would have to write {x=42}a,
we already know which record type it is, because record fields don't have disambiguation. If it's (data D = D { x, y :: Int }) then (x :: D -> Int) and we would have (({x=42}) :: D -> D). Or (data E n = E1 { ex, ey :: n } | E2 { ey :: n } | E3 {ex :: n}), (ey :: E n -> n), (({ex=42}) :: Num n => E n -> E n), but probably not ever allowing to change (E n1 -> E n2) even if it changes both ex and ey. I think it wouldn't be a terrible syntax, ({...}), kind of like infix operators can be made into functions like (+). If you wanted to make a proposal for such an extension. -Isaac

According to the wiki, since I'm not a committee member, I should post
proposals here. See below my reply to Isaac's message.
Isaac Dupree
Jon Fairbairn wrote:
Ian Lynagh
writes: [field update] /has/ the binding level of function application. ie, instead of a{x=42} one would have to write {x=42}a, we already know which record type it is, because record fields don't have disambiguation.
OK, I'd forgotten that. Makes things straightforward.
I think it wouldn't be a terrible syntax, ({...}), kind of like infix operators can be made into functions like (+). If you wanted to make a proposal for such an extension.
I was wondering how to make it compatible. That looks like a reasonable compromise, so... Proposal: FirstClassFieldUpdates Summary: Add some syntax that makes field updates into functions. Description: On several occasions I've wanted to pass arguments that modified records and been disappointed that I have to use a lambda expression. Parenthesis around updates would make them into functions, ie ({a=1,b=2,...}) would mean the same as (\d -> d{a=1,b=2,...}), but be more concise. This chimes reasonably well with (+) turning an infix operator into a function. ({}) would be the (polymorphic) identity function. This would permit concise calls to functions with default/optional parameters:
data Defaults_for_f = Defaults_for_f {option1::A, option2::B, ...} defaults_for_f = Defaults_for_f {option1=default1, ...}
f options other arguments = let params = options defaults_for_f in ...
allows one to write f ({}) ... (or f id ... if no-one likes ({})) to call f with the default arguments, or f ({option1 = something_else}) ... to go away from the defaults. Discussion: I would rather make {field1=a, field2=b, ...} a function. ie instead of a{thing=1} one would write {thing=1} a. In other words {field1=a, field2=b, ...} would be a notation for the function that is currently written \d -> d{field1=a, field2=b, ...}. Again we would want empty record updates {} to be the identity function. We would then remove the thing{fu=bar} syntax (where thing is a variable). This would simultaneously simplify the syntax, remove the misleading "f x {a=b}" bemoaned in StricterLabelledFieldSyntax and make certain use cases (such as default parameters) more concise. Unfortunately old programmes wouldn't compile any more¹, but I think that Haskell' is the place for backwards incompatible changes that simplify things. The difficulty would be what to do about Constructor{fu=bar}, given that Constructor is currently defined to operate both as a function and be used in patterns (there's something fishy about this when the record has named fields). As yet I haven't thought of a good way of doing that, hence the current proposal that adds syntax rather than takes it away. [1] All the errors would be compile time errors. -- Jón Fairbairn Jon.Fairbairn@cl.cam.ac.uk

Jon Fairbairn wrote:
Parenthesis around updates would make them into functions, ie ({a=1,b=2,...}) would mean the same as (\d -> d{a=1,b=2,...}), but be more concise.
yes it is, however field updates are occasionally slightly annoying, since they can't change something's type at all, IIRC. Say, data C nx ny = C { x :: nx, y :: ny } x_set :: nx2 -> C nx1 ny -> C nx2 ny --x_set x2 c = c {x = x2} --type error --x_set x2 = ({x = x2}) --still a type error x_set x2 c = C {x = x2, y = y c} --legal Which is possibly a reason to stay away from field-update syntax on some occasions, and therefore not want it to get a more prominent place in the language if it doesn't deserve it yet. -Isaac

Isaac Dupree
Jon Fairbairn wrote:
Parenthesis around updates would make them into functions, ie ({a=1,b=2,...}) would mean the same as (\d -> d{a=1,b=2,...}), but be more concise.
yes it is, however field updates are occasionally slightly annoying, since they can't change something's type at all, IIRC. Say, data C nx ny = C { x :: nx, y :: ny } x_set :: nx2 -> C nx1 ny -> C nx2 ny --x_set x2 c = c {x = x2} --type error
If that were the case, it would be a serious wart that needed to be addressed. However, implementation would be fairly straightforward as an "extension" is already present in ghc: let x_set x2 c = c{x=x2} :t x_set x_set :: nx -> C t ny -> C nx ny ;-) (or did I misunderstand you?) -- Jón Fairbairn Jon.Fairbairn@cl.cam.ac.uk

Hi all,
Jon Fairbairn
Isaac Dupree
wrote: yes it is, however field updates are occasionally slightly annoying, since they can't change something's type at all, IIRC. Say, data C nx ny = C { x :: nx, y :: ny } x_set :: nx2 -> C nx1 ny -> C nx2 ny --x_set x2 c = c {x = x2} --type error
If that were the case, it would be a serious wart that needed to be addressed. However, implementation would be fairly straightforward as an "extension" is already present in ghc:
let x_set x2 c = c{x=x2} :t x_set x_set :: nx -> C t ny -> C nx ny
;-) (or did I misunderstand you?)
Indeed, field update can change the type, which I guess is the point Jon is making. And Isaac's example above compiles without any problems or extensions. H98 as far as I'm aware. However, there are cases where the current field update facility arguably isn't good enough, namely when there are more than one constructor, some of which do not have certain of the fields. See http://hackage.haskell.org/trac/haskell-prime/wiki/ExistingRecords for examples, in particular "Polymorphic Record Update take II". As an aside, having revisited that discussion, I still think the idea of being able to do an update for constructors that do NOT have certain fields makes a lot of sense. The record wildcard extension, that was mentioned as a possible workaround, seems far less appealing and flexible. I don't even know what it would mean if it's used more than once in a scope, e.g. what about the following: f (C1 {a = 1, ..}) (C2 {b = 2, ..}) = (C1 {a = 10, ..}, C2 {b = 20, ..}) ??? Best, /Henrik -- Henrik Nilsson School of Computer Science The University of Nottingham nhn@cs.nott.ac.uk This message has been checked for viruses but the contents of an attachment may still contain software viruses, which could damage your computer system: you are advised to perform your own checks. Email communications with the University of Nottingham may be monitored as permitted by UK legislation.

Jon Fairbairn wrote:
Isaac Dupree
writes: Jon Fairbairn wrote:
Parenthesis around updates would make them into functions, ie ({a=1,b=2,...}) would mean the same as (\d -> d{a=1,b=2,...}), but be more concise. yes it is, however field updates are occasionally slightly annoying, since they can't change something's type at all, IIRC. Say, data C nx ny = C { x :: nx, y :: ny } x_set :: nx2 -> C nx1 ny -> C nx2 ny --x_set x2 c = c {x = x2} --type error
If that were the case, it would be a serious wart that needed to be addressed. However, implementation would be fairly straightforward as an "extension" is already present in ghc:
oh maybe I got confused. (My confusion also could have been the result of a bug that was recently fixed in GHC that affected the type of some cases like that where there are multiple constructors...) -Isaac

| Proposal: FirstClassFieldUpdates | | Summary: | Add some syntax that makes field updates into functions. I'm wary about occupying too much "syntactic space" with Haskell's named-field notation. If you had a keyword, like update { foo = bar } meaning \x. x { foo = bar } that'd get you into a new syntactic space. But braces alone are so precious that I'm not sure that record updates justify consuming them. On a related matter, people want to use record syntax for GADTs and existentials. For record selection and construction these are more or less fine (ie one can make a sensible spec). But record update is another matter. Haskell 98 says that record update can change the type of a record (contrary to some posts in this thread), but the specification becomes really rather tricky for GADTs and existentials. Indeed, I was going to propose that in H Prime we might consider making update *not* change the type, backing away from the current H98 story, but one that makes the spec a lot easier. But various people have been arguing in favour of the H98 story so I may have an uphill struggle! Simon

Simon Peyton-Jones
| Proposal: FirstClassFieldUpdates | | Summary: Add some syntax that makes field updates into | functions.
I'm wary about occupying too much "syntactic space" with Haskell's named-field notation. If you had a keyword, like update { foo = bar } meaning \x. x { foo = bar } that'd get you into a new syntactic space.
It'd also make the syntax too noisy to be of any interest.
But braces alone are so precious that I'm not sure that record updates justify consuming them.
I'm not particularly wedded to braces, it's simply that they are the syntax already used for updates, so to make updates first class that is the obvious choice. For first class updates I'd be happy with something like “foo := bar”, but then I would want the syntax of record construction to be something similar. For some reason, the use of braces in record syntax differs from all others I can think of: all the rest are x {something; something; something} and can replaced by layout. So braces (with commas) for records at all is an irregularity.
On a related matter, people want to use record syntax for GADTs and existentials. For record selection and construction these are more or less fine (ie one can make a sensible spec). But record update is another matter. Haskell 98 says that record update can change the type of a record (contrary to some posts in this thread), but the specification becomes really rather tricky for GADTs and existentials. Indeed, I was going to propose that in H Prime we might consider making update *not* change the type, backing away from the current H98 story, but one that makes the spec a lot easier. But various people have been arguing in favour of the H98 story so I may have an uphill struggle!
I'm coming back to this stuff rather late; I can't say I understand the interactions between GADTs, existentials and records. In the absence of those developments what I would have liked to have seen would have been a decomposition of data declarations and the resulting types into orthogonal parts. For one thing, allowing “Constr a b c” for construction and pattern matching on something that was declared as “Constr {x::A, y::B, z::C}” looks improper to me, and another is the restricted nature of Haskell’s union types (cf what I started to talk about at AngloHaskell; see http://www.cl.cam.ac.uk/~jf15/Haskell-notes/AngloHaskell2009-Not-Talk.xhtml for some notes on that) So the outline would be (forgive the poor choice of keywords here): 1. distinguishable types The type “dtype Constr T1 T2…” would correspond to a single alternative of a data declaration (dtype is just an arbitrary keyword from distinguishable type). The idea is that two dtypes only match if their (fully qualified) constructors match. 2. Symmentric unions of distinguishable types A type (dtype1 | dtype2 | …) corresponds to the alternatives of a data declaration. Note that “|” can only be used on distinguishable types (and unions of distinguishable types). So a non-record-syntax data declaration data Widget = Thing1 A | Thing2 B | … could still be valid but now be a shorthand for type Widget = dtype Thing1 A | dtype Thing2 B | … One of the benefits of this is that the type of anything can be written down without having to refer to any declarations. 3. Once that is done, we can come up with a design for records: field1:=x . field2:=y . … $ emptyRecord Now “field:=x”; is a first class function, polymorphic on all records that have “field” as a field. We might want to choose some nicer syntax for emptyRecord, (“{}” if you like), but the only other expression syntax needed is the pseudo operator “:=”, though some syntax for the types would need to be designed. “record (field1::Type1, …)” would do, with “record ()” for the empty record. There is no /need/ to use up precious braces ;-). * * * You’ll complain that this isn’t fully worked out, and as I say, I don’t know how it interacts with GADTs and other things I’m not up to date with. But as far as I remember, I could simulate all of this in Ponder’s type system, so it shouldn’t be too hard for someone au fait with the way things are currently done to specify it properly. -- Jón Fairbairn Jon.Fairbairn@cl.cam.ac.uk

Ian Lynagh wrote:
Hi all,
I've made a ticket and proposal page for making the labelled field syntax stricter, e.g. making this illegal:
data A = A {x :: Int}
y :: Maybe A y = Just A {x = 5}
+1: The precedence here is an ugly wart. It's particularly annoying when teaching Haskell syntax to newbies; the simple rule "juxtaposition binds tighter than everything else" doesn't quite work. Ganesh =============================================================================== Please access the attached hyperlink for an important electronic communications disclaimer: http://www.credit-suisse.com/legal/en/disclaimer_email_ib.html ===============================================================================

On Sun, 2009-07-26 at 02:34 +0100, Ian Lynagh wrote:
Hi all,
I've made a ticket and proposal page for making the labelled field syntax stricter, e.g. making this illegal:
data A = A {x :: Int}
y :: Maybe A y = Just A {x = 5}
and requiring this instead:
data A = A {x :: Int}
y :: Maybe A y = Just (A {x = 5})
I think I don't like it. It makes the "labelled function argument" trick much less nice syntactically. ... <- createProcess proc { cwd = Just "blah" } This is especially so if the labelled function argument is not the final parameter since then one cannot use $, you'd have to put the whole thing in ()'s. The labelled argument technique is one I think we should be making greater use of (eg look at the proliferation of openFile variants) so I don't think we should be changing the syntax to make it harder / uglier. Duncan

On Sun, Jul 26, 2009 at 02:34:59AM +0100, Ian Lynagh wrote:
I've made a ticket and proposal page for making the labelled field syntax stricter, e.g. making this illegal:
data A = A {x :: Int}
y :: Maybe A y = Just A {x = 5}
and requiring this instead:
data A = A {x :: Int}
y :: Maybe A y = Just (A {x = 5})
I don't like this not only because it would make a lot of code more unwieldy, but it muddles the interpretation of how one interprets braces. Right now, we have a very simple rule, braces always bind to the left, no matter where they are used, you can always tell what they mean by the thing immediately preceeding them. Whether it is 'let', 'do', 'where', a constructor, or an expression, you have a simple rule to remember which is nice. Also, what about data declarations? Would we need something like below? It seems odd to apply such a rule sometimes but not others.
data Foo = (Foo { .. }) | ...
John -- John Meacham - ⑆repetae.net⑆john⑈ - http://notanumber.net/

On Wed, Aug 12, 2009 at 11:45:04PM -0700, John Meacham wrote:
Also, what about data declarations? Would we need something like below? It seems odd to apply such a rule sometimes but not others.
data Foo = (Foo { .. }) | ...
You would not need these parentheses; nor would you need parentheses in foo = Foo { ... } Thanks Ian
participants (13)
-
Duncan Coutts
-
Henrik Nilsson
-
Ian Lynagh
-
Iavor Diatchki
-
Isaac Dupree
-
John Meacham
-
Jon Fairbairn
-
Malcolm Wallace
-
Neil Mitchell
-
Sean Leather
-
Simon Marlow
-
Simon Peyton-Jones
-
Sittampalam, Ganesh