9e1b806cfb6b0c925d20be37c80bd2af8eeef9c6
[ghc-hetmet.git] / ghc / compiler / typecheck / TcSplice.lhs
1 %
2 % (c) The GRASP/AQUA Project, Glasgow University, 1992-1998
3 %
4 \section[TcSplice]{Template Haskell splices}
5
6 \begin{code}
7 module TcSplice( tcSpliceExpr, tcSpliceDecls ) where
8
9 #include "HsVersions.h"
10
11 import HscMain          ( compileExpr )
12 import TcRnDriver       ( importSupportingDecls )
13         -- These imports are the reason that TcSplice 
14         -- is very high up the module hierarchy
15
16 import CompManager      ( sandboxIO )
17         -- Ditto, but this one could be defined muchlower down
18
19 import qualified Language.Haskell.THSyntax as Meta
20
21 import HscTypes         ( HscEnv(..), GhciMode(..), PersistentCompilerState(..), unQualInScope )
22 import Convert          ( convertToHsExpr, convertToHsDecls )
23 import RnExpr           ( rnExpr )
24 import RdrHsSyn         ( RdrNameHsExpr, RdrNameHsDecl )
25 import RnHsSyn          ( RenamedHsExpr )
26 import TcExpr           ( tcMonoExpr )
27 import TcHsSyn          ( TcExpr, TypecheckedHsExpr, mkHsLet, zonkTopExpr )
28 import TcSimplify       ( tcSimplifyTop )
29 import TcType           ( TcType )
30 import TcEnv            ( spliceOK, tcMetaTy )
31 import TcRnTypes        ( TopEnv(..) )
32 import Name             ( Name )
33 import TcRnMonad
34
35 import TysWiredIn       ( mkListTy )
36 import PrelNames        ( exprTyConName, declTyConName )
37 import Outputable
38 import GHC.Base         ( unsafeCoerce# )       -- Should have a better home in the module hierarchy
39 \end{code}
40
41
42 %************************************************************************
43 %*                                                                      *
44 \subsection{Main interface + stubs for the non-GHCI case
45 %*                                                                      *
46 %************************************************************************
47
48 \begin{code}
49 tcSpliceDecls :: RenamedHsExpr -> TcM [RdrNameHsDecl]
50
51 tcSpliceExpr :: Name 
52              -> RenamedHsExpr
53              -> TcType
54              -> TcM TcExpr
55
56 #ifndef GHCI
57 tcSpliceExpr n e ty = pprPanic "Cant do tcSpliceExpr without GHCi" (ppr e)
58 tcSpliceDecls e     = pprPanic "Cant do tcSpliceDecls without GHCi" (ppr e)
59 #else
60 \end{code}
61
62 %************************************************************************
63 %*                                                                      *
64 \subsection{Splicing an expression}
65 %*                                                                      *
66 %************************************************************************
67
68 \begin{code}
69 tcSpliceExpr name expr res_ty
70   = getStage            `thenM` \ level ->
71     case spliceOK level of {
72         Nothing         -> failWithTc (illegalSplice level) ;
73         Just next_level -> 
74
75     case level of {
76         Comp                   -> tcTopSplice expr res_ty ;
77         Brack _ ps_var lie_var ->  
78
79         -- A splice inside brackets
80         -- NB: ignore res_ty
81         -- e.g.   [| reverse $(h 4) |]
82         -- Here (h 4) :: Q Exp
83         -- but $(h 4) :: forall a.a     i.e. anything!
84
85     tcMetaTy exprTyConName                      `thenM` \ meta_exp_ty ->
86     setStage (Splice next_level) (
87         setLIEVar lie_var          $
88         tcMonoExpr expr meta_exp_ty
89     )                                           `thenM` \ expr' ->
90
91         -- Write the pending splice into the bucket
92     readMutVar ps_var                           `thenM` \ ps ->
93     writeMutVar ps_var ((name,expr') : ps)      `thenM_`
94
95     returnM (panic "tcSpliceExpr")      -- The returned expression is ignored
96     }} 
97
98 -- tcTopSplice used to have this:
99 -- Note that we do not decrement the level (to -1) before 
100 -- typechecking the expression.  For example:
101 --      f x = $( ...$(g 3) ... )
102 -- The recursive call to tcMonoExpr will simply expand the 
103 -- inner escape before dealing with the outer one
104
105 tcTopSplice expr res_ty
106   = tcMetaTy exprTyConName              `thenM` \ meta_exp_ty ->
107     setStage topSpliceStage (
108         getLIE (tcMonoExpr expr meta_exp_ty)
109     )                                   `thenM` \ (expr', lie) ->
110
111         -- Solve the constraints
112     tcSimplifyTop lie                   `thenM` \ const_binds ->
113     let 
114         q_expr = mkHsLet const_binds expr'
115     in
116     zonkTopExpr q_expr                  `thenM` \ zonked_q_expr ->
117
118         -- Run the expression
119     traceTc (text "About to run" <+> ppr zonked_q_expr)         `thenM_`
120     runMetaE zonked_q_expr              `thenM` \ simple_expr ->
121   
122     let 
123         -- simple_expr :: Meta.Exp
124
125         expr2 :: RdrNameHsExpr
126         expr2 = convertToHsExpr simple_expr 
127     in
128     traceTc (text "Got result" <+> ppr expr2)   `thenM_`
129     initRn SourceMode (rnExpr expr2)            `thenM` \ (exp3, fvs) ->
130     importSupportingDecls fvs                   `thenM` \ env ->
131
132     setGblEnv env (tcMonoExpr exp3 res_ty)
133 \end{code}
134
135
136 %************************************************************************
137 %*                                                                      *
138 \subsection{Splicing an expression}
139 %*                                                                      *
140 %************************************************************************
141
142 \begin{code}
143 -- Always at top level
144 tcSpliceDecls expr
145   = tcMetaTy declTyConName              `thenM` \ meta_dec_ty ->
146     setStage topSpliceStage (
147         getLIE (tcMonoExpr expr (mkListTy meta_dec_ty))
148     )                                   `thenM` \ (expr', lie) ->
149         -- Solve the constraints
150     tcSimplifyTop lie                   `thenM` \ const_binds ->
151     let 
152         q_expr = mkHsLet const_binds expr'
153     in
154     zonkTopExpr q_expr                  `thenM` \ zonked_q_expr ->
155
156         -- Run the expression
157     traceTc (text "About to run" <+> ppr zonked_q_expr)         `thenM_`
158     runMetaD zonked_q_expr              `thenM` \ simple_expr ->
159     let 
160         -- simple_expr :: [Meta.Dec]
161         decls :: [RdrNameHsDecl]
162         decls = convertToHsDecls simple_expr 
163     in
164     returnM decls
165 \end{code}
166
167
168 %************************************************************************
169 %*                                                                      *
170 \subsection{Running an expression}
171 %*                                                                      *
172 %************************************************************************
173
174 \begin{code}
175 runMetaE :: TypecheckedHsExpr   -- Of type (Q Exp)
176          -> TcM Meta.Exp        -- Of type Exp
177 runMetaE e = runMeta e
178
179 runMetaD :: TypecheckedHsExpr   -- Of type (Q [Dec]
180          -> TcM [Meta.Dec]      -- Of type [Dec]
181 runMetaD e = runMeta e
182
183 runMeta :: TypecheckedHsExpr    -- Of type (Q t)
184         -> TcM t                -- Of type t
185 runMeta expr :: TcM t
186   = getTopEnv           `thenM` \ top_env ->
187     getEps              `thenM` \ eps ->
188     getNameCache        `thenM` \ name_cache -> 
189     getModule           `thenM` \ this_mod ->
190     getGlobalRdrEnv     `thenM` \ rdr_env -> 
191     let
192         ghci_mode = top_mode top_env
193
194         hsc_env = HscEnv { hsc_mode = ghci_mode, hsc_HPT = top_hpt top_env,
195                            hsc_dflags = top_dflags top_env }
196
197         pcs = PCS { pcs_nc = name_cache, pcs_EPS = eps }
198
199         print_unqual = unQualInScope rdr_env
200     in
201     if (ghci_mode == OneShot) then
202         failWithTc (ptext SLIT("You must use --make or --interactive to run splice expressions"))
203         -- The reason for this is that the demand-linker doesn't have
204         -- enough information available to link all the things that
205         -- are needed when you try to run a splice
206     else
207     ioToTcRn (do {
208         -- Warning: if Q is anything other than IO, we may need to wrap 
209         -- the expression 'expr' in a runQ before compiling it
210       hval <- HscMain.compileExpr hsc_env pcs this_mod print_unqual expr
211
212         -- hval :: HValue
213         -- Need to coerce it to IO t
214     ; sandboxIO (unsafeCoerce# hval :: IO t) }) `thenM` \ either_tval ->
215
216     case either_tval of
217         Left err -> failWithTc (vcat [text "Exception when running compiled-time code:", 
218                                       nest 4 (text (show err))])
219         Right v  -> returnM v
220 \end{code}
221
222
223
224 -----------------------------------
225         Random comments
226
227
228       module Foo where
229         import Lib( g :: Int -> M Exp )
230         h x = not x     
231         f x y = [| \z -> (x, $(g y), z, map, h) |]
232
233         h p = $( (\q r -> if q then [| \s -> (p,r,s) |] 
234                                else ... ) True 3)   )
235
236 ==> core
237
238         f :: Liftable a => a -> Int -> M Exp
239         f = /\a -> \d::Liftable a ->
240             \ x y -> genSym "z"         `bindM` \ z::String ->
241                      g y                `bindM` \ vv::Exp ->
242                      Lam z (Tup [lift d x, v, Var z, 
243                                  Glob "Prelude" "map",
244                                  Glob "Foo" "h"])
245
246
247         h :: Tree Int -> M Exp
248         h = \p -> \s' -> (p,3,s')
249
250
251                 Bound   Used
252
253         map:    C0      C1      (top-level/imp)
254         x:      C0      C1      (lam/case)
255         y:      C0      C0
256         z:      C1      C1
257
258         p:      C0      S1
259         r:      S0      S1
260         q:      S0      S0
261         s:      S1      S1
262
263 -------
264
265         f x y = lam "z" (tup [lift x, g y, var "z", 
266                               [| map |], [| h |] ])
267 ==> core
268         
269         f = \x y -> lam "z" (tup [lift d x, g y, var "z",
270                                   return (Glob "Prelude" "map"),
271                                   return (Glob "Foo" "h")])
272
273
274
275
276
277
278
279         h :: M Exp -> M Exp
280         h v = [| \x -> map $v x |]
281
282         g :: Tree Int -> M Exp
283         g x = $(h [| x |])
284 ==>
285         g x = \x' -> map x x'
286
287 *** Simon claims x does not have to be liftable! **
288         
289 Level 0 compile time
290 Level 1 run time
291 Level 2 code returned by run time (generation time)
292
293 Non-top-level variables
294         x occurs at level 1
295           inside brackets
296             bound at level 0    --> x
297             bound at level 1    --> var "x"
298
299           not inside brackets   --> x
300
301         x at level 2
302           inside brackets
303             bound at level 0    --> x
304             bound at level 1    --> var "x"
305
306         f x = x
307
308 Two successive brackets aren't allowed
309
310
311 %************************************************************************
312 %*                                                                      *
313 \subsection{Errors and contexts}
314 %*                                                                      *
315 %************************************************************************
316
317 \begin{code}
318 illegalSplice level
319   = ptext SLIT("Illegal splice at level") <+> ppr level
320
321 #endif  /* GHCI */
322 \end{code}