[commit: ghc] wip/rae: Bring unbound tyvars into scope during reifyInstances. (89eb979)
git at git.haskell.org
git at git.haskell.org
Fri Oct 31 17:36:22 UTC 2014
Repository : ssh://git@git.haskell.org/ghc
On branch : wip/rae
Link : http://ghc.haskell.org/trac/ghc/changeset/89eb97936346f356a2db50ead41745a6f432bb15/ghc
>---------------------------------------------------------------
commit 89eb97936346f356a2db50ead41745a6f432bb15
Author: Richard Eisenberg <eir at cis.upenn.edu>
Date: Tue Oct 21 09:13:08 2014 -0400
Bring unbound tyvars into scope during reifyInstances.
Fix #9262.
>---------------------------------------------------------------
89eb97936346f356a2db50ead41745a6f432bb15
compiler/rename/RnSplice.lhs | 7 +++++++
compiler/typecheck/TcSplice.lhs | 30 ++++++++++++++++--------------
2 files changed, 23 insertions(+), 14 deletions(-)
diff --git a/compiler/rename/RnSplice.lhs b/compiler/rename/RnSplice.lhs
index c7b962e..94e3fc2 100644
--- a/compiler/rename/RnSplice.lhs
+++ b/compiler/rename/RnSplice.lhs
@@ -87,6 +87,13 @@ which is a bit inconsistent -- but there are a lot of them. We might
thereby get some bogus unused-import warnings, but we won't crash the
type checker. Not very satisfactory really.
+Note [Renamer errors]
+~~~~~~~~~~~~~~~~~~~~~
+It's important to wrap renamer calls in checkNoErrs, because the
+renamer does not fail for out of scope variables etc. Instead it
+returns a bogus term/type, so that it can report more than one error.
+We don't want the type checker to see these bogus unbound variables.
+
\begin{code}
rnSpliceGen :: Bool -- Typed splice?
-> (HsSplice Name -> RnM (a, FreeVars)) -- Outside brackets, run splice
diff --git a/compiler/typecheck/TcSplice.lhs b/compiler/typecheck/TcSplice.lhs
index e952a27..aebf430 100644
--- a/compiler/typecheck/TcSplice.lhs
+++ b/compiler/typecheck/TcSplice.lhs
@@ -523,14 +523,6 @@ tcTopSpliceExpr isTypedSplice tc_action
; zonkTopLExpr (mkHsDictLet (EvBinds const_binds) expr') }
\end{code}
-Note [Renamer errors]
-~~~~~~~~~~~~~~~~~~~~~
-It's important to wrap renamer calls in checkNoErrs, because the
-renamer does not fail for out of scope variables etc. Instead it
-returns a bogus term/type, so that it can report more than one error.
-We don't want the type checker to see these bogus unbound variables.
-
-
%************************************************************************
%* *
Annotations
@@ -1005,12 +997,22 @@ reifyInstances th_nm th_tys
<+> ppr_th th_nm <+> sep (map ppr_th th_tys)) $
do { loc <- getSrcSpanM
; rdr_ty <- cvt loc (mkThAppTs (TH.ConT th_nm) th_tys)
- ; (rn_ty, _fvs) <- checkNoErrs $ rnLHsType doc rdr_ty -- Rename to HsType Name
- -- checkNoErrs: see Note [Renamer errors]
- ; (ty, _kind) <- tcLHsType rn_ty
- ; ty <- zonkTcTypeToType emptyZonkEnv ty -- Substitute out the meta type variables
- -- In particular, the type might have kind
- -- variables inside it (Trac #7477)
+ -- #9262 says to bring vars into scope, like in HsForAllTy case
+ -- of rnHsTyKi
+ ; let (kvs, tvs) = extractHsTyRdrTyVars rdr_ty
+ tv_bndrs = userHsTyVarBndrs loc tvs
+ hs_tvbs = mkHsQTvs tv_bndrs
+ -- Rename to HsType Name
+ ; ((rn_tvbs, rn_ty), _fvs)
+ <- bindHsTyVars doc Nothing kvs hs_tvbs $ \ rn_tvbs ->
+ do { (rn_ty, fvs) <- rnLHsType doc rdr_ty
+ ; return ((rn_tvbs, rn_ty), fvs) }
+ ; (ty, _kind) <- tcHsTyVarBndrs rn_tvbs $ \ _tvs ->
+ tcLHsType rn_ty
+ ; ty <- zonkTcTypeToType emptyZonkEnv ty
+ -- Substitute out the meta type variables
+ -- In particular, the type might have kind
+ -- variables inside it (Trac #7477)
; traceTc "reifyInstances" (ppr ty $$ ppr (typeKind ty))
; case splitTyConApp_maybe ty of -- This expands any type synonyms
More information about the ghc-commits
mailing list