[Haskell] Re: Proposal: Relative Module Imports

S. Alexander Jacobson alex at alexjacobson.com
Thu May 5 11:52:29 EDT 2005


On Tue, 3 May 2005, Samuel Bronson wrote:
> Maybe something like
>
> from Text.HaXML.XML import (Types, Escape, Pretty)
>
> would be nice.

The problem with this one is that you need a way to express all the 
other stuff in import statements like "qualified" or "as", the 
imported list, etc.

If you don't like the dots and are willing to deal with having to type 
the current module hierarchy twice, a more verbose syntax would be

   Proposal			  Translation
   --------                        -----------
   module Foo.Bar.Baz.Bing where   module Foo.Bar.Baz.Bing where
   from Foo.Bar.Baz
      import Blip                  import Foo.Bar.Baz.Blip as Blip
   from Text.HaXML.XML
      import Types                 import Text.HaXML.XML.Types as Types
      import Escape                import Text.HaXML.XML.Escape as Escape

Not as tight as the prior syntax I proposed, but more readable and 
still a large improvement on the status quo.

Thoughts?


-Alex-
______________________________________________________________
S. Alexander Jacobson tel:917-770-6565 http://alexjacobson.com


On Tue, 3 May 2005, Samuel Bronson wrote:

> On 5/3/05, S. Alexander Jacobson <alex <at> alexjacobson.com> 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.
>
> This would be really nice, but I'm not sure I like the way you propose
> to do it. Those bare dots don't look very nice to me, and I really
> don't like the idea of having to count them... I'm not even sure I
> like the idea of imports relative to the current module.
>
> I almost want "import Text.HaXML.XML.{Types,Escape,Pretty}", but not
> quite. And that would not be nice for qualified imports, anyway.
>
> Maybe something like
>
> from Text.HaXML.XML import (Types, Escape, Pretty)
>
> would be nice.
>
> -- Sam
>
> _______________________________________________
> Haskell mailing list
> Haskell at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell
>



More information about the Haskell mailing list