module namespaces with "Prelude"

Alastair Reid reid@cs.utah.edu
23 Apr 2002 17:09:18 +0100


[copied to original recipients along with the original bug report]

On ghc-bugs, Hal Daume reported problems with Hugs (and ghci) where
importing IO.hs causes a module called Bar.IO (i.e., Bar/IO.hs) to be
loaded - leading to the load to fail.

I've systematically tried every way of invoking Hugs (December 2001)
that makes sense (and a few that don't) and didn't find any that
worked.  Here's what I tried:

  cd /tmp
  mkdir Bar

  cat > Bar/Foo.hs
  module Bar.Foo where
  import IO

  cat > Bar/IO.hs
  module Bar.IO where

  hugs Bar.Foo
  # unexpected failure: confuses Bar.IO for IO

  hugs -P.: Bar.Foo
  # unexpected failure: confuses Bar.IO for IO

  hugs Bar.Foo.hs
  # expected failure: Bar.Foo.hs doesn't exist

  hugs Bar/Foo.hs
  # unexpected failure: confuses Bar.IO for IO

  cd Bar
  hugs Bar.Foo
  # expected failure: Can't find Bar.Foo

  hugs Foo
  # unexpected failure: confuses Bar.IO for IO

  hugs -P..: Bar.Foo
  # unexpected failure: confuses Bar.IO for IO
  
Did I do the wrong thing or do we need to tweak the loader?

(I didn't test with import chasing turned off - could that be it?)

-- 
Alastair Reid        reid@cs.utah.edu        http://www.cs.utah.edu/~reid/


It happens in Hugs, too, but somewhat differently.  Here's a test case.

Go to /foo and do mkdir Bar.  In Bar, create IO.hs and make its contents:

  module Bar.IO where

then also in Bar create Foo.hs

  module Bar.Foo where
  import IO

Then when in directory Bar load ghci (using 5.02.1) and load Bar.Foo and
you'll get:

  IO.hs: file name does not match module name `IO'

Quit ghci, load hugs and load Bar.Foo and you'll get:

  ERROR "Foo.hs" - Module "IO" not previously loaded

(worse things can happen in hugs -- if say Bar.IO imported Bar.Foo and
plain Bar.Foo imported plain old IO hugs will complain about cyclic
modules)

if you are in /foo instead of /foo/Bar when you load ghci and set paths
correctly it will work.

I don't know that this is exactly a bug in the software as much as it's
just somewhat underspecified what to do in these situations (I could be
wrong though).  IMO if you say in an import "import XXX" and it looks in
XXX.(l)hs and the module names is "YYY.XXX" it should keep looking instead
of just dying.  I don't really know what repurcussions this will have,
though.

--
Hal Daume III

 "Computer science is no more about computers    | hdaume@isi.edu
  than astronomy is about telescopes." -Dijkstra | www.isi.edu/~hdaume

On Mon, 22 Apr 2002, Simon Peyton-Jones wrote:

> Hal,
> 
> If your question is GHC-specific, send it to ghc-users not the haskell
> list.
> 
> And it would save time if you could be more specific.   Say what
> compiler
> you are using, enclose a test case, etc.  Otherwise we're all guessing.
> 
> Simon
> 
> | -----Original Message-----
> | From: Hal Daume III [mailto:hdaume@ISI.EDU] 
> | Sent: 23 April 2002 03:21
> | To: Alastair Reid
> | Cc: Haskell Mailing List
> | Subject: Re: module namespaces with "Prelude"
> | 
> | 
> | Ah, so the problem was that even though I had the superdir of 
> | NLP in my path, I was actually loading the modules in ghci 
> | from the NLP directory.  Still, I find this behavior odd, 
> | since even if I were in the NLP directory I could not import 
> | "NLP.Foo" simply as "Foo", I don't see why I should be 
> | allowed to (try to) import "NLP.Prelude" simply as "Prelude", 
> | thus messing stuff up...
> | 
> | --
> | Hal Daume III
> | 
> |  "Computer science is no more about computers    | hdaume@isi.edu
> |   than astronomy is about telescopes." -Dijkstra | www.isi.edu/~hdaume
> | 
> | On 23 Apr 2002, Alastair Reid wrote:
> | 
> | > 
> | > >>>>> "#Hal" == Hal Daume <hdaume@ISI.EDU> writes:
> | > 
> | > > I'm developing my package "NLP" for supporting common NLP 
> | functions 
> | > > and have a set of functions/datatypes that are common to 
> | almost all 
> | > > of my modules and I wanted to separate them off into an 
> | > > "NLP.Prelude" file, but this seems not to work.  One of 
> | my modules 
> | > > imports Prelude (the Haskell one) directly so I can hide a few 
> | > > definitions, but then it looks at NLP/Prelude.lhs and 
> | complains that 
> | > > the name of that module "NLP.Prelude" doesn't match "Prelude". 
> | > > SHould I simply name my module "NLP.NLPPrelude" or 
> | something (which 
> | > > is ugly, imo) or what?
> | > 
> | > The only change that hierarchial module namespaces make is that the 
> | > dots become a legal part of the name and that compilers have a 
> | > sensible way of mapping them onto filenames such as 
> | replacing dots by 
> | > slashes.  So, under the new scheme, these names are different and 
> | > unrelated
> | > 
> | >    Prelude   NLP.Prelude   User.Hal.Daume.NLP.Prelude
> | > 
> | > in the same way that these names were different and 
> | unrelated in the 
> | > old scheme.
> | > 
> | >    Prelude   NLP_Prelude   User_Hal_Daume_NLP_Prelude
> | > 
> | > If you are seeing something other than that, the problem is 
> | with your 
> | > compiler or the way you are using command line arguments to your 
> | > compiler (e.g., Hugs' import chasing mechanism has some interesting 
> | > interactions with hierarchial namespaces) and you should 
> | say which one 
> | > you're using and how you're using it.
> | > 
> | > --
> | > Alastair Reid
> | > 
> | 
> | _______________________________________________
> | Haskell mailing list
> | Haskell@haskell.org http://www.haskell.org/mailman/listinfo/haskell
> | 
>