[commit: ghc] wip/ttypeable: TcTypeable: Don't generate bindings for special primitive tycons (69dbfe0)
git at git.haskell.org
git at git.haskell.org
Fri Jul 8 14:31:15 UTC 2016
Repository : ssh://git@git.haskell.org/ghc
On branch : wip/ttypeable
Link : http://ghc.haskell.org/trac/ghc/changeset/69dbfe079ca32bf968e6dbb9acae7a484f11862a/ghc
>---------------------------------------------------------------
commit 69dbfe079ca32bf968e6dbb9acae7a484f11862a
Author: Ben Gamari <ben at smart-cactus.org>
Date: Wed Mar 16 15:34:03 2016 +0100
TcTypeable: Don't generate bindings for special primitive tycons
>---------------------------------------------------------------
69dbfe079ca32bf968e6dbb9acae7a484f11862a
compiler/typecheck/TcTypeable.hs | 19 +++++++++++++++++--
1 file changed, 17 insertions(+), 2 deletions(-)
diff --git a/compiler/typecheck/TcTypeable.hs b/compiler/typecheck/TcTypeable.hs
index 04d07d1..cb79e08 100644
--- a/compiler/typecheck/TcTypeable.hs
+++ b/compiler/typecheck/TcTypeable.hs
@@ -13,7 +13,8 @@ import IfaceEnv( newGlobalBinder )
import TcEnv
import TcRnMonad
import PrelNames
-import TysPrim ( primTyCons )
+import TysPrim ( primTyCons, tYPETyConName, funTyConName )
+import TysWiredIn ( runtimeRepTyCon )
import Id
import Type
import TyCon
@@ -21,6 +22,7 @@ import DataCon
import Name( getOccName )
import OccName
import Module
+import NameSet
import HsSyn
import DynFlags
import Bag
@@ -166,6 +168,17 @@ 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"
@@ -209,7 +222,9 @@ ghcPrimTypeableBinds stuff
where
all_prim_tys :: [TyCon]
all_prim_tys = [ tc' | tc <- funTyCon : primTyCons
- , tc' <- tc : tyConATs tc ]
+ , tc' <- tc : tyConATs tc
+ , not $ tyConName tc' `elemNameSet` specialPrimTyCons
+ ]
mkBind :: TyCon -> LHsBinds Id
mkBind = mk_typeable_binds stuff
More information about the ghc-commits
mailing list