RFC: qualified vs unqualified names in defining instance methods

consider Haskell 98 report, section 4.3.2 "Instance Declarations": The declarations d may contain bindings only for the class methods of C. 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. (This rule is identical to that used for subordinate names in export lists --- Section 5.2.) For example, this is legal, even though range is in scope only with the qualified name Ix.range. module A where import qualified Ix instance Ix.Ix T where range = ... i consider this confusing (see example at the end), but even worse is that the reference to 5.2 appears to rule out the use of qualified names when defining instance methods. while this abbreviation of qualified names as unqualified names when unambiguous may be harmless in the majority of cases, it seems wrong that the more appropriate explicit disambiguation via qualified names is ruled out entirely. i submit that 4.3.2 should be amended so that qualified names are permitted when defining instance methods. here's an example to show that the unambiguity holds only on the lhs of the method definition, and that the forced use of unqualified names can be confusing: module QI where import Prelude hiding (Functor(..)) import qualified Prelude (Functor(..)) data X a = X a deriving Show instance Prelude.Functor X where fmap f (X a) = X (f a) where q = (reverse fmap,Prelude.fmap not [True],reverse QI.fmap) fmap = "fmap" note that there are two unqualified uses of 'fmap' in the instance declaration, referring to different qualified names: - in the lhs, 'fmap' refers to 'Prelude.fmap', which isn't in scope unqualified, only qualified - in the rhs, 'fmap' refers to 'QI.fmap' claus

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.
I believe this was a change introduced in H'98 to tidy up the language. Previously, if a class was imported qualified, it was only possible to declare an instance method by using a qualified name on the lhs. It was felt that this was an oddity, because there are no other situations in which it was even possible to define a variable with an explicitly-qualified name, and in any case the qualification was entirely redundant, because there was no ambiguity. Additionally, permitting a qualified name to appear in the definitional position of any declaration led to ambiguity in parsing. Regards, Malcolm

Hello,
I think that the H98 change was a good one. Qualified names should
only be used in _uses_ of variables (to disambiguate) and not in
definitions because (hopefully) there is nothing to disambiguate in a
definition.
By the way, method definitions already have a distinction between what
is on the LHS and what is on the RHS. For example, consider the
following instance:
instance Show a => Show (Maybe a) where
show Nothing = "Nothing"
show (Just a) = "Just " ++ show a
Here "show" is not a recursive function because the "show" on the RHS
is different from the "show" on the LHS.
So my preference is to keep the status quo on this issue.
-Iavor
On Fri, Apr 25, 2008 at 7:09 AM, Claus Reinke
consider Haskell 98 report, section 4.3.2 "Instance Declarations":
The declarations d may contain bindings only for the class methods of C. 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. (This rule is identical to that used for subordinate names in export lists --- Section 5.2.) For example, this is legal, even though range is in scope only with the qualified name Ix.range. module A where import qualified Ix
instance Ix.Ix T where range = ...
i consider this confusing (see example at the end), but even worse is that the reference to 5.2 appears to rule out the use of qualified names when defining instance methods.
while this abbreviation of qualified names as unqualified names when unambiguous may be harmless in the majority of cases, it seems wrong that the more appropriate explicit disambiguation via qualified names is ruled out entirely. i submit that 4.3.2 should be amended so that qualified names are permitted when defining instance methods.
here's an example to show that the unambiguity holds only on the lhs of the method definition, and that the forced use of unqualified names can be confusing:
module QI where import Prelude hiding (Functor(..)) import qualified Prelude (Functor(..)) data X a = X a deriving Show instance Prelude.Functor X where fmap f (X a) = X (f a) where q = (reverse fmap,Prelude.fmap not [True],reverse QI.fmap) fmap = "fmap"
note that there are two unqualified uses of 'fmap' in the instance declaration, referring to different qualified names: - in the lhs, 'fmap' refers to 'Prelude.fmap', which isn't in scope unqualified, only qualified
- in the rhs, 'fmap' refers to 'QI.fmap'
claus
_______________________________________________ Haskell-prime mailing list Haskell-prime@haskell.org http://www.haskell.org/mailman/listinfo/haskell-prime

I think that the H98 change was a good one. Qualified names should only be used in _uses_ of variables (to disambiguate) and not in definitions because (hopefully) there is nothing to disambiguate in a definition.
i was not suggesting to disallow the unqualified def (even though it irks me as an unneccesary exception). only that i be allowed to use a qualified name to make the code less confusing to read (not to mention that the qualified name is in scope, the unqualified name isn't..).
By the way, method definitions already have a distinction between what is on the LHS and what is on the RHS. For example, consider the following instance:
instance Show a => Show (Maybe a) where show Nothing = "Nothing" show (Just a) = "Just " ++ show a
Here "show" is not a recursive function because the "show" on the RHS is different from the "show" on the LHS.
actually, both 'show's refer to the same thing here, method 'show' in class 'Show', and the disambiguation is via the types. now compare this with an instance from the class alias encoding i posted in the other thread: instance (FooBar a how, How (CFoo a) (Derived (CFooBar a))) => Foo a (Derived (CFooBar a)) where foo = foo is it obvious to you which foo refers to what? and though it looks similar to your example, the disambiguation is not via types (alone), but via what is in scope, plus the exception that i can/have to refer to something that isn't in scope on the left hand side. for reference (spoiler ahead;-), in this example: - 'Foo' is in scope as both 'FooAndBar.Foo' and 'Foo' - the lhs 'foo' is not in scope, but refers to 'FooAndBar.foo', which is in scope - the rhs 'foo' is in scope as both 'FooBar.foo' and 'foo', and comes from 'FooBar a how', not from any 'Foo' in the same module, we have: class How (CFooBar a) how => FooBar a how where foo :: a -> Bool foo _ = True bar :: Int -> a -> [a] here, the lhs 'foo' refers to 'FooBar.foo', which is also in scope as 'foo', and belongs to class 'FooBar'! so the left hand side 'foo's in the definitions refer to different things. i originally filed this as a bug, until Simon PJ kindly pointed me to the Haskell 98 report, which forces GHC to behave this way.. i guess i'll remember this oddity for a while, so i can live with it, but if it is irksome that the report allows me to refer to a name that is not in scope, it is far from obvious why it needs to prevent me from referring to a name that *is* in scope (Malcolm mentioned parsing ambiguities as the reason for this, but in my case, GHC recognizes the qualified name and *complains* about it). claus

Claus Reinke wrote:
i originally filed this as a bug, until Simon PJ kindly pointed me to the Haskell 98 report, which forces GHC to behave this way.. i guess i'll remember this oddity for a while, so i can live with it, but if it is irksome that the report allows me to refer to a name that is not in scope, it is far from obvious why it needs to prevent me from referring to a name that *is* in scope (Malcolm mentioned parsing ambiguities as the reason for this, but in my case, GHC recognizes the qualified name and *complains* about it).
Is it too hard to remember that in an instance declaration you can give bindings for methods of the class being instantiated only? To me, the oddity is that the method name must be in scope at all - this is a definition, not a reference, with a fixed set of things that can be defined. However, there is a consistency issue with record construction. The fields of a record construction are very much like the methods in an instance declaration: they are bindings for already-defined identifiers, and the set of available identifiers is known statically. In Haskell 98: aexp -> qcon { fbind1 , ... , fbindn } fbind -> qvar = exp so record fields can be referred to by qualified names, and in fact you are required to use the name by which the field is in scope - but GHC's DisambiguateRecordFields extension relaxes this so you're allowed to use the unqualified name. So, in summary: - Haskell 98 is completely inconsistent here. - GHC + DisambiguateRecordFields is a bit more consistent in that unqualified names are allowed in both settings, but still allows qualified names in one setting but not the other. So whatever we do we should be consistent. It would be slightly strange if record construction required the unqualified name, but record update required the qualified name, when the field name is only in scope qualified. So that indicates that we should allow either form in record construction (and instance declaration), i.e. Claus's suggestion + DisambiguateRecordFields. Cheers, Simon

Hello,
On Fri, Apr 25, 2008 at 3:00 PM, Simon Marlow
... It would be slightly strange if record construction required the unqualified name, but record update required the qualified name, when the field name is only in scope qualified. So that indicates that we should allow either form in record construction (and instance declaration), i.e. Claus's suggestion + DisambiguateRecordFields.
My preference would be to disallow qualified names in: (i) the method names of instances, (ii) record construction (C { l = e }), (iii) record patterns (C { l = p }). I think that this is consistent, and it easy easy to see what the labels refer to: in the case of instances, the method belongs to the class in question (which can be qualified), and in the case of records the label belongs to the specified constructor (which can also be qualified). As Simon points out, record updates still require qualified names but I don't think that there is an inconsistency there because I think of record updates as the application of a (oddly named) function, just like record selection is the application of a (normally named) function. Therefore, it makes sense that we may have to use qualified names to disambiguate which function we are referring to. -Iavor
participants (4)
-
Claus Reinke
-
Iavor Diatchki
-
Malcolm Wallace
-
Simon Marlow