[commit: ghc] wip/generalized-arrow: Move special tycons (0a6cd5b)
git at git.haskell.org
git at git.haskell.org
Mon Mar 21 17:11:28 UTC 2016
Repository : ssh://git@git.haskell.org/ghc
On branch : wip/generalized-arrow
Link : http://ghc.haskell.org/trac/ghc/changeset/0a6cd5b1a58c8222b970d3efc222f97ce748be09/ghc
>---------------------------------------------------------------
commit 0a6cd5b1a58c8222b970d3efc222f97ce748be09
Author: Ben Gamari <ben at smart-cactus.org>
Date: Wed Mar 16 17:51:01 2016 +0100
Move special tycons
>---------------------------------------------------------------
0a6cd5b1a58c8222b970d3efc222f97ce748be09
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 ce25c30..34f020c 100644
--- a/compiler/prelude/TysPrim.hs
+++ b/compiler/prelude/TysPrim.hs
@@ -27,6 +27,7 @@ module TysPrim(
funTyCon, funTyConName,
primTyCons,
+ primTypeableTyCons,
charPrimTyCon, charPrimTy,
intPrimTyCon, intPrimTy,
@@ -79,7 +80,7 @@ module TysPrim(
#include "HsVersions.h"
import {-# SOURCE #-} TysWiredIn
- ( runtimeRepTy, liftedTypeKind
+ ( runtimeRepTyCon, runtimeRepTy, liftedTypeKind
, vecRepDataConTyCon, ptrRepUnliftedDataConTyCon
, voidRepDataConTy, intRepDataConTy
, wordRepDataConTy, int64RepDataConTy, word64RepDataConTy, addrRepDataConTy
@@ -93,6 +94,7 @@ import {-# SOURCE #-} TysWiredIn
import Var ( TyVar, KindVar, mkTyVar )
import Name
+import NameEnv
import TyCon
import SrcLoc
import Unique
@@ -155,6 +157,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 b59489d..d0360f5 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
@@ -166,17 +165,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"
@@ -221,7 +209,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