X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=ghc%2Fcompiler%2Ftypecheck%2FTcSplice.lhs;h=34e03945fbe5a2c9c0acbaf9cbe27e230c1d8eb6;hb=380148608fa354ac972d45aa933400a1a5c4dd7f;hp=47b2f6c7d15c6f66521dfe0aa4842ded8760f47f;hpb=d068f518de21a7a21613eb5a34c5eac8517bef75;p=ghc-hetmet.git diff --git a/ghc/compiler/typecheck/TcSplice.lhs b/ghc/compiler/typecheck/TcSplice.lhs index 47b2f6c..34e0394 100644 --- a/ghc/compiler/typecheck/TcSplice.lhs +++ b/ghc/compiler/typecheck/TcSplice.lhs @@ -41,7 +41,7 @@ import NameEnv ( lookupNameEnv ) import HscTypes ( lookupType, ExternalPackageState(..), emptyModDetails ) import OccName import Var ( Id, TyVar, idType ) -import Module ( moduleUserString ) +import Module ( moduleString ) import TcRnMonad import IfaceEnv ( lookupOrig ) import Class ( Class, classExtraBigSig ) @@ -56,7 +56,7 @@ import IdInfo ( GlobalIdDetails(..) ) import TysWiredIn ( mkListTy ) import DsMeta ( expQTyConName, typeQTyConName, decTyConName, qTyConName, nameTyConName ) import ErrUtils ( Message ) -import SrcLoc ( noLoc, unLoc, getLoc ) +import SrcLoc ( SrcSpan, noLoc, unLoc, getLoc ) import Outputable import Unique ( Unique, Uniquable(..), getKey, mkUniqueGrimily ) @@ -149,6 +149,9 @@ tc_bracket (DecBr decls) ; return (mkAppTy q_ty (mkListTy decl_ty)) -- Result type is Q [Dec] } + +tc_bracket (PatBr _) + = failWithTc (ptext SLIT("Tempate Haskell pattern brackets are not supported yet")) \end{code} @@ -207,14 +210,8 @@ tcTopSplice expr res_ty -- Run the expression traceTc (text "About to run" <+> ppr zonked_q_expr) `thenM_` - runMetaE zonked_q_expr `thenM` \ simple_expr -> + runMetaE convertToHsExpr zonked_q_expr `thenM` \ expr2 -> - let - -- simple_expr :: TH.Exp - - expr2 :: LHsExpr RdrName - expr2 = convertToHsExpr (getLoc expr) simple_expr - in traceTc (text "Got result" <+> ppr expr2) `thenM_` showSplice "expression" @@ -297,12 +294,8 @@ kcTopSpliceType expr -- Run the expression ; traceTc (text "About to run" <+> ppr zonked_q_expr) - ; simple_ty <- runMetaT zonked_q_expr + ; hs_ty2 <- runMetaT convertToHsType zonked_q_expr - ; let -- simple_ty :: TH.Type - hs_ty2 :: LHsType RdrName - hs_ty2 = convertToHsType (getLoc expr) simple_ty - ; traceTc (text "Got result" <+> ppr hs_ty2) ; showSplice "type" zonked_q_expr (ppr hs_ty2) @@ -333,11 +326,8 @@ tcSpliceDecls expr -- Run the expression ; traceTc (text "About to run" <+> ppr zonked_q_expr) - ; simple_expr <- runMetaD zonked_q_expr + ; decls <- runMetaD convertToHsDecls zonked_q_expr - -- simple_expr :: [TH.Dec] - -- decls :: [RdrNameHsDecl] - ; decls <- handleErrors (convertToHsDecls (getLoc expr) simple_expr) ; traceTc (text "Got result" <+> vcat (map ppr decls)) ; showSplice "declarations" zonked_q_expr @@ -359,21 +349,25 @@ tcSpliceDecls expr %************************************************************************ \begin{code} -runMetaE :: LHsExpr Id -- Of type (Q Exp) - -> TcM TH.Exp -- Of type Exp -runMetaE e = runMeta e - -runMetaT :: LHsExpr Id -- Of type (Q Type) - -> TcM TH.Type -- Of type Type -runMetaT e = runMeta e - -runMetaD :: LHsExpr Id -- Of type Q [Dec] - -> TcM [TH.Dec] -- Of type [Dec] -runMetaD e = runMeta e - -runMeta :: LHsExpr Id -- Of type X - -> TcM t -- Of type t -runMeta expr +runMetaE :: (SrcSpan -> TH.Exp -> Either Message (LHsExpr RdrName)) + -> LHsExpr Id -- Of type (Q Exp) + -> TcM (LHsExpr RdrName) +runMetaE = runMeta + +runMetaT :: (SrcSpan -> TH.Type -> Either Message (LHsType RdrName)) + -> LHsExpr Id -- Of type (Q Type) + -> TcM (LHsType RdrName) +runMetaT = runMeta + +runMetaD :: (SrcSpan -> [TH.Dec] -> Either Message [LHsDecl RdrName]) + -> LHsExpr Id -- Of type Q [Dec] + -> TcM [LHsDecl RdrName] +runMetaD = runMeta + +runMeta :: (SrcSpan -> th_syn -> Either Message hs_syn) + -> LHsExpr Id -- Of type X + -> TcM hs_syn -- Of type t +runMeta convert expr = do { hsc_env <- getTopEnv ; tcg_env <- getGblEnv ; this_mod <- getModule @@ -392,11 +386,21 @@ runMeta expr { -- Coerce it to Q t, and run it -- Running might fail if it throws an exception of any kind (hence tryAllM) -- including, say, a pattern-match exception in the code we are running - either_tval <- tryAllM (TH.runQ (unsafeCoerce# hval)) + -- + -- We also do the TH -> HS syntax conversion inside the same + -- exception-cacthing thing so that if there are any lurking + -- exceptions in the data structure returned by hval, we'll + -- encounter them inside the tryALlM + either_tval <- tryAllM $ do + { th_syn <- TH.runQ (unsafeCoerce# hval) + ; case convert (getLoc expr) th_syn of + Left err -> do { addErrTc err; return Nothing } + Right hs_syn -> return (Just hs_syn) } ; case either_tval of - Left exn -> failWithTc (mk_msg "run" exn) - Right v -> returnM v + Right (Just v) -> return v + Right Nothing -> failM -- Error already in Tc monad + Left exn -> failWithTc (mk_msg "run" exn) -- Exception }}} where mk_msg s exn = vcat [text "Exception when trying to" <+> text s <+> text "compile-time code:", @@ -415,7 +419,7 @@ instance TH.Quasi (IOEnv (Env TcGblEnv TcLclEnv)) where qReport True msg = addErr (text msg) qReport False msg = addReport (text msg) - qCurrentModule = do { m <- getModule; return (moduleUserString m) } + qCurrentModule = do { m <- getModule; return (moduleString m) } qReify v = reify v qRecover = recoverM @@ -471,8 +475,8 @@ reify th_name ppr_ns (TH.Name _ (TH.NameG TH.VarName mod)) = text "var" lookupThName :: TH.Name -> TcM Name -lookupThName th_name - = do { let rdr_name = thRdrName guessed_ns th_name +lookupThName th_name@(TH.Name occ flavour) + = do { let rdr_name = thRdrName guessed_ns occ_str flavour -- Repeat much of lookupOccRn, becase we want -- to report errors in a TH-relevant way @@ -490,9 +494,9 @@ lookupThName th_name } where -- guessed_ns is the name space guessed from looking at the TH name - guessed_ns | isLexCon occ_fs = OccName.dataName - | otherwise = OccName.varName - occ_fs = mkFastString (TH.nameBase th_name) + guessed_ns | isLexCon (mkFastString occ_str) = OccName.dataName + | otherwise = OccName.varName + occ_str = TH.occString occ tcLookupTh :: Name -> TcM TcTyThing -- This is a specialised version of TcEnv.tcLookup; specialised mainly in that @@ -658,8 +662,8 @@ reifyName thing -- have free variables, we may need to generate NameL's for them. where name = getName thing - mod = moduleUserString (nameModule name) - occ_str = occNameUserString occ + mod = moduleString (nameModule name) + occ_str = occNameString occ occ = nameOccName name mk_varg | OccName.isDataOcc occ = TH.mkNameG_d | OccName.isVarOcc occ = TH.mkNameG_v