[Haskell] Proposal: Relative Module Imports
Simon Marlow
simonmar at microsoft.com
Fri May 6 09:07:33 EDT 2005
On 03 May 2005 22:13, S. Alexander Jacobson wrote:
> Problem: We need a way to simplify module imports.
>
> Problem details:
>
> * Hierarchical module names are getting really long (including a
> functional area, a package name, and a module name).
>
> * People typically import multiple modules from areas close to each
> other in the hierarchical module namespace (especially in the case of
> intra-package imports).
>
> * Long module names are required even for non-exposed modules because
> a program may contain only one module with a given name (regardless of
> its visibility).
>
> Idea: Allow module relative imports in a manner that does not break
> any existing code.
>
> Proposal:
>
> * Use preceding dots to indicate that module name is relative
> * Use from keyword to specify a different relative base.
>
> Example:
>
> Dot relative syntax Translation
> ------------------- -----------
> module Text.Space.Foo.M where module Text.Space.Foo.M where
> import .M2 import Text.Space.Foo.M2 as M2
> import ..Bar.Baz import Text.Space.Bar.Baz as Bar.Baz
> import Data.Set import Data.Set
> from ...HaXML.XML
> import .Types import Text.HaXML.XML.Types as Types
> import .Escape import Text.HaXML.XML.Escape as
> Escape import .Pretty import Text.HaXML.XML.Pretty
> as Pretty
>
> I believe that the proposed syntax is much more concise and readable
> than the current equivalent.
I was sure something like this had been suggested before, and in fact
several similar schemes have. Here's a couple of starters:
http://www.haskell.org/pipermail/libraries/2001-February/000268.html
http://www.haskell.org/pipermail/libraries/2001-March/000322.html
Why haven't we ever implemented anything like this? A good question,
with no really good answer. I think it's a combination of
(a) the current situation isn't *really* hurting that much
(b) the current situation is *really* easy to describe and implement
(c) none of the proposed solutions are obviously the right thing
(e.g. the '.' prefixes look a little obscure, IMO).
and from my perspective:
(d) I hoped that something like grafting would provide a more
general solution.
Oh, and there was a recent proposal on the libraries list to allow
exporting of qualified names, which solves a similar/overlapping
problem:
http://www.haskell.org/pipermail/libraries/2005-March/003390.html
FWIW, I think this proposal ended in a reasonable result. It just needs
someone to implement it...
Cheers,
Simon
More information about the Haskell
mailing list