Re: curiosity, bug, or just dead code?

2007-09-10 Thread Stefan O'Rear
On Tue, Sep 11, 2007 at 12:02:26AM +0100, Claus Reinke wrote:
> 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.

This is a known bug in hugs; quoth the user's guide:

In Haskell 98, a missing export list means all names defined in the
current module. In Hugs, it is treated as "(module M)", where M is the
current module. This is almost the same, differing only when an imported
module is aliased as M.

Yes, this is a dark corner in H98.

Stefan


signature.asc
Description: Digital signature
___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: curiosity, bug, or just dead code?

2007-09-10 Thread Ross Paterson
On Tue, Sep 11, 2007 at 12:02:26AM +0100, Claus Reinke wrote:
> 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

All the GHC behaviour described above follows the Haskell 98 Report.
This treatment of omitted export lists is a documented bug in Hugs
(section 5.1.4 of the User's Guide).

On Mon, Sep 10, 2007 at 06:15:20PM -0700, Tim Chevalier wrote:
> This seems like a GHC bug to me. The Haskell 98 report says:
> "It is legal for more than one module in scope to use the same
> qualifier, provided that all names can still be resolved
> unambiguously." (section 5.3.3)

I think "all names" there was intended to mean all references in the
program (cf 5.5.2).  The module exports the locally defined length,
and there is no reference to T.length.
___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: curiosity, bug, or just dead code?

2007-09-10 Thread Tim Chevalier
On 9/10/07, Claus Reinke <[EMAIL PROTECTED]> wrote:
> 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?
>

This seems like a GHC bug to me. The Haskell 98 report says:
"It is legal for more than one module in scope to use the same
qualifier, provided that all names can still be resolved
unambiguously." (section 5.3.3)
and in this case, T.length is ambiguous as you say, so I think the
module should fail to typecheck.

Cheers,
Tim

-- 
Tim Chevalier * catamorphism.org * Often in error, never in doubt
"Investing in monopoly software is like investing in crack cocaine; it
is the consequential damages, rather than the immediate ones, that
kill you in the end." -- Kent Paul Dolan
___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


curiosity, bug, or just dead code?

2007-09-10 Thread Claus Reinke

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