Cabal vs Haskell [sic]

S. Alexander Jacobson alex at alexjacobson.com
Sun Apr 24 12:54:49 EDT 2005


On Fri, 22 Apr 2005, Simon Peyton-Jones wrote:
> Bottom line: the current story is pretty defensible.  I'm not sure that
> keeping names unique by implicitly using package-ids is worth the
> bother.

If the current Haskell story is that module names are top-level then 
it is incompatible with the current Cabal story.  The current Cabal 
story is that module names are implicitly qualified by package-ids. 
Cabal's build-depends tag says that some set of package names are 
required to interpret enclosed import declarations.  In other words, 
that the import declarations are themselves insufficient to identify 
the external modules required to interpret the enclosed modules.

I strongly prefer the current Haskell story to the current Cabal story 
for reasons enumerated at length in this thread*.  Hierarchical module 
names should need no qualification.  But, they do need some syntax to 
make those names easier on developers.  Here is my suggestion:

   New Syntax                             Translation
   ----------                             -----------
   module Name.Space Foo.M where          module Name.Space.Foo.M where
   import Bing.Baz                        import Name.Space.Bing.Baz
   import HAppS ACID                      import HAppS.ACID
   from HaXml.Text.XML
      import Types                        import HaXML.Text.XML.Types
      import Escape                       import HaXML.Text.XML.Escape
      import Pretty                       import HaXML.Text.XML.Pretty

We also need a standardized way to resolve hierarchical module names 
to interfaces and implementation, but that is a separate topic.

-Alex-

* Quick recap of arguments against Cabal:

   * namespace issues shouldn't be mixed with physical packaging issues
   * dev tools operate on source files/directories not packages
   * Cabal fragility with respect to changes in build-depends tag
   * Cabal fragility with respect to changes in modules of other packages
   * incompatibility between unqualified imports and Cabal versioning

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









On Sat, 23 Apr 2005, Simon Marlow wrote:

> On 23 April 2005 00:21, ross at soi.city.ac.uk wrote:
>
>> On Fri, Apr 22, 2005 at 11:28:21PM +0100, Simon Peyton-Jones wrote:
>>> And this observation points towards a simpler solution: rather than
>>> invisibly pre-pend the package name, just get the programmer to do
>>> so. So package P exposes a module called P.M and package Q exposes
>>> Q.M.  All P's internal modules are called P.something, and similarly
>>> for Q.  (We rely on some social mechanism for allocating new package
>>> names, as now.) Now of course you can import P.M and Q.M in a single
>>> module.
>>
>> This would obscure the hierarchy a bit.  A common current practice is
>> a variant of this: modules either have allocated names or their names
>> have the form
>>
>> 	allocated prefix + proper name + whatever you like
>>
>> e.g. Graphics.Rendering.OpenGL.GL.Texturing.Queries -- it seems to
>> work pretty well, and should scale, as long as the proper names are
>> distinct, e.g. package names or otherwise allocated.
>
> Right.  Also, prepending package names to module names to avoid the
> overlap restriction suffers from another difficulty: versioning.  You
> can't combine two versions of a package without including the version
> number in the module names of all the modules in the package.  But then
> you end up with source code that has to be edited when the version of a
> package changes, which is highly undesirable.
>
> IMO, it's a good thing that package names and versions are separate from
> module names.  It means we can (mostly) stick to the original aim of
> using the module hierarchy to reflect functionality, and not clutter it
> up with version numbers and other administravia.
>
> Cheers,
> 	Simon
> _______________________________________________
> Libraries mailing list
> Libraries at haskell.org
> http://www.haskell.org/mailman/listinfo/libraries
>



More information about the Libraries mailing list