entities imported from multiple modules
Stavros Tripakis
Stavros.Tripakis@imag.fr
Wed, 4 Dec 2002 14:50:02 +0100 (MET)
Hi,
I would like to report what I believe is a difference of Hugs
with the Haskell'98 report, in particular the section :
http://haskell.cs.yale.edu/onlinereport/modules.html#sect5
In this section, it is mentionned that
"There is no reference to y, so it is not erroneous that distinct
entities called y are exported by both B and C. An error is only
reported if y is actually mentioned. "
However, Hugs complains:
Prelude> :load A.hs
Reading file "A.hs":
Reading file "B.hs":
Reading file "D.hs":
Reading file "B.hs":
Reading file "C.hs":
Reading file "A.hs":
ERROR A.hs - Entity "y" imported from module "B" already defined in module "C"
I consider this a bug (perhaps serious, since the whole point of
modules is name scoping), am I wrong?
Please find below the files A.hs, B.hs, C.hs, D.hs
Thank you in advance for your reply,
Best regards
Stavros
PS. I am a newcomer to Haskell, and I enjoy it a lot !!!
cougourde (Haskell) 352. cat A.hs
module A where
import B
import C
tup = (b, c, d, x)
cougourde (Haskell) 353. cat B.hs
module B( d, b, x, y ) where
import D
x = "x"
y = "y"
b = "b"
cougourde (Haskell) 354. cat C.hs
module C( d, c, x, y ) where
import D
x = "x"
y = "y"
c = "c"
cougourde (Haskell) 355. cat D.hs
module D( d ) where
d = "d"