Skip to content

Commit

Permalink
Add support for Template Haskell module finalizers.
Browse files Browse the repository at this point in the history
Template Haskell module finalizers are run after a module is type checked.
  • Loading branch information
mainland committed Jun 27, 2013
1 parent 56405e2 commit 646b630
Show file tree
Hide file tree
Showing 5 changed files with 34 additions and 6 deletions.
11 changes: 10 additions & 1 deletion compiler/typecheck/TcRnDriver.lhs
Expand Up @@ -22,7 +22,7 @@ module TcRnDriver (
) where
#ifdef GHCI
import {-# SOURCE #-} TcSplice ( tcSpliceDecls )
import {-# SOURCE #-} TcSplice ( tcSpliceDecls, runQuasi )
import RnSplice ( rnSplice )
#endif
Expand Down Expand Up @@ -521,6 +521,15 @@ tc_rn_src_decls boot_details ds
; setEnvs (tcg_env, tcl_env) $
case group_tail of
{ Nothing -> do { tcg_env <- checkMain -- Check for `main'
; traceTc "returning from tc_rn_src_decls: " $
ppr $ nameEnvElts $ tcg_type_env tcg_env -- RAE
#ifdef GHCI
-- Run all module finalizers
; th_modfinalizers_var <- fmap tcg_th_modfinalizers getGblEnv
; modfinalizers <- readTcRef th_modfinalizers_var
; writeTcRef th_modfinalizers_var []
; mapM_ runQuasi modfinalizers
#endif /* GHCI */
; return (tcg_env, tcl_env)
}
Expand Down
10 changes: 6 additions & 4 deletions compiler/typecheck/TcRnMonad.lhs
Expand Up @@ -92,8 +92,9 @@ initTc hsc_env hsc_src keep_rn_syntax mod do_this
dependent_files_var <- newIORef [] ;
#ifdef GHCI
th_topdecls_var <- newIORef [] ;
th_topnames_var <- newIORef emptyNameSet ;
th_topdecls_var <- newIORef [] ;
th_topnames_var <- newIORef emptyNameSet ;
th_modfinalizers_var <- newIORef [] ;
#endif /* GHCI */
let {
maybe_rn_syntax :: forall a. a -> Maybe a ;
Expand All @@ -103,8 +104,9 @@ initTc hsc_env hsc_src keep_rn_syntax mod do_this
gbl_env = TcGblEnv {
#ifdef GHCI
tcg_th_topdecls = th_topdecls_var,
tcg_th_topnames = th_topnames_var,
tcg_th_topdecls = th_topdecls_var,
tcg_th_topnames = th_topnames_var,
tcg_th_modfinalizers = th_modfinalizers_var,
#endif /* GHCI */
tcg_mod = mod,
Expand Down
6 changes: 6 additions & 0 deletions compiler/typecheck/TcRnTypes.lhs
Expand Up @@ -117,6 +117,9 @@ import Util
import Data.Set (Set)
#ifdef GHCI
import qualified Language.Haskell.TH as TH
#endif
\end{code}


Expand Down Expand Up @@ -303,6 +306,9 @@ data TcGblEnv
tcg_th_topnames :: TcRef NameSet,
-- ^ Exact names bound in top-level declarations in tcg_th_topdecls
tcg_th_modfinalizers :: TcRef [TH.Q ()],
-- ^ Template Haskell module finalizers
#endif /* GHCI */
tcg_ev_binds :: Bag EvBind, -- Top-level evidence bindings
Expand Down
12 changes: 11 additions & 1 deletion compiler/typecheck/TcSplice.lhs
Expand Up @@ -13,7 +13,7 @@ module TcSplice( tcSpliceType, tcSpliceExpr, tcSpliceDecls, tcBracket,
runQuasiQuoteExpr, runQuasiQuotePat,
runQuasiQuoteDecl, runQuasiQuoteType,
runAnnotation,
runMetaE, runMetaP, runMetaT, runMetaD ) where
runQuasi, runMetaE, runMetaP, runMetaT, runMetaD ) where
#include "HsVersions.h"
Expand Down Expand Up @@ -832,6 +832,12 @@ deprecatedDollar quoter
%* *
%************************************************************************
\begin{code}
runQuasi :: TH.Q a -> TcM a
runQuasi act = TH.runQ act
\end{code}
\begin{code}
data MetaOps th_syn hs_syn
= MT { mt_desc :: String -- Type of beast (expression, type etc)
Expand Down Expand Up @@ -1079,6 +1085,10 @@ instance TH.Quasi (IOEnv (Env TcGblEnv TcLclEnv)) where
addErr $
hang (ptext (sLit "The binder") <+> quotes (ppr name) <+> ptext (sLit "is not a NameU."))
2 (text "Probable cause: you used mkName instead of newName to generate a binding.")
qAddModFinalizer fin = do
th_modfinalizers_var <- fmap tcg_th_modfinalizers getGblEnv
updTcRef th_modfinalizers_var (\fins -> fin:fins)
\end{code}
Expand Down
1 change: 1 addition & 0 deletions compiler/typecheck/TcSplice.lhs-boot
Expand Up @@ -35,6 +35,7 @@ runQuasiQuoteType :: HsQuasiQuote RdrName -> TcM (LHsType RdrName)
runQuasiQuotePat :: HsQuasiQuote RdrName -> TcM (LPat RdrName)
runAnnotation :: CoreAnnTarget -> LHsExpr Name -> TcM Annotation

runQuasi :: TH.Q a -> TcM a
runMetaE :: LHsExpr Id -> TcM (LHsExpr RdrName)
runMetaP :: LHsExpr Id -> TcM (LPat RdrName)
runMetaT :: LHsExpr Id -> TcM (LHsType RdrName)
Expand Down

0 comments on commit 646b630

Please sign in to comment.