Hello again,

Wolfgang wrote

> 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 entire
>   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)
>     ...

Well, it's not that simple currently. Name clashes are only illegal if they
lead to unresolvable references. Thus if we have

module Main where

  sin x = x+1
  sin :: Float -> Float

  main = print (sin 1)

then that program is illegal since in "sin 1" we cannot say which "sin" it
is (from the Prelude or from Main). It is for this reason that it is legal
to use qualified names to refer to top level declarations. Thus, according
to the October release of the Report, the following is legal

module Main where

  sin x = x+1
  sin :: Float -> Float

  main = print (Prelude.sin 1, Main.sin 1)

since the qualified names are different, but in my proposal, one would
instead write

module Main where

  sin x = x+1
  sin :: Float -> Float

  main = print (Prelude.sin 1, sin 1)

to get the same effect. 

So I do not think that the Report is really inconsistent, it is just very
intricate. Shadowing imported names is a much easier rule to formulate and
understand, I think. And the same programs can be written as today.


> > 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 exported 
> from module M (module M) where { ... }

That's right (this refers to section 5.2, fifth numbered item). What is
the rationale behind requiring the qualified name to be visible also?

> who prefers to forbid shadowing of imported names :-)

Even by nested bindings?

/kff




_______________________________________________
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell

Reply via email to