[commit: ghc] ghc-8.0: ghc-boot: Don't use reexported-modules (e303d93)

git at git.haskell.org git at git.haskell.org
Mon May 16 17:54:32 UTC 2016


Repository : ssh://git@git.haskell.org/ghc

On branch  : ghc-8.0
Link       : http://ghc.haskell.org/trac/ghc/changeset/e303d93fecdcb748cd341ca69f803b8201a84f51/ghc

>---------------------------------------------------------------

commit e303d93fecdcb748cd341ca69f803b8201a84f51
Author: Ben Gamari <ben at smart-cactus.org>
Date:   Mon May 16 16:14:07 2016 +0200

    ghc-boot: Don't use reexported-modules
    
    This isn't supported by GHC 7.8


>---------------------------------------------------------------

e303d93fecdcb748cd341ca69f803b8201a84f51
 libraries/ghc-boot-th/ghc-boot-th.cabal.in        | 2 ++
 libraries/ghc-boot/GHC/LanguageExtensions/Type.hs | 5 +++++
 libraries/ghc-boot/GHC/Lexeme.hs                  | 5 +++++
 libraries/ghc-boot/ghc-boot.cabal.in              | 6 ++----
 4 files changed, 14 insertions(+), 4 deletions(-)

diff --git a/libraries/ghc-boot-th/ghc-boot-th.cabal.in b/libraries/ghc-boot-th/ghc-boot-th.cabal.in
index 3aebfbf..58d8961 100644
--- a/libraries/ghc-boot-th/ghc-boot-th.cabal.in
+++ b/libraries/ghc-boot-th/ghc-boot-th.cabal.in
@@ -20,6 +20,8 @@ description:    This library contains various bits shared between the @ghc@ and
 cabal-version:  >=1.10
 build-type:     Simple
 extra-source-files: changelog.md
+exposed:        False
+-- Since this is re-exported by ghc-boot
 
 source-repository head
     type:     git
diff --git a/libraries/ghc-boot/GHC/LanguageExtensions/Type.hs b/libraries/ghc-boot/GHC/LanguageExtensions/Type.hs
new file mode 100644
index 0000000..0b3fc92
--- /dev/null
+++ b/libraries/ghc-boot/GHC/LanguageExtensions/Type.hs
@@ -0,0 +1,5 @@
+{-# LANGUAGE PackageImports #-}
+
+module GHC.LanguageExtensions.Type ( module X ) where
+
+import "ghc-boot-th" GHC.LanguageExtensions.Type as X
diff --git a/libraries/ghc-boot/GHC/Lexeme.hs b/libraries/ghc-boot/GHC/Lexeme.hs
new file mode 100644
index 0000000..ab9310e
--- /dev/null
+++ b/libraries/ghc-boot/GHC/Lexeme.hs
@@ -0,0 +1,5 @@
+{-# LANGUAGE PackageImports #-}
+
+module GHC.Lexeme ( module X ) where
+
+import "ghc-boot-th" GHC.Lexeme as X
diff --git a/libraries/ghc-boot/ghc-boot.cabal.in b/libraries/ghc-boot/ghc-boot.cabal.in
index eed11e3..49b45c1 100644
--- a/libraries/ghc-boot/ghc-boot.cabal.in
+++ b/libraries/ghc-boot/ghc-boot.cabal.in
@@ -37,13 +37,11 @@ Library
 
     exposed-modules:
             GHC.LanguageExtensions
+            GHC.LanguageExtensions.Type
+            GHC.Lexeme
             GHC.PackageDb
             GHC.Serialized
 
-    reexported-modules:
-            GHC.LanguageExtensions.Type,
-            GHC.Lexeme
-
     build-depends: base       >= 4.7 && < 4.10,
                    binary     == 0.8.*,
                    bytestring == 0.10.*,



More information about the ghc-commits mailing list