Simon Peyton-Jones wrote:
> I wrote:
> > 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 strange thing about this part of Haskell 98 is that given

---------- Baz.hs --------------------------------------
module Baz where
newtype Ding = MakeDing Int
---------- Bar.hs --------------------------------------
module Bar(module Baz) where
import Baz hiding (Ding)
--------------------------------------------------------

the type Ding itself is not visible within Bar, but its constructor
MakeDing is. Consequently one can't give a signature for

   ding = MakeDing 123

in Bar (the exact opposite of an abstract type? :-).

Another question: What is visible in Bar when the name of MakeDing is
changed to Ding, too?

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.informatik.uni-muenchen.de/~Sven.Panne


Reply via email to