
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