After some experiments and a look into the Haskell 98 report I'm totally
confused. What does

   module M1(module M2)
   import M2 hiding (H)
   ...

exactly mean? GHC's and Hugs' behaviour in different cases is
inconsistent, and the report is unclear. So here are the tests:

The module Baz stays unchanged in all examples:
---------- Baz.hs --------------------------------------
module Baz where
newtype Ding = MakeDing Int
newtype Dong = MakeDong Char
--------------------------------------------------------

The following modules are similar to the ones which caused my initial
confusion:
---------- Bar.hs --------------------------------------
module Bar(module Baz) where
import Baz hiding (Ding)
---------- Foo.hs --------------------------------------
module Foo where
import Bar
data D = MakeD Dong deriving Show
data E = MakeE Bool deriving Show
--------------------------------------------------------
GHC compiles this happily, it even does not complain about a missing
Show instance for Dong. But strangely enough, E's Show instance is
*not* exported. This made me *really* crazy in a large program.  %-{
Hugs correctly complains about the missing Show instance of Dong.

Hiding only the type name still exports the constructor:
---------- Bar.hs --------------------------------------
module Bar(module Baz) where
import Baz hiding (Ding)
---------- Foo.hs --------------------------------------
module Foo where
import Bar
ding = MakeDing 123
--------------------------------------------------------
GHC compiles this happily again, but refuses the attempt to add the
signature ding::Ding (Type constructor or class not in scope:
`Ding'). Hugs accepts even the signature, despite the hiding clause.

Hiding the type name and the constructor made the behaviour a little
bit more predictable:
---------- Bar.hs --------------------------------------
module Bar(module Baz) where
import Baz hiding (Ding(..))
---------- Foo.hs --------------------------------------
module Foo where
import Bar
data C = MakeC Ding deriving Show
data D = MakeD Dong deriving Show
data E = MakeE Bool deriving Show
--------------------------------------------------------
GHC tells me "Type constructor or class not in scope: `Ding'" again
and Hugs needs a Show instance for Ding.

But Hugs does not care about the (..)-part:
---------- Bar.hs --------------------------------------
module Bar(module Baz) where
import Baz hiding (Ding(..))
---------- Foo.hs --------------------------------------
module Foo where
import Bar
ding :: Ding
ding = MakeDing 123
--------------------------------------------------------
GHC complains about Ding and MakeDing not being in scope (as
expected), while Hugs is completely happy with this.

Can somebody elaborate on this?

Cheers,
   Sven
-- 
Sven Panne                                        Tel.: +49/89/2178-2235
LMU, Institut fuer Informatik                     FAX : +49/89/2178-2211
LFE Programmier- und Modellierungssprachen              Oettingenstr. 67
mailto:[EMAIL PROTECTED]            D-80538 Muenchen
http://www.pms.informatik.uni-muenchen.de/mitarbeiter/panne


Reply via email to