Definition of hidden instance members (bug in GHC or Hugs+Yhc)

Hi, This is either a GHC bug, or a Yhc+Hugs bug - I'm not sure which, but the compilers disagree: import Prelude hiding ((==)) data Foo = Foo instance Eq Foo where (==) a b = True GHC says: Temp.hs:14:4: `==' is not a (visible) method of class `Eq' Yhc and Hugs both successfully compile the module. Does anyone know which compiler(s) are in the wrong, and need bugs filing? Thanks Neil

This is either a GHC bug, or a Yhc+Hugs bug - I'm not sure which, but the compilers disagree:
import Prelude hiding ((==)) data Foo = Foo instance Eq Foo where (==) a b = True
I was thinking that GHC's behaviour seems more sensible, but the following fails: import qualified Module as M instance MClass Foo where M.foo = undefined M. is not allowed as a prefix of a function, which makes resolving ambiguities hard unless the compiler solves the issue for you (as Hugs and Yhc do) Thanks Neil

On 2008 Jul 5, at 19:02, Neil Mitchell wrote:
This is either a GHC bug, or a Yhc+Hugs bug - I'm not sure which, but the compilers disagree:
import Prelude hiding ((==)) data Foo = Foo instance Eq Foo where (==) a b = True
I was thinking that GHC's behaviour seems more sensible, but the following fails:
import qualified Module as M
instance MClass Foo where M.foo = undefined
M. is not allowed as a prefix of a function, which makes resolving ambiguities hard unless the compiler solves the issue for you (as Hugs and Yhc do)
But this works for me in ghc: foo.hs:
import Mod as M
data Bar a = Bar Int a
instance M.MClass (Bar a) where foo _ = M.foozero foozero = Bar 0 (undefined :: a)
main = putStrLn "foo"
Mod.hs:
module Mod where
class MClass a where foo :: a -> a foozero :: a
-- brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allbery@kf8nh.com system administrator [openafs,heimdal,too many hats] allbery@ece.cmu.edu electrical and computer engineering, carnegie mellon university KF8NH

M. is not allowed as a prefix of a function, which makes resolving ambiguities hard unless the compiler solves the issue for you (as Hugs and Yhc do)
See also: http://www.haskell.org/pipermail/haskell-prime/2008-April/002569.html http://hackage.haskell.org/trac/ghc/ticket/2237 Claus

I think GHC is right here. See http://haskell.org/onlinereport/decls.html#instance-decls esp the bit starting "It is illegal to give a binding..." Simon | -----Original Message----- | From: haskell-cafe-bounces@haskell.org [mailto:haskell-cafe-bounces@haskell.org] On Behalf Of Neil | Mitchell | Sent: 06 July 2008 00:03 | To: Haskell Cafe | Subject: [Haskell-cafe] Re: Definition of hidden instance members (bug in GHC or Hugs+Yhc) | | > This is either a GHC bug, or a Yhc+Hugs bug - I'm not sure which, but | > the compilers disagree: | > | > import Prelude hiding ((==)) | > data Foo = Foo | > instance Eq Foo where | > (==) a b = True | | I was thinking that GHC's behaviour seems more sensible, but the | following fails: | | import qualified Module as M | | instance MClass Foo where | M.foo = undefined | | M. is not allowed as a prefix of a function, which makes resolving | ambiguities hard unless the compiler solves the issue for you (as Hugs | and Yhc do) | | Thanks | | Neil | _______________________________________________ | Haskell-Cafe mailing list | Haskell-Cafe@haskell.org | http://www.haskell.org/mailman/listinfo/haskell-cafe

On Sun, Jul 06, 2008 at 12:00:07AM +0100, Neil Mitchell wrote:
This is either a GHC bug, or a Yhc+Hugs bug - I'm not sure which, but the compilers disagree:
import Prelude hiding ((==)) data Foo = Foo instance Eq Foo where (==) a b = True
GHC says: Temp.hs:14:4: `==' is not a (visible) method of class `Eq'
Yhc and Hugs both successfully compile the module.
Does anyone know which compiler(s) are in the wrong, and need bugs filing?
GHC is correct. Report 4.3.2: "It is illegal to give a binding for a class method that is not in scope, but the name under which it is in scope is immaterial; in particular, it may be a qualified name." In this case neither == nor Prelude.== is in scope.
participants (5)
-
Brandon S. Allbery KF8NH
-
Claus Reinke
-
Neil Mitchell
-
Ross Paterson
-
Simon Peyton-Jones