Scope of imported names
Wolfgang Lux
wlux@uni-muenster.de
Mon, 22 Oct 2001 12:44:14 +0200
Karl-Filip Faxen wrote
> Section 5.5.2 relates to name clashes and has an interesting example
> towards the end:
> =
> module F where
> =
> sin :: Float -> Float
> sin x =3D (x::Float)
> =
> f x =3D Prelude.sin (F.sin x)
> =
> where the type signature refers to the local "sin" rather than the impo=
rted
> although none of them is visible unqualified. These rules are quite tri=
cky
> to understand, I think. They are also different in spirit from the rule=
s
The Haskell report seems to be inconsistent here (once again). In the =
beginning of section 5.3 it says =
Imported names serve as top level declarations: they scope over the ent=
ire
body of the module but may be shadowed by local NON-TOP-LEVEL bindings.=
Thus, the definition of sin in module F is invalid because another =
top-level declaration of sin already exists due to the (implicit) =
import of the Prelude. In order to redefine sin locally the imported =
definition should be hidden and imported only qualified:
module F where
import Prelude hiding(sin)
import qualified Prelude(sin)
...
> for instance declarations in section 4.3.2 where the binding occurrence=
s
> for the names of the methods must be qualified if the unqualified metho=
d =
> name is not in scope. In the "sin" example it is allowed to resolve the=
=
> name clash using the "extra" knowledge that it is illegal to provide ty=
pe
> signatures for imported names, wheras in the case for instance declarat=
ions
> we may not use the corresponding "extra" knowledge that only methods in=
=
> the instance'd class may be bound by the bindings.
> =
> What I'm driving at is this: I propose that top level bindings shadow
> imported names and that qualified names can not be used to refer to
> declarations in the same module. =
The second part is going to conflict with the revised report which relies=
=
on the qualified names of entities in order to specify which entites expo=
rted =
from module M (module M) where { ... }
> /kff
> =
> who feels very relieved at having come out publicly in favour of shadow=
ing
> imported names ;-)
Wolfgang
who prefers to forbid shadowing of imported names :-)
--
Wolfgang Lux Phone: +49-251-83-38263
Institut fuer Wirtschaftinformatik FAX: +49-251-83-38259
Universitaet Muenster Email: wlux@uni-muenster.de