generalize RecordPuns and RecordWildCards to work with qualified names?

Record punning is not all that useful with qualified module names. If I write '(M.Record { M.rec_x })' it says " Qualified variable in pattern" and if I write '(M.Record { rec_x })' it says 'Not in scope: `rec_x''. Could it be this extension be further extended slightly so that 'f (M.Record { M.rec_x })' will desugar to 'f (M.Record { M.rec_x = rec_x })'? Similarly, RecordWildCards could support this too. It seems simple and useful to me... am I missing anything fatally problematic about this? Would anyone else use it?

Can you give a concrete program to illustrate your point, please? I'm not getting it. Simon | -----Original Message----- | From: haskell-cafe-bounces@haskell.org [mailto:haskell-cafe-bounces@haskell.org] On | Behalf Of Evan Laforge | Sent: 17 July 2009 23:57 | To: haskell | Subject: [Haskell-cafe] generalize RecordPuns and RecordWildCards to work with | qualified names? | | Record punning is not all that useful with qualified module names. If | I write '(M.Record { M.rec_x })' it says " Qualified variable in | pattern" and if I write '(M.Record { rec_x })' it says 'Not in scope: | `rec_x''. Could it be this extension be further extended slightly so | that 'f (M.Record { M.rec_x })' will desugar to 'f (M.Record { M.rec_x | = rec_x })'? | | Similarly, RecordWildCards could support this too. | | It seems simple and useful to me... am I missing anything fatally | problematic about this? Would anyone else use it? | _______________________________________________ | Haskell-Cafe mailing list | Haskell-Cafe@haskell.org | http://www.haskell.org/mailman/listinfo/haskell-cafe

Hello,
I think that Even refers to an example like this:
module A where
data A = A { a :: Int }
The following works:
{-# LANGUAGE NamedFieldPuns #-}
module B where
import A
f (A { a }) = a
However, if we import "A" qualified, then punning does not seem to work:
{-# LANGUAGE NamedFieldPuns #-}
module B where
import qualified A
f (A.A { a }) = a
This results in: Not in scope: `a'
{-# LANGUAGE NamedFieldPuns #-}
module B where
import qualified A
f (A.A { A.a }) = a
This results in: Qualified variable in pattern: A.a
Even is suggesting that instead of reporting an error, in the second
case we could use the translation:
f (A.A { A.a }) = a
-->
f (A.A { A.a = a })
(i.e., when punning occurs with a qualified name, use just the
unqualified part of the name in the pattern)
Hope that this helps,
-Iavor
On Thu, Jul 23, 2009 at 12:51 PM, Simon
Peyton-Jones
Can you give a concrete program to illustrate your point, please? I'm not getting it.
Simon
| -----Original Message----- | From: haskell-cafe-bounces@haskell.org [mailto:haskell-cafe-bounces@haskell.org] On | Behalf Of Evan Laforge | Sent: 17 July 2009 23:57 | To: haskell | Subject: [Haskell-cafe] generalize RecordPuns and RecordWildCards to work with | qualified names? | | Record punning is not all that useful with qualified module names. If | I write '(M.Record { M.rec_x })' it says " Qualified variable in | pattern" and if I write '(M.Record { rec_x })' it says 'Not in scope: | `rec_x''. Could it be this extension be further extended slightly so | that 'f (M.Record { M.rec_x })' will desugar to 'f (M.Record { M.rec_x | = rec_x })'? | | Similarly, RecordWildCards could support this too. | | It seems simple and useful to me... am I missing anything fatally | problematic about this? Would anyone else use it? | _______________________________________________ | Haskell-Cafe mailing list | Haskell-Cafe@haskell.org | http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Oh, now I get it, thanks. This message concerns design choices for record-syntax-related GHC extensions. Lennart, pls tune in. You don’t need to have read the thread to understand this message. | I think that Even refers to an example like this: | | module A where | data A = A { a :: Int } | | The following works: | | {-# LANGUAGE NamedFieldPuns #-} | module B where | import A | f (A { a }) = a | | However, if we import "A" qualified, then punning does not seem to work: | | {-# LANGUAGE NamedFieldPuns #-} | module B where | import qualified A | f (A.A { a }) = a | | This results in: Not in scope: `a' Right. What is happening is that GHC looks up the first 'a' (the one on the LHS) and finds it not in scope. If you add -XDisambiguateRecordFields, it works fine. But admittedly, the error message is unhelpful. I could improve that. Now on to the suggested change: | {-# LANGUAGE NamedFieldPuns #-} | module B where | import qualified A | | f (A.A { A.a }) = a | | This results in: Qualified variable in pattern: A.a | | Even is suggesting that instead of reporting an error, in the second | case we could use the translation: | | f (A.A { A.a }) = a --> f (A.A { A.a = a }) | | (i.e., when punning occurs with a qualified name, use just the | unqualified part of the name in the pattern) Yes, that'd be possible. But it seems debatable -- it doesn't *look* as if the pattern (A.A { A.a }) binds 'a' -- and it seems even less desirable in record construction and update. To be concrete, would you expect these to work too? g a = A.A { A.a } --> g a = A.A { A.a = a } h x a = x { A.a } --> h x a = a { A.a = a } In these cases, I think the abbreviated code looks too confusing. With -XDisambiguateRecordFields you could say g a = A.A { a } which seems better. (But there's no help for record update, since we don’t know which data constructor is involved.) So my current conclusion is: improve the error message, perhaps suggesting the flag -XDismabiguateRecordFields, but don't add the change you suggest. Comments? Simon

At a minimum I think the error message should be better.
I also think it would be natural to use the DisambiguateRecordFields
for the places where RecordWildcards are used.
I mean, if I change from unqualified import to a qualified one, and
then change all visible names to be qualified I would expect things to
still work.
For RecordPuns I don't have an opinion on what to do.
-- Lennart
On Sun, Aug 9, 2009 at 9:42 PM, Simon Peyton-Jones
Oh, now I get it, thanks. This message concerns design choices for record-syntax-related GHC extensions. Lennart, pls tune in. You don’t need to have read the thread to understand this message.
| I think that Even refers to an example like this: | | module A where | data A = A { a :: Int } | | The following works: | | {-# LANGUAGE NamedFieldPuns #-} | module B where | import A | f (A { a }) = a | | However, if we import "A" qualified, then punning does not seem to work: | | {-# LANGUAGE NamedFieldPuns #-} | module B where | import qualified A | f (A.A { a }) = a | | This results in: Not in scope: `a'
Right. What is happening is that GHC looks up the first 'a' (the one on the LHS) and finds it not in scope. If you add -XDisambiguateRecordFields, it works fine. But admittedly, the error message is unhelpful. I could improve that.
Now on to the suggested change:
| {-# LANGUAGE NamedFieldPuns #-} | module B where | import qualified A | | f (A.A { A.a }) = a | | This results in: Qualified variable in pattern: A.a | | Even is suggesting that instead of reporting an error, in the second | case we could use the translation: | | f (A.A { A.a }) = a --> f (A.A { A.a = a }) | | (i.e., when punning occurs with a qualified name, use just the | unqualified part of the name in the pattern)
Yes, that'd be possible. But it seems debatable -- it doesn't *look* as if the pattern (A.A { A.a }) binds 'a' -- and it seems even less desirable in record construction and update. To be concrete, would you expect these to work too?
g a = A.A { A.a } --> g a = A.A { A.a = a } h x a = x { A.a } --> h x a = a { A.a = a }
In these cases, I think the abbreviated code looks too confusing.
With -XDisambiguateRecordFields you could say
g a = A.A { a }
which seems better. (But there's no help for record update, since we don’t know which data constructor is involved.)
So my current conclusion is: improve the error message, perhaps suggesting the flag -XDismabiguateRecordFields, but don't add the change you suggest.
Comments?
Simon
_______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

| Even is suggesting that instead of reporting an error, in the second | case we could use the translation: | | f (A.A { A.a }) = a --> f (A.A { A.a = a }) | | (i.e., when punning occurs with a qualified name, use just the | unqualified part of the name in the pattern)
Yes, that'd be possible. But it seems debatable -- it doesn't *look* as if the pattern (A.A { A.a }) binds 'a' -- and it seems even less desirable in record construction and update. To be concrete, would you expect these to work too?
g a = A.A { A.a } --> g a = A.A { A.a = a } h x a = x { A.a } --> h x a = a { A.a = a }
Oh, I didn't realize that record punning included construction as well. Yeah, that's a little funky looking. I don't mind seeing the binding form and I think a new reader could figure it out without too much trouble but I would be a little confused by the construction form and think a new reader would also be confused.
With -XDisambiguateRecordFields you could say
g a = A.A { a }
which seems better. (But there's no help for record update, since we don’t know which data constructor is involved.)
I didn't know about DisambiguateRecordFields! Looks like that also makes the wildcard work like I want it to. The ghc docs for DisambiguateRecordFields don't make this very clear to me... it talks about disambiguating names in scope, but if I say "R.R { a = val}" I wouldn't expect it to "disambiguate" 'a', which is not in scope at all, to 'R.a' which looks like a completely different name. Rereading the paragraph at 7.3.11 I'm still surprised this works. Maybe add something like: ... preceeding docs ... This also means that if you use qualified imports you can still use unqualified field names. E.g. in the pattern @(R.R { a = a_val })@, @a@ will be disambiguated to @R.a@, even if @R@ is imported qualified. I gather we're not supposed to call them "records" anymore, they're supposed to be something I forget now, but the rest of the ghc docs says records, so...
So my current conclusion is: improve the error message, perhaps suggesting the flag -XDismabiguateRecordFields, but don't add the change you suggest.
Comments?
Sounds good to me. I'll try adding DisambiguateRecordFields and try out the new punning, thanks!

Evan, Lennart Thanks for the provocation. I've committed a patch that fixes all these issues. Try now! Simon Thu Aug 20 13:34:43 BST 2009 simonpj@microsoft.com * Improvements to record puns, wildcards * Make C { A.a } work with punning, expanding to C { A.a = a } * Make it so that, with -fwarn-unused-matches, f (C {..}) = x does not complain about the bindings introduced by the "..". * Make -XRecordWildCards implies -XDisambiguateRecordFields. * Overall refactoring of RnPat, which had become very crufty. In particular, there is now a monad, CpsRn, private to RnPat, which deals with the cps-style plumbing. This is why so many lines of RnPat have changed. * Refactor the treatment of renaming of record fields into two passes - rnHsRecFields1, used both for patterns and expressions, which expands puns, wild-cards - a local renamer in RnPat for fields in patterns - a local renamer in RnExpr for fields in construction and update This make it all MUCH easier to understand * Improve documentation of record puns, wildcards, and disambiguation | -----Original Message----- | From: haskell-cafe-bounces@haskell.org [mailto:haskell-cafe-bounces@haskell.org] On | Behalf Of Evan Laforge | Sent: 12 August 2009 23:59 | To: Simon Peyton-Jones | Cc: Augustsson, Lennart; haskell; GHC users | Subject: Re: [Haskell-cafe] generalize RecordPuns and RecordWildCards to work with | qualified names? | | > | Even is suggesting that instead of reporting an error, in the second | > | case we could use the translation: | > | | > | f (A.A { A.a }) = a --> f (A.A { A.a = a }) | > | | > | (i.e., when punning occurs with a qualified name, use just the | > | unqualified part of the name in the pattern) | > | > Yes, that'd be possible. But it seems debatable -- it doesn't *look* as if the | pattern (A.A { A.a }) binds 'a' -- and it seems even less desirable in record | construction and update. To be concrete, would you expect these to work too? | > | > g a = A.A { A.a } --> g a = A.A { A.a = a } | > h x a = x { A.a } --> h x a = a { A.a = a } | | Oh, I didn't realize that record punning included construction as | well. Yeah, that's a little funky looking. I don't mind seeing the | binding form and I think a new reader could figure it out without too | much trouble but I would be a little confused by the construction form | and think a new reader would also be confused. | | > With -XDisambiguateRecordFields you could say | > | > g a = A.A { a } | > | > which seems better. (But there's no help for record update, since we don't know | which data constructor is involved.) | | I didn't know about DisambiguateRecordFields! Looks like that also | makes the wildcard work like I want it to. | | The ghc docs for DisambiguateRecordFields don't make this very clear | to me... it talks about disambiguating names in scope, but if I say | "R.R { a = val}" I wouldn't expect it to "disambiguate" 'a', which is | not in scope at all, to 'R.a' which looks like a completely different | name. Rereading the paragraph at 7.3.11 I'm still surprised this | works. Maybe add something like: | | ... preceeding docs ... | | This also means that if you use qualified imports you can still use | unqualified field names. E.g. in the pattern @(R.R { a = a_val })@, | @a@ will be disambiguated to @R.a@, even if @R@ is imported qualified. | | I gather we're not supposed to call them "records" anymore, they're | supposed to be something I forget now, but the rest of the ghc docs | says records, so... | | > So my current conclusion is: improve the error message, perhaps suggesting the | flag -XDismabiguateRecordFields, but don't add the change you suggest. | > | > Comments? | | Sounds good to me. I'll try adding DisambiguateRecordFields and try | out the new punning, thanks! | _______________________________________________ | Haskell-Cafe mailing list | Haskell-Cafe@haskell.org | http://www.haskell.org/mailman/listinfo/haskell-cafe
participants (4)
-
Evan Laforge
-
Iavor Diatchki
-
Lennart Augustsson
-
Simon Peyton-Jones