Skip to content

Commit

Permalink
Add support for Template Haskell state.
Browse files Browse the repository at this point in the history
  • Loading branch information
mainland committed Jun 27, 2013
1 parent 646b630 commit fdce179
Show file tree
Hide file tree
Showing 3 changed files with 27 additions and 0 deletions.
6 changes: 6 additions & 0 deletions compiler/typecheck/TcRnMonad.lhs
Expand Up @@ -53,6 +53,10 @@ import Util
import Data.IORef
import qualified Data.Set as Set
import Control.Monad
#ifdef GHCI
import qualified Data.Map as Map
#endif
\end{code}


Expand Down Expand Up @@ -95,6 +99,7 @@ initTc hsc_env hsc_src keep_rn_syntax mod do_this
th_topdecls_var <- newIORef [] ;
th_topnames_var <- newIORef emptyNameSet ;
th_modfinalizers_var <- newIORef [] ;
th_state_var <- newIORef Map.empty ;
#endif /* GHCI */
let {
maybe_rn_syntax :: forall a. a -> Maybe a ;
Expand All @@ -107,6 +112,7 @@ initTc hsc_env hsc_src keep_rn_syntax mod do_this
tcg_th_topdecls = th_topdecls_var,
tcg_th_topnames = th_topnames_var,
tcg_th_modfinalizers = th_modfinalizers_var,
tcg_th_state = th_state_var,
#endif /* GHCI */
tcg_mod = mod,
Expand Down
7 changes: 7 additions & 0 deletions compiler/typecheck/TcRnTypes.lhs
Expand Up @@ -118,6 +118,10 @@ import Util
import Data.Set (Set)
#ifdef GHCI
import Data.Map ( Map )
import Data.Dynamic ( Dynamic )
import Data.Typeable ( TypeRep )
import qualified Language.Haskell.TH as TH
#endif
\end{code}
Expand Down Expand Up @@ -309,6 +313,9 @@ data TcGblEnv
tcg_th_modfinalizers :: TcRef [TH.Q ()],
-- ^ Template Haskell module finalizers
tcg_th_state :: TcRef (Map TypeRep Dynamic),
-- ^ Template Haskell state
#endif /* GHCI */
tcg_ev_binds :: Bag EvBind, -- Top-level evidence bindings
Expand Down
14 changes: 14 additions & 0 deletions compiler/typecheck/TcSplice.lhs
Expand Up @@ -84,6 +84,10 @@ import qualified Language.Haskell.TH.Syntax as TH
#ifdef GHCI
-- Because GHC.Desugar might not be in the base library of the bootstrapping compiler
import GHC.Desugar ( AnnotationWrapper(..) )
import qualified Data.Map as Map
import Data.Dynamic ( fromDynamic, toDyn )
import Data.Typeable ( typeOf )
#endif
import GHC.Exts ( unsafeCoerce# )
Expand Down Expand Up @@ -1089,6 +1093,16 @@ instance TH.Quasi (IOEnv (Env TcGblEnv TcLclEnv)) where
qAddModFinalizer fin = do
th_modfinalizers_var <- fmap tcg_th_modfinalizers getGblEnv
updTcRef th_modfinalizers_var (\fins -> fin:fins)
qGetQ = do
th_state_var <- fmap tcg_th_state getGblEnv
th_state <- readTcRef th_state_var
let x = Map.lookup (typeOf x) th_state >>= fromDynamic
return x
qPutQ x = do
th_state_var <- fmap tcg_th_state getGblEnv
updTcRef th_state_var (\m -> Map.insert (typeOf x) (toDyn x) m)
\end{code}
Expand Down

0 comments on commit fdce179

Please sign in to comment.