Module reexports at the package level

Simon Marlow marlowsd at gmail.com
Mon Oct 14 15:39:53 UTC 2013


On 04/10/2013 11:07, Joachim Breitner wrote:
> not sure if this is the right mailing list, as it affects GHC and Cabal,
> but can be used by all library authors. But it is a close fit.
>
> I’d like to propose Module re-reports on the package level, in order to
> make package reorganization easier on the users. For details, please see
> http://ghc.haskell.org/trac/ghc/wiki/ModuleReexports
> and for discussion, I suggest to use the trac ticket
> http://ghc.haskell.org/trac/ghc/ticket/8407
>
> Questions are:
>   * Is this useful enough?
>   * Is the design (syntax and semantics) good?

It's not clear whether it's worth doing this, because it doesn't add any 
new functionality, only convenience.  To re-export a module from a 
package you can already write a stub module like this:

   {-# LANGUAGE PackageImports #-}
   module Data.Foo (module X) where
   import "foo" Data.Foo as X

so the convenience would be not having to write (or automatically 
generate) all these stub modules.

You could implement package re-exports by automatically generating these 
stub modules, which would require only changes in Cabal.  Or you could 
implement them directly, which would need changes in lots of places - 
when I considered doing this before, I concluded that it probably wasn't 
worth it.

Cheers,
Simon


More information about the Libraries mailing list