RE: [Haskell] ambiguous record field names which actually aren’t ambigious

Simon Peyton-Jones simonpj at microsoft.com
Tue May 29 11:19:55 EDT 2007


[Redirecting to ghc-bugs]

|     module A where
|         data A = A { label :: Int }
|
|     module B where
|         data B = B { label :: Int }
|
|         b :: B
|         b = B { label = 0 }
|
|         x :: B -> ()
|         x B { label = 0 } = ()
|
| GHC reports an ambiguity for both usages of label.

Are you sure?  Module B doesn't even import A!

And if you mean that B does import A, then Haskell 98 indeed says it's ambiguous.

Now, it's true that in the case of both
        a) pattern matching
        b) record construction
there's a lot less ambiguity, because you know which *data constructor* is involved.  (Even better than knowing which module is involved.  But for
        c) record update  (x { label = 0 })
        d) field selection (label x)
you have no such clues.

Haskell could be defined to take advantage of (a) and (b), but if it was then it'd *also* work if data A and data B were defined in the same module, and Section 3.15 of the Haskell Report clearly states otherwise.

I conclude that Hugs is not implementing Haskell 98 here.  In fact there's clearly a bug in Hugs:

        module A where
          data A = A { foo :: Int }

        module B where
          import A
          data B = B { foo :: Bool }
          a = A {foo=3}

yields:
        ERROR "B.hs":8 - Constructor "A" does not have selected fields in A{foo = 3}

Commenting out the declaration of data B makes the definition of 'a' work.  I'm ccing hugs-bugs.

Simon


More information about the Hugs-Bugs mailing list