[commit: ghc] wip/ttypeable: Move special tycons (59ea724)

git at git.haskell.org git at git.haskell.org
Sat Oct 1 21:34:14 UTC 2016


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

On branch  : wip/ttypeable
Link       : http://ghc.haskell.org/trac/ghc/changeset/59ea72428c70282cd9715b956cb8d37bc56c0018/ghc

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

commit 59ea72428c70282cd9715b956cb8d37bc56c0018
Author: Ben Gamari <ben at smart-cactus.org>
Date:   Wed Mar 16 17:51:01 2016 +0100

    Move special tycons


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

59ea72428c70282cd9715b956cb8d37bc56c0018
 compiler/prelude/TysPrim.hs      | 16 +++++++++++++++-
 compiler/typecheck/TcTypeable.hs | 18 +++---------------
 2 files changed, 18 insertions(+), 16 deletions(-)

diff --git a/compiler/prelude/TysPrim.hs b/compiler/prelude/TysPrim.hs
index 7430ec8..b8f57c4 100644
--- a/compiler/prelude/TysPrim.hs
+++ b/compiler/prelude/TysPrim.hs
@@ -31,6 +31,7 @@ module TysPrim(
 
         funTyCon, funTyConName,
         primTyCons,
+        primTypeableTyCons,
 
         charPrimTyCon,          charPrimTy,
         intPrimTyCon,           intPrimTy,
@@ -81,7 +82,7 @@ module TysPrim(
 #include "HsVersions.h"
 
 import {-# SOURCE #-} TysWiredIn
-  ( runtimeRepTy, liftedTypeKind
+  ( runtimeRepTyCon, runtimeRepTy, liftedTypeKind
   , vecRepDataConTyCon, ptrRepUnliftedDataConTyCon
   , voidRepDataConTy, intRepDataConTy
   , wordRepDataConTy, int64RepDataConTy, word64RepDataConTy, addrRepDataConTy
@@ -95,6 +96,7 @@ import {-# SOURCE #-} TysWiredIn
 
 import Var              ( TyVar, mkTyVar )
 import Name
+import NameEnv
 import TyCon
 import SrcLoc
 import Unique
@@ -157,6 +159,18 @@ primTyCons
 #include "primop-vector-tycons.hs-incl"
     ]
 
+-- | The names of the 'TyCon's which we define 'Typeable' bindings for
+-- explicitly in "Data.Typeable.Internal"
+-- and should not generate bindings for in "GHC.Types".
+--
+-- See Note [Mutually recursive representations of primitive types]
+primTypeableTyCons :: NameEnv TyConRepName
+primTypeableTyCons = mkNameEnv
+    [ (tYPETyConName, trTYPEName)
+    , (tyConName runtimeRepTyCon, trRuntimeRepName)
+    , (funTyConName, trArrowName)
+    ]
+
 mkPrimTc :: FastString -> Unique -> TyCon -> Name
 mkPrimTc fs unique tycon
   = mkWiredInName gHC_PRIM (mkTcOccFS fs)
diff --git a/compiler/typecheck/TcTypeable.hs b/compiler/typecheck/TcTypeable.hs
index cb79e08..061d22f 100644
--- a/compiler/typecheck/TcTypeable.hs
+++ b/compiler/typecheck/TcTypeable.hs
@@ -13,8 +13,7 @@ import IfaceEnv( newGlobalBinder )
 import TcEnv
 import TcRnMonad
 import PrelNames
-import TysPrim ( primTyCons, tYPETyConName, funTyConName )
-import TysWiredIn ( runtimeRepTyCon )
+import TysPrim ( primTyCons, primTypeableTyCons )
 import Id
 import Type
 import TyCon
@@ -22,7 +21,7 @@ import DataCon
 import Name( getOccName )
 import OccName
 import Module
-import NameSet
+import NameEnv
 import HsSyn
 import DynFlags
 import Bag
@@ -168,17 +167,6 @@ mkTypeableTyConBinds tycons
        ; gbl_env <- tcExtendGlobalValEnv tycon_rep_ids getGblEnv
        ; return (gbl_env `addTypecheckedBinds` tc_binds) }
 
--- | The names of the 'TyCon's which we handle explicitly in "Data.Typeable.Internal"
--- and should not generate bindings for in "GHC.Types".
---
--- See Note [Mutually recursive representations of primitive types]
-specialPrimTyCons :: NameSet
-specialPrimTyCons = mkNameSet
-    [ tYPETyConName
-    , tyConName runtimeRepTyCon
-    , funTyConName
-    ]
-
 -- | Generate bindings for the type representation of a wired-in TyCon defined
 -- by the virtual "GHC.Prim" module. This is where we inject the representation
 -- bindings for primitive types into "GHC.Types"
@@ -223,7 +211,7 @@ ghcPrimTypeableBinds stuff
     all_prim_tys :: [TyCon]
     all_prim_tys = [ tc' | tc <- funTyCon : primTyCons
                          , tc' <- tc : tyConATs tc
-                         , not $ tyConName tc' `elemNameSet` specialPrimTyCons
+                         , not $ tyConName tc' `elemNameEnv` primTypeableTyCons
                          ]
 
     mkBind :: TyCon -> LHsBinds Id



More information about the ghc-commits mailing list