[Haskell-cafe] generalize RecordPuns and RecordWildCards to work with qualified names?

Iavor Diatchki iavor.diatchki at gmail.com
Fri Jul 24 19:48:48 EDT 2009


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<simonpj at microsoft.com> wrote:
> Can you give a concrete program to illustrate your point, please?  I'm not getting it.
>
> Simon
>
> | -----Original Message-----
> | From: haskell-cafe-bounces at haskell.org [mailto:haskell-cafe-bounces at 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 at haskell.org
> | http://www.haskell.org/mailman/listinfo/haskell-cafe
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>


More information about the Haskell-Cafe mailing list