I think it's an ill-thought-out exception. The point is this:
if a data constructor cannot appear on its own in a hiding
list, then you can't hide the constructor without hiding the
type. Currently you can say
import Maybe hiding( Just )
It would be simpler and more unifo
hello,
i was wondering if there was a reasong why "hiding imports" have different
semantics from "importing imports" and "exports". what i mean is, if one
writes:
module A(T) where
data T = T
only the type constructor T is exported. simillarly if i write:
modul
> In the current Report draft, the idea is that a hiding clause hides
> both qualified and unqualified names
>
> import Foo hiding( f )
> hides Foo.f as well as unqualified f.
>
> I think we all agreed that is a good change. But we (ahem, I) forgot
> to prop
Thomas Hallgren says:
| The following program was accepted by previous versions of
| GHC, but is not in GHC 5.02
|
| module HidingBug where
| import Prelude hiding (lookup)
|
| lookup env x = Prelude.lookup x env
|
| Instead, you get the error message
ecide something.
I'll adopt Simon & Manuel's view unless enough people yell.
Frankly, I don't think it is worth a hullabaloo.
Simon
| -Original Message-
| From: Manuel M. T. Chakravarty [mailto:[EMAIL PROTECTED]]
| Sent: 30 August 2001 07:20
| To: Simon Marlow
| Cc: [EMAI
"Simon Peyton-Jones" wrote
> | For instance if a have
> |
> | module A where
> | data T = A | B
> |
> | which entities are imported when I include the declaration
> |
> | import A hiding(T)
> |
> | in a module? The report is not clear about thi
See Section 4.4.2, after the table. Does that answer the qestion?
Simon
| -Original Message-
| From: S. Alexander Jacobson [mailto:[EMAIL PROTECTED]]
| Sent: 12 July 2001 15:03
| To: [EMAIL PROTECTED]
| Cc: [EMAIL PROTECTED]
| Subject: Re: Another question wrt hiding imports
I asked this a while ago and never got an answer. Asking again in
better context:
How do you control importing operator precedence?
Suppose that you have:
f x = 2 + 2 * x
And an imported module increases the precedence of (+).
You end up getting mangled.
My assumption is that the only way to
| For instance if a have
|
| module A where
| data T = A | B
|
| which entities are imported when I include the declaration
|
| import A hiding(T)
|
| in a module? The report is not clear about this but I would
| expect that
| this imports data constructors A and B into the current
After the recent discussion import hiding clauses in import
declarations, I was wondering what the meaning of hiding clauses is in
the case of algebraic data types (or classes).
For instance if a have
module A where
data T = A | B
which entities are imported when I include the
tion: What's the rationale of throwing
different namespaces together in the hiding clause?
Cheers,
Sven
--
Sven PanneTel.: +49/89/2178-2235
LMU, Institut fuer Informatik FAX : +49/89/2178-2211
LFE Programmier- und Modellierungsspra
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
> OK, then I'll rephrase my question: What's the rationale of throwing
> different namespaces together in the hiding clause?
Maybe they shouldn't be -- but if not, then
hiding( Ding )
would hide a type constructor or class Ding, but not a constructor Ding,
which
> 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
>
> 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
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 m
#
X-Comment5: #
Lennart Augustsson writes:
> What about this (sorry to keep complaining):
>
> module M where
> import Prelude hiding (ShowS)
> ...
>
> Is it legal? Well, that depends what the int
Original-Via: uk.ac.nsf; Sun, 15 Dec 91 05:18:50 GMT
What about this (sorry to keep complaining):
module M where
import Prelude hiding (ShowS)
...
Is it legal? Well, that depends what the interface file
for Prelude looks like. If it says (e.g.)
showChar
cerning import/export/hiding lists I'd like to raise.
Simon
Synonyms
At present a type synonym can be exported by saying
module A(T)
type T = Int
The type T is not abstract, because the full synonym is exported. If T
were declared with a data decl,
Original-Via: uk.ac.nsf; Fri, 25 Oct 91 18:27:51 BST
Original-Sender: [EMAIL PROTECTED]
John Peterson writes:
> import Prelude hiding(Dialogue)
> main _ = error "main"
>
> Actually I'm not sure how this program refers to 'Dialogue' at all.
ppens is you import a module, A, and it contains a value, say
x::T
and also a type synonym for T, say
type T = Int
but then you hide T on import. I.e.
import A hiding(T)
What is really important here is the actual interface to A. If the
x :: T occurs in the implementation,
Original-Via: uk.ac.nsf; Thu, 24 Oct 91 01:55:59 BST
What happens with the following program?
import Prelude hiding(Dialogue)
main _ = error "main"
Dialogue is not in the Core so it can be hidden, making main have an
unknown type.
-- Lennart
Original-Via: uk.ac.nsf; Wed, 23 Oct 91 23:39:10 BST
What happens is you import a module, A, and it contains a value, say
x::T
and also a type synonym for T, say
type T = Int
but then you hide T on import. I.e.
import A hiding(T)
The type synonym T is not imported any
Original-Via: uk.ac.nsf; Thu, 3 Oct 91 04:59:15 BST
If I have an interface
interface A where
data T = X | Y
and then do the following
module B where
import A hiding(T)
...
Does that mean that only the type is hidden, but not the constructors (X, Y)?
Or is it the same as
24 matches
Mail list logo