[Haskell-cafe] Splitting Hackage Packages and re-exporting entire modules (with same module name)

Bertram Felgenhauer bertram.felgenhauer at googlemail.com
Wed Jul 13 17:31:10 CEST 2011


Antoine Latter wrote:
> If you give the module a new name in the new package then the old
> module can re-export all of the symbols in the new module.
> 
> In GHC I don't think there is a way for two packages to export the
> same module and have them be recognized as the same thing, as far as I
> know.

Right, but you don't have to rename the module if you use the
PackageImports extension. (Incidentally, this used by the haskell2010
ibrary, which is implemented in terms of base)

http://haskell.org/ghc/docs/latest/html/users_guide/syntax-extns.html#package-imports

So the following should work, assuming 'original' is a package exporting
the Foo.Bar module.

  {-# LANGUAGE PackageImports #-}
  module Foo.Bar (module Original) where

  import "original" Foo.Bar as Original

Best regards,

Bertram



More information about the Haskell-Cafe mailing list