consider this module, which is accepted by ghci-6.6.1:

   module T where
   import qualified Prelude as T(length)
   import Prelude(length)
   length = 0

there is no way to refer to either length, as both 'length' and 'T.length' are ambiguous (ghci complains on uses of either name). but is it a bug?

then again, everything is implicitly exported, and there are two possible 'T.length'.. (hugs [20051031] complains about conflicting exports, on loading T).

now for the good part:

   module Q where
   import T
   main = print T.length

loads fine, and running main returns 0.

   Ok, modules loaded: Q, T.
   *Q> main
   0

so this must be a bug, right? or a matter of interpretation?

not everything is exported implicitly: imported items, whether unqualified or qualified and renamed to share the current module as qualifier are not exported by default. and changing
   module T where

to
   module T(module T) where

leads to conflicting export errors on load in ghci.

currently, i think ghci is right, and hugs is wrong (note that
my hugs is rather old, though), but it wasn't what i expected.

claus


_______________________________________________
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to