module namespaces with "Prelude"
Johan Nordlander
nordland@cs.chalmers.se
Thu, 25 Apr 2002 01:07:39 +0200
On Tuesday, April 23, 2002, at 06:09 , Alastair Reid wrote:
>
> [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/
We're approaching a dark corner here, where the principle of a
single, hierarchical module namespace clashes with the
established idea of searching for modules along an externally
defined directory path.
In Hugs, and I think in ghci as well, the implementation of
hierarchical modules allows a module hierarchy with several
roots. Not only is it possible to define multiple roots in the
search path, the current directory is also an implicit root, and
if a module is being imported by another module, the directory
where the importing module was found is another one.
Now, since there's nothing that prevents the directory
hierarchies starting at these roots from overlapping, we have a
potential for ambiguity when we want to map module names to
filenames. In the examples above, the module defined in
Bar/IO.hs is given the name Bar.IO. However, according to the
way we map module names onto files, Bar/IO.hs will also appear
to be a valid implementation of module IO, since the directory
Bar is implicitly an alternative root to the module hierarchy.
One solution would then be to start parsing Bar/IO.hs until we
can determine if its module name matches the name suggested by
its file name and the current root. However, implementing such
a check seems like a big hack, when the real problem is the
questionable support for multiple roots. It's also not a
trivial thing to do, since we would need to backtrack from
parsing and continue the module search in case of a name
mismatch.
One might also argue that the problem is these extra roots that
are implicitly added to the search path. Arguably, dropping the
current directory and the directory of the importing module from
the search path would solve the problems listed above. But
there's still a possibility to list overlapping directories in
the search path proper, so dropping the implicit directories
wouldn't really cure the disease, only make it less prominent.
Furthermore, this feature is there because it has been in Hugs
for a long time, and many people seem to rely on it quite
heavily.
Still, the current status is unsatisfactory. Of the two ways
forward pointed at above, dropping the implicit roots and
putting the burden on the programmer to define consistent search
paths is by far the easiest one to implement. However, one
should bear in mind that this will disturb many people,
particularly those who don't use hierarchical modules. Doing
speculative parsing of module headers looks more robust, but it
would indeed be a complicated way of resolving ambiguities that
shouldn't be there in the first place. A fully satisfactory
solution can't be obtained, I think, unless we make the whole
module hierarchy single-rooted. That would make it harder to
integrate local modules with the standard libraries, though, and
would probably need some kind of module "mounting" facility to
be practical. However, I don't believe we're ready for such an
experiment just yet.
All in all, dropping all implicit directories from the search
path gets my vote.
-- Johan