[commit: ghc] wip/T9858-typeable-ben2: Fixes (ce20012)

git at git.haskell.org git at git.haskell.org
Sun Sep 13 04:20:02 UTC 2015


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

On branch  : wip/T9858-typeable-ben2
Link       : http://ghc.haskell.org/trac/ghc/changeset/ce20012c31b11d2f9816317ddbb58b89b27919d0/ghc

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

commit ce20012c31b11d2f9816317ddbb58b89b27919d0
Author: Ben Gamari <ben at smart-cactus.org>
Date:   Wed Sep 2 16:33:58 2015 +0200

    Fixes


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

ce20012c31b11d2f9816317ddbb58b89b27919d0
 compiler/basicTypes/DataCon.hs      |  3 +--
 compiler/coreSyn/CorePrep.hs        |  2 +-
 compiler/iface/IfaceSyn.hs          |  1 -
 compiler/prelude/PrelNames.hs       | 21 +++++++++++----------
 libraries/ghc-prim/GHC/IntWord64.hs |  3 ---
 5 files changed, 13 insertions(+), 17 deletions(-)

diff --git a/compiler/basicTypes/DataCon.hs b/compiler/basicTypes/DataCon.hs
index 7b8cfa4..0384ecc 100644
--- a/compiler/basicTypes/DataCon.hs
+++ b/compiler/basicTypes/DataCon.hs
@@ -17,6 +17,7 @@ module DataCon (
 
         -- ** Type construction
         mkDataCon, fIRST_TAG,
+        buildAlgTyCon,
 
         -- ** Type deconstruction
         dataConRepType, dataConSig, dataConInstSig, dataConFullSig,
@@ -46,8 +47,6 @@ module DataCon (
         promoteDataCon, promoteDataCon_maybe,
         promoteType, promoteKind,
         isPromotableType, computeTyConPromotability,
-
-        buildAlgTyCon
     ) where
 
 #include "HsVersions.h"
diff --git a/compiler/coreSyn/CorePrep.hs b/compiler/coreSyn/CorePrep.hs
index 8dc8a79..7b256a4 100644
--- a/compiler/coreSyn/CorePrep.hs
+++ b/compiler/coreSyn/CorePrep.hs
@@ -60,7 +60,7 @@ import MonadUtils       ( mapAccumLM )
 import Data.List        ( mapAccumL )
 import Control.Monad
 
-#if __GLASGOW_HASKELL__ < 709
+#if __GLASGOW_HASKELL__ < 710
 import Control.Applicative
 #endif
 
diff --git a/compiler/iface/IfaceSyn.hs b/compiler/iface/IfaceSyn.hs
index 4fed18c..d35aa8a 100644
--- a/compiler/iface/IfaceSyn.hs
+++ b/compiler/iface/IfaceSyn.hs
@@ -694,7 +694,6 @@ pprIfaceDecl ss (IfaceFamily { ifName = tycon, ifTyVars = tyvars
     pp_rhs IfaceBuiltInSynFamTyCon
       = ppShowIface ss (ptext (sLit "built-in"))
 
-
     pp_branches (IfaceClosedSynFamilyTyCon (Just (ax, brs)))
       = vcat (map (pprAxBranch (pprPrefixIfDeclBndr ss tycon)) brs)
         $$ ppShowIface ss (ptext (sLit "axiom") <+> ppr ax)
diff --git a/compiler/prelude/PrelNames.hs b/compiler/prelude/PrelNames.hs
index 28bfc33..6dc4b9d 100644
--- a/compiler/prelude/PrelNames.hs
+++ b/compiler/prelude/PrelNames.hs
@@ -320,9 +320,6 @@ basicKnownKeyNames
         -- Type-level naturals
         knownNatClassName, knownSymbolClassName,
 
-        -- Implicit parameters
-        ipClassName,
-
         -- Source locations
         callStackDataConName, callStackTyConName,
         srcLocDataConName,
@@ -1209,10 +1206,6 @@ knownNatClassName     = clsQual gHC_TYPELITS (fsLit "KnownNat") knownNatClassNam
 knownSymbolClassName :: Name
 knownSymbolClassName  = clsQual gHC_TYPELITS (fsLit "KnownSymbol") knownSymbolClassNameKey
 
--- Implicit parameters
-ipClassName :: Name
-ipClassName         = clsQual gHC_CLASSES (fsLit "IP") ipClassNameKey
-
 -- Source Locations
 callStackDataConName, callStackTyConName, srcLocDataConName :: Name
 callStackDataConName
@@ -1349,9 +1342,6 @@ knownSymbolClassNameKey = mkPreludeClassUnique 43
 ghciIoClassKey :: Unique
 ghciIoClassKey = mkPreludeClassUnique 44
 
-ipClassNameKey :: Unique
-ipClassNameKey = mkPreludeClassUnique 45
-
 {-
 ************************************************************************
 *                                                                      *
@@ -1577,6 +1567,14 @@ callStackTyConKey = mkPreludeTyConUnique 182
 typeRepTyConKey :: Unique
 typeRepTyConKey = mkPreludeTyConUnique 183
 
+-- Implicit Parameters
+ipTyConKey :: Unique
+ipTyConKey = mkPreludeTyConUnique 184
+
+ipCoNameKey :: Unique
+ipCoNameKey = mkPreludeTyConUnique 185
+
+
 ---------------- Template Haskell -------------------
 --      USES TyConUniques 200-299
 -----------------------------------------------------
@@ -1652,6 +1650,9 @@ callStackDataConKey, srcLocDataConKey :: Unique
 callStackDataConKey                     = mkPreludeDataConUnique 36
 srcLocDataConKey                        = mkPreludeDataConUnique 37
 
+ipDataConKey :: Unique
+ipDataConKey                            = mkPreludeDataConUnique 38
+
 trTyConDataConKey, trModuleDataConKey, trNameSDataConKey :: Unique
 trTyConDataConKey  = mkPreludeTyConUnique 185
 trModuleDataConKey = mkPreludeTyConUnique 186
diff --git a/libraries/ghc-prim/GHC/IntWord64.hs b/libraries/ghc-prim/GHC/IntWord64.hs
index 63989b8..52dc08e 100644
--- a/libraries/ghc-prim/GHC/IntWord64.hs
+++ b/libraries/ghc-prim/GHC/IntWord64.hs
@@ -23,11 +23,8 @@ module GHC.IntWord64 (
 #endif
     ) where
 
-import GHC.Types ()
-
 #if WORD_SIZE_IN_BITS < 64
 import GHC.Prim
-import GHC.CString ()  -- So that unpackCString# works
 
 foreign import ccall unsafe "hs_eqWord64"    eqWord64#     :: Word64# -> Word64# -> Int#
 foreign import ccall unsafe "hs_neWord64"    neWord64#     :: Word64# -> Word64# -> Int#



More information about the ghc-commits mailing list