summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorSimon Peyton Jones <simonpj@microsoft.com>2013-11-22 09:40:10 +0000
committerSimon Peyton Jones <simonpj@microsoft.com>2013-11-22 16:39:17 +0000
commite9999500694e2da81b43657cb86c48c8d20266fa (patch)
tree2b1337daeef7f32068f246d7488c131fa91b33f9
parent7881488201629aa1ab36e3e0fbeb4d7b4b85bd91 (diff)
downloadhaskell-e9999500694e2da81b43657cb86c48c8d20266fa.tar.gz
Clarify what is in ic_tythings, and refactor TcRnDriver.setInteractiveContext
Previously there was a ton of cruft to do wtih "visible ids" in setInteractiveContext, but I made it all a lot simpler by providing a way to add to the typecheckers list of "global type variables", via TcEnv.tcExtendGlobalTyVars. This is much nicer.
-rw-r--r--compiler/main/HscTypes.lhs9
-rw-r--r--compiler/typecheck/TcRnDriver.lhs111
2 files changed, 53 insertions, 67 deletions
diff --git a/compiler/main/HscTypes.lhs b/compiler/main/HscTypes.lhs
index a3c6a65802..5e634c6dc0 100644
--- a/compiler/main/HscTypes.lhs
+++ b/compiler/main/HscTypes.lhs
@@ -1103,6 +1103,8 @@ data InteractiveContext
ic_rn_gbl_env :: GlobalRdrEnv,
-- ^ The cached 'GlobalRdrEnv', built by
-- 'InteractiveEval.setContext' and updated regularly
+ -- It contains everything in scope at the command line,
+ -- including everything in ic_tythings and ic_sys_vars
ic_tythings :: [TyThing],
-- ^ TyThings defined by the user, in reverse order of
@@ -1110,8 +1112,9 @@ data InteractiveContext
-- local variables in scope at that point
ic_sys_vars :: [Id],
- -- ^ Variables defined automatically by the system (e.g.
- -- record field selectors). See Notes [ic_sys_vars]
+ -- ^ Variables defined automatically from
+ -- ic_ty_things (e.g. record field selectors).
+ -- See Notes [ic_sys_vars]
ic_instances :: ([ClsInst], [FamInst]),
-- ^ All instances and family instances created during
@@ -1144,7 +1147,7 @@ data InteractiveContext
Note [ic_sys_vars]
~~~~~~~~~~~~~~~~~~
This list constains any Ids that arise from TyCons, Classes or
-instances defined interactively, but that are not given by
+instances defined interactively, but that are *not* given by
'implicitTyThings'. This includes record selectors, default methods,
and dfuns.
diff --git a/compiler/typecheck/TcRnDriver.lhs b/compiler/typecheck/TcRnDriver.lhs
index 5e5358051f..73f78b793c 100644
--- a/compiler/typecheck/TcRnDriver.lhs
+++ b/compiler/typecheck/TcRnDriver.lhs
@@ -62,6 +62,7 @@ import CoreSyn
import ErrUtils
import Id
import VarEnv
+import VarSet
import Module
import UniqFM
import Name
@@ -82,6 +83,7 @@ import Annotations
import Data.List ( sortBy )
import Data.IORef ( readIORef )
import Data.Ord
+import BasicTypes hiding( SuccessFlag(..) )
#ifdef GHCI
import TcType ( isUnitTy, isTauTy )
@@ -90,7 +92,6 @@ import TcMatches
import RnTypes
import RnExpr
import MkId
-import BasicTypes hiding( SuccessFlag(..) )
import TidyPgm ( globaliseAndTidyId )
import TysWiredIn ( unitTy, mkListTy )
#endif
@@ -1450,74 +1451,41 @@ setInteractiveContext hsc_env icxt thing_inside
-- This mimics the more selective call to hptInstances in tcRnImports
(home_insts, home_fam_insts) = hptInstances hsc_env (\_ -> True)
(ic_insts, ic_finsts) = ic_instances icxt
+ ty_things = ic_tythings icxt
- -- Note [GHCi temporary Ids]
- -- Ideally we would just make a type_env from ic_tythings
- -- and ic_sys_vars, adding in implicit things. However, Ids
- -- bound interactively might have some free type variables
- -- (RuntimeUnk things), and if we don't register these free
- -- TyVars as global TyVars then the typechecker will try to
- -- quantify over them and fall over in zonkQuantifiedTyVar.
- --
- -- So we must add any free TyVars to the typechecker's global
- -- TyVar set. This is what happens when the local environment
- -- is extended, so we use tcExtendGhciEnv below which extends
- -- the local environment with the Ids.
- --
- -- However, any Ids bound this way will shadow other Ids in
- -- the GlobalRdrEnv, so we have to be careful to only add Ids
- -- which are visible in the GlobalRdrEnv.
- --
- -- Perhaps it would be better to just extend the global TyVar
- -- list from the free tyvars in the Ids here? Anyway, at least
- -- this hack is localised.
- --
- -- Note [delete shadowed tcg_rdr_env entries]
- -- We also *delete* entries from tcg_rdr_env that we have
- -- shadowed in the local env (see above). This isn't strictly
- -- necessary, but in an out-of-scope error when GHC suggests
- -- names it can be confusing to see multiple identical
- -- entries. (#5564)
- --
- (tmp_ids, types_n_classes) = partitionWith sel_id (ic_tythings icxt)
- where sel_id (AnId id) = Left id
- sel_id other = Right other
-
- type_env = mkTypeEnvWithImplicits
- (map AnId (ic_sys_vars icxt) ++ types_n_classes)
-
- visible_tmp_ids = filter visible tmp_ids
- where visible id = not (null (lookupGRE_Name (ic_rn_gbl_env icxt)
- (idName id)))
+ type_env = mkTypeEnvWithImplicits
+ (map AnId (ic_sys_vars icxt) ++ ty_things)
con_fields = [ (dataConName c, dataConFieldLabels c)
- | ATyCon t <- types_n_classes
+ | ATyCon t <- ty_things
, c <- tyConDataCons t ]
in
- updGblEnv (\env -> env {
- tcg_rdr_env = delListFromOccEnv (ic_rn_gbl_env icxt)
- (map getOccName visible_tmp_ids)
- -- Note [delete shadowed tcg_rdr_env entries]
- , tcg_type_env = type_env
- , tcg_insts = ic_insts
- , tcg_inst_env = extendInstEnvList
- (extendInstEnvList (tcg_inst_env env) ic_insts)
- home_insts
- , tcg_fam_insts = ic_finsts
- , tcg_fam_inst_env = extendFamInstEnvList
- (extendFamInstEnvList (tcg_fam_inst_env env)
- ic_finsts)
- home_fam_insts
- , tcg_field_env = RecFields (mkNameEnv con_fields)
- (mkNameSet (concatMap snd con_fields))
- -- setting tcg_field_env is necessary to make RecordWildCards work
- -- (test: ghci049)
- , tcg_fix_env = ic_fix_env icxt
- , tcg_default = ic_default icxt
- }) $
-
- tcExtendGhciEnv visible_tmp_ids $ -- Note [GHCi temporary Ids]
- thing_inside
+ do { gbl_env <- getGblEnv
+ ; let gbl_env' = gbl_env {
+ tcg_rdr_env = ic_rn_gbl_env icxt
+ , tcg_type_env = type_env
+ , tcg_insts = ic_insts
+ , tcg_fam_insts = ic_finsts
+ , tcg_inst_env = extendInstEnvList
+ (extendInstEnvList (tcg_inst_env gbl_env) ic_insts)
+ home_insts
+ , tcg_fam_inst_env = extendFamInstEnvList
+ (extendFamInstEnvList (tcg_fam_inst_env gbl_env)
+ ic_finsts)
+ home_fam_insts
+ , tcg_field_env = RecFields (mkNameEnv con_fields)
+ (mkNameSet (concatMap snd con_fields))
+ -- setting tcg_field_env is necessary
+ -- to make RecordWildCards work (test: ghci049)
+ , tcg_fix_env = ic_fix_env icxt
+ , tcg_default = ic_default icxt }
+
+ ; lcl_env' <- tcExtendGlobalTyVars [ ATcId { tct_id = id, tct_closed = NotTopLevel }
+ | AnId id <- ty_things
+ , not (isEmptyVarSet (tyVarsOfType (idType id))) ]
+ -- See Note [Global tyvars]
+
+ ; setEnvs (gbl_env', lcl_env') thing_inside }
#ifdef GHCI
-- | The returned [Id] is the list of new Ids bound by this statement. It can
@@ -1574,6 +1542,16 @@ tcRnStmt hsc_env ictxt rdr_stmt
nest 2 (ppr id <+> dcolon <+> ppr (idType id))])
\end{code}
+Note [Global tyvars]
+~~~~~~~~~~~~~~~~~~~~
+Ids bound interactively (in ic_tythings) might have some free type
+variables (RuntimeUnk things), and if we don't register these free
+TyVars as global TyVars then the typechecker will try to quantify over
+them and fall over in zonkQuantifiedTyVar.
+
+So we must add any free TyVars to the typechecker's global
+TyVar set.
+
Note [Interactively-bound Ids in GHCi]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
The Ids bound by previous Stmts in GHCi are currently
@@ -1593,6 +1571,11 @@ The Ids bound by previous Stmts in GHCi are currently
to look at them, and :info expects the things it looks up to have
tidy types
+However note that TyCons, Classes, and even Ids bound by other top-level
+declarations in GHCi (eg foreign import, record selectors) currently get
+External Names, with :INTERACTIVE as the module name. This seems
+totally inconsistent to me.
+
--------------------------------------------------------------------------
Typechecking Stmts in GHCi