summaryrefslogtreecommitdiff
path: root/ghc/compiler
diff options
context:
space:
mode:
Diffstat (limited to 'ghc/compiler')
-rw-r--r--ghc/compiler/typecheck/TcSplice.lhs10
1 files changed, 8 insertions, 2 deletions
diff --git a/ghc/compiler/typecheck/TcSplice.lhs b/ghc/compiler/typecheck/TcSplice.lhs
index ffc9ec6ef2..24bb40cfbb 100644
--- a/ghc/compiler/typecheck/TcSplice.lhs
+++ b/ghc/compiler/typecheck/TcSplice.lhs
@@ -19,6 +19,7 @@ import qualified Language.Haskell.TH.Syntax as TH
import HsSyn ( HsBracket(..), HsExpr(..), HsSplice(..), LHsExpr, LHsDecl,
HsType, LHsType )
+import LoadIface ( loadHomeInterface )
import Convert ( convertToHsExpr, convertToHsDecls, convertToHsType, thRdrName )
import RnExpr ( rnLExpr )
import RnEnv ( lookupFixityRn, lookupSrcOcc_maybe, lookupImportedName )
@@ -126,8 +127,13 @@ tcBracket brack res_ty
tc_bracket :: HsBracket Name -> TcM TcType
tc_bracket (VarBr v)
- = tcMetaTy nameTyConName
- -- Result type is Var (not Q-monadic)
+ = do { loadHomeInterface msg v -- Reason: deprecation checking asumes the
+ -- home interface is loaded, and this is the
+ -- only way that is going to happen
+ ; tcMetaTy nameTyConName -- Result type is Var (not Q-monadic)
+ }
+ where
+ msg = ptext SLIT("Need interface for Template Haskell quoted Name")
tc_bracket (ExpBr expr)
= newTyFlexiVarTy liftedTypeKind `thenM` \ any_ty ->