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

Antoine Latter aslatter at gmail.com
Wed Jul 13 17:39:22 CEST 2011


On Wed, Jul 13, 2011 at 10:31 AM, Bertram Felgenhauer
<bertram.felgenhauer at googlemail.com> wrote:
> 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
>

The downside to this approach is that anyone trying to use the module
in GHCi (or use the module in a non-Cabal setting) will need to
manually hide one of the packages.

Does anyone know if there is a way to make Cabal auto-hide a package
after install without too much trickery? That might be more than you
want to do.

Antoine

> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>



More information about the Haskell-Cafe mailing list