> I'm totally
> confused. What does
> 
>    module M1(module M2)
>    import M2 hiding (H)
>    ...
> 
> exactly mean? 

The intention is this: M1 exports everything that M1 imports from M2.
Since H is not imported, it should not be exported either.  It does
not make any difference whether or not the things imported from M2 
were defined in M2 (M2 might have imported them and re-exported them).

The Report is deficient if this is not clear from the report.  Would
you like to suggest some specific clarified wording that could go in
the Report, so that it is clear?


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

GHC's behaviour is very strange.  I'll check into it.

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

That's a bug in Hugs -- but remember that Hugs does not claim to 
completely support Haskell's module system.

The is true for the other two cases.

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


Reply via email to