modules and re-export

Sigbjorn Finne sigbjorn_finne@hotmail.com
Wed, 21 Mar 2001 22:14:58 +0100


Peter Thiemann thiemann@informatik.uni-freiburg.de writes:
>
> I have a little question about the following two modules. Suppose you
> want to write your own variant of the prelude that redefines a couple
> of names but leaves all the rest unchanged. The Haskell report says
> that the following should work:
> ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
> module BUG2A (module BUG2A, module Prelude) where
>
> import Prelude hiding (head)
>
> head = "HEAD"
> ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
....
> ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
> module BUG2B where
>
> import qualified Prelude
> import BUG2A
> ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
>
> Unfortunately, this does not behave as (I think) it should:
>
> Reading file "BUG2B.hs":
>
Parsing.....................................................................
...
> ERROR "BUG2B.hs": Entity "head" imported from module "BUG2A" already
> defined in module "Prelude"
>
> However, this should be legal from my reading of the report.

Hi Peter,

yep, that's right, and it is a known wrinkle in Hugs' implementation of
modules.
I submitted a source fix which addresses just this a couple of weeks ago,

  http://haskell.cs.yale.edu/pipermail/hugs-bugs/2001-March/000184.html

hopefully it will be included in future releases of Hugs98.

hth
--sigbjorn