Libraries and hierarchies

Manuel M T Chakravarty chak@cse.unsw.edu.au
Mon, 04 Aug 2003 11:54:35 +1000 (EST)


"Simon Marlow" <simonmar@microsoft.com> wrote,

> What follows is a proposal from Simon P.J. and myself, for solving some
> of the problems that have arisen with hierarchical modules in Haskell.
> 
> We think this is quite a nice solution: 
[..]

Yes, I think, it is nice, too.

> SOURCE CODE
> ~~~~~~~~~~~
> What about module names in the source code, and how are modules
> compiled?  Suppose I am compiling a package whose default site is
> Foo.Bar, and containing modules Foo.Bar.A.B, and Foo.Bar.A.C (assuming
> it is installed at the default site).  I put the source code in A/B.hs
> and A/C.hs, and the code would look like this:
> 
>     module A.B where
>     import A.C
> 
> The implementation must obey the following rule:
> 	When compiling a module belonging to a package, that package
> 	is temporarily grafted into the root of the module hierarchy.
> 
> This means that 'import A.C' will find the module A.C from the package
> being compiled.  If there is already a global module A.C, the package
> module "wins"; so the global module A.C is inaccessible.  (There could
> be some extra mechanism to get around this, if it seems important.)
> 
> Modules in other packages can be imported only by uttering their full
> path names in the global hierarchy (of the compiler that is compiling
> the package).
> 
> After installing the library, the tree of modules it contains will be
> grafted into the global hierarchy at possibly many places, and the
> modules can then only be imported by uttering their full path names in
> the global hierarchy.
> 
> Alternative design: modules in the current package could be specified
> explicitly, perhaps by prefixing them with '.'.  This would avoid the
> possibility of overlap between the current package and the global
> hierarchy, at the expense of having to add lots of extra '.'s.

I'd feel more comfortable with the alternative design.
Relative and absolute names are different things; hence, it
seems cleaner to distinguish them lexically.  Moreover, when
reading somebody else's code, it is helpful if it is easy to
distinguish absolute from relative names (eg, to know where
to look when trying to visit imported modules).

Cheers,
Manuel