[project @ 2003-10-13 10:43:02 by simonpj]
[ghc-hetmet.git] / ghc / compiler / typecheck / TcRnMonad.lhs
1 \begin{code}
2 module TcRnMonad(
3         module TcRnMonad,
4         module TcRnTypes,
5         module IOEnv
6   ) where
7
8 #include "HsVersions.h"
9
10 import TcRnTypes        -- Re-export all
11 import IOEnv            -- Re-export all
12
13 import HsSyn            ( MonoBinds(..) )
14 import HscTypes         ( HscEnv(..), ModGuts(..), ModIface(..),
15                           TyThing, Dependencies(..),
16                           ExternalPackageState(..), HomePackageTable,
17                           ModDetails(..), HomeModInfo(..), 
18                           Deprecs(..), FixityEnv, FixItem,
19                           GhciMode, lookupType, unQualInScope )
20 import Module           ( Module, ModuleName, unitModuleEnv, foldModuleEnv, emptyModuleEnv )
21 import RdrName          ( GlobalRdrEnv, emptyGlobalRdrEnv,      
22                           LocalRdrEnv, emptyLocalRdrEnv )
23 import Name             ( Name, isInternalName )
24 import Type             ( Type )
25 import NameEnv          ( extendNameEnvList )
26 import InstEnv          ( InstEnv, emptyInstEnv, extendInstEnv )
27
28 import VarSet           ( emptyVarSet )
29 import VarEnv           ( TidyEnv, emptyTidyEnv )
30 import ErrUtils         ( Message, Messages, emptyMessages, errorsFound, 
31                           addShortErrLocLine, addShortWarnLocLine, printErrorsAndWarnings )
32 import SrcLoc           ( SrcLoc, mkGeneralSrcLoc )
33 import NameEnv          ( emptyNameEnv )
34 import NameSet          ( emptyDUs, emptyNameSet )
35 import OccName          ( emptyOccEnv )
36 import Module           ( moduleName )
37 import Bag              ( emptyBag )
38 import Outputable
39 import UniqSupply       ( UniqSupply, mkSplitUniqSupply, uniqFromSupply, splitUniqSupply )
40 import Unique           ( Unique )
41 import CmdLineOpts      ( DynFlags, DynFlag(..), dopt, opt_PprStyle_Debug )
42 import Bag              ( snocBag, unionBags )
43 import Panic            ( showException )
44  
45 import Maybe            ( isJust )
46 import IO               ( stderr )
47 import DATA_IOREF       ( newIORef, readIORef )
48 import EXCEPTION        ( Exception )
49 \end{code}
50
51
52
53 %************************************************************************
54 %*                                                                      *
55                         initTc
56 %*                                                                      *
57 %************************************************************************
58
59 \begin{code}
60 ioToTcRn :: IO r -> TcRn r
61 ioToTcRn = ioToIOEnv
62 \end{code}
63
64 \begin{code}
65 initTc :: HscEnv
66        -> Module 
67        -> TcM r
68        -> IO (Maybe r)
69                 -- Nothing => error thrown by the thing inside
70                 -- (error messages should have been printed already)
71
72 initTc hsc_env mod do_this
73  = do { errs_var     <- newIORef (emptyBag, emptyBag) ;
74         tvs_var      <- newIORef emptyVarSet ;
75         type_env_var <- newIORef emptyNameEnv ;
76         dfuns_var    <- newIORef emptyNameSet ;
77
78         let {
79              gbl_env = TcGblEnv {
80                 tcg_mod      = mod,
81                 tcg_rdr_env  = emptyGlobalRdrEnv,
82                 tcg_fix_env  = emptyNameEnv,
83                 tcg_default  = Nothing,
84                 tcg_type_env = emptyNameEnv,
85                 tcg_type_env_var = type_env_var,
86                 tcg_inst_env  = mkImpInstEnv hsc_env,
87                 tcg_inst_uses = dfuns_var,
88                 tcg_exports  = [],
89                 tcg_imports  = init_imports,
90                 tcg_dus      = emptyDUs,
91                 tcg_binds    = EmptyMonoBinds,
92                 tcg_deprecs  = NoDeprecs,
93                 tcg_insts    = [],
94                 tcg_rules    = [],
95                 tcg_fords    = []
96              } ;
97              lcl_env = TcLclEnv {
98                 tcl_errs       = errs_var,
99                 tcl_loc        = mkGeneralSrcLoc FSLIT("Top level of module"),
100                 tcl_ctxt       = [],
101                 tcl_rdr        = emptyLocalRdrEnv,
102                 tcl_th_ctxt    = topStage,
103                 tcl_arrow_ctxt = topArrowCtxt,
104                 tcl_env        = emptyNameEnv,
105                 tcl_tyvars     = tvs_var,
106                 tcl_lie        = panic "initTc:LIE"     -- LIE only valid inside a getLIE
107              } ;
108         } ;
109    
110         -- OK, here's the business end!
111         maybe_res <- initTcRnIf 'a' hsc_env gbl_env lcl_env $
112                              do { r <- tryM do_this 
113                                 ; case r of
114                                     Right res -> return (Just res)
115                                     Left _    -> return Nothing } ;
116
117         -- Print any error messages
118         msgs <- readIORef errs_var ;
119         printErrorsAndWarnings msgs ;
120
121         let { dflags = hsc_dflags hsc_env
122             ; final_res | errorsFound dflags msgs = Nothing
123                         | otherwise               = maybe_res } ;
124
125         return final_res
126     }
127   where
128     init_imports = emptyImportAvails { imp_qual = unitModuleEnv mod emptyAvailEnv }
129         -- Initialise tcg_imports with an empty set of bindings for
130         -- this module, so that if we see 'module M' in the export
131         -- list, and there are no bindings in M, we don't bleat 
132         -- "unknown module M".
133
134 mkImpInstEnv :: HscEnv -> InstEnv
135 -- At the moment we (wrongly) build an instance environment from all the
136 -- home-package modules we have already compiled.
137 -- We should really only get instances from modules below us in the 
138 -- module import tree.
139 mkImpInstEnv (HscEnv {hsc_dflags = dflags, hsc_HPT = hpt})
140   = foldModuleEnv (add . md_insts . hm_details) emptyInstEnv hpt
141   where
142     add dfuns inst_env = foldl extendInstEnv inst_env dfuns
143
144 -- mkImpTypeEnv makes the imported symbol table
145 mkImpTypeEnv :: ExternalPackageState -> HomePackageTable
146              -> Name -> Maybe TyThing
147 mkImpTypeEnv pcs hpt = lookup 
148   where
149     pte = eps_PTE pcs
150     lookup name | isInternalName name = Nothing
151                 | otherwise           = lookupType hpt pte name
152 \end{code}
153
154
155 %************************************************************************
156 %*                                                                      *
157                 Initialisation
158 %*                                                                      *
159 %************************************************************************
160
161
162 \begin{code}
163 initTcRnIf :: Char              -- Tag for unique supply
164            -> HscEnv
165            -> gbl -> lcl 
166            -> TcRnIf gbl lcl a 
167            -> IO a
168 initTcRnIf uniq_tag hsc_env gbl_env lcl_env thing_inside
169    = do { us     <- mkSplitUniqSupply uniq_tag ;
170         ; us_var <- newIORef us ;
171
172         ; let { env = Env { env_top = hsc_env,
173                             env_us  = us_var,
174                             env_gbl = gbl_env,
175                             env_lcl = lcl_env } }
176
177         ; runIOEnv env thing_inside
178         }
179 \end{code}
180
181 %************************************************************************
182 %*                                                                      *
183                 Simple accessors
184 %*                                                                      *
185 %************************************************************************
186
187 \begin{code}
188 getTopEnv :: TcRnIf gbl lcl HscEnv
189 getTopEnv = do { env <- getEnv; return (env_top env) }
190
191 getGblEnv :: TcRnIf gbl lcl gbl
192 getGblEnv = do { env <- getEnv; return (env_gbl env) }
193
194 updGblEnv :: (gbl -> gbl) -> TcRnIf gbl lcl a -> TcRnIf gbl lcl a
195 updGblEnv upd = updEnv (\ env@(Env { env_gbl = gbl }) -> 
196                           env { env_gbl = upd gbl })
197
198 setGblEnv :: gbl -> TcRnIf gbl lcl a -> TcRnIf gbl lcl a
199 setGblEnv gbl_env = updEnv (\ env -> env { env_gbl = gbl_env })
200
201 getLclEnv :: TcRnIf gbl lcl lcl
202 getLclEnv = do { env <- getEnv; return (env_lcl env) }
203
204 updLclEnv :: (lcl -> lcl) -> TcRnIf gbl lcl a -> TcRnIf gbl lcl a
205 updLclEnv upd = updEnv (\ env@(Env { env_lcl = lcl }) -> 
206                           env { env_lcl = upd lcl })
207
208 setLclEnv :: lcl' -> TcRnIf gbl lcl' a -> TcRnIf gbl lcl a
209 setLclEnv lcl_env = updEnv (\ env -> env { env_lcl = lcl_env })
210
211 getEnvs :: TcRnIf gbl lcl (gbl, lcl)
212 getEnvs = do { env <- getEnv; return (env_gbl env, env_lcl env) }
213
214 setEnvs :: (gbl', lcl') -> TcRnIf gbl' lcl' a -> TcRnIf gbl lcl a
215 setEnvs (gbl_env, lcl_env) = updEnv (\ env -> env { env_gbl = gbl_env, env_lcl = lcl_env })
216 \end{code}
217
218
219 Command-line flags
220
221 \begin{code}
222 getDOpts :: TcRnIf gbl lcl DynFlags
223 getDOpts = do { env <- getTopEnv; return (hsc_dflags env) }
224
225 doptM :: DynFlag -> TcRnIf gbl lcl Bool
226 doptM flag = do { dflags <- getDOpts; return (dopt flag dflags) }
227
228 ifOptM :: DynFlag -> TcRnIf gbl lcl () -> TcRnIf gbl lcl ()     -- Do it flag is true
229 ifOptM flag thing_inside = do { b <- doptM flag; 
230                                 if b then thing_inside else return () }
231
232 getGhciMode :: TcRnIf gbl lcl GhciMode
233 getGhciMode = do { env <- getTopEnv; return (hsc_mode env) }
234 \end{code}
235
236 \begin{code}
237 getEpsVar :: TcRnIf gbl lcl (TcRef ExternalPackageState)
238 getEpsVar = do { env <- getTopEnv; return (hsc_EPS env) }
239
240 getEps :: TcRnIf gbl lcl ExternalPackageState
241 getEps = do { env <- getTopEnv; readMutVar (hsc_EPS env) }
242
243 setEps :: ExternalPackageState -> TcRnIf gbl lcl ()
244 setEps eps = do { env <- getTopEnv; writeMutVar (hsc_EPS env) eps }
245
246 updateEps :: (ExternalPackageState -> (ExternalPackageState, a))
247           -> TcRnIf gbl lcl a
248 updateEps upd_fn = do   { eps_var <- getEpsVar
249                         ; eps <- readMutVar eps_var
250                         ; let { (eps', val) = upd_fn eps }
251                         ; writeMutVar eps_var eps'
252                         ; return val }
253
254 updateEps_ :: (ExternalPackageState -> ExternalPackageState)
255            -> TcRnIf gbl lcl ()
256 updateEps_ upd_fn = do  { eps_var <- getEpsVar
257                         ; updMutVar eps_var upd_fn }
258
259 getHpt :: TcRnIf gbl lcl HomePackageTable
260 getHpt = do { env <- getTopEnv; return (hsc_HPT env) }
261 \end{code}
262
263 %************************************************************************
264 %*                                                                      *
265                 Unique supply
266 %*                                                                      *
267 %************************************************************************
268
269 \begin{code}
270 newUnique :: TcRnIf gbl lcl Unique
271 newUnique = do { us <- newUniqueSupply ; 
272                  return (uniqFromSupply us) }
273
274 newUniqueSupply :: TcRnIf gbl lcl UniqSupply
275 newUniqueSupply
276  = do { env <- getEnv ;
277         let { u_var = env_us env } ;
278         us <- readMutVar u_var ;
279         let { (us1, us2) = splitUniqSupply us } ;
280         writeMutVar u_var us1 ;
281         return us2 }
282 \end{code}
283
284
285 %************************************************************************
286 %*                                                                      *
287                 Debugging
288 %*                                                                      *
289 %************************************************************************
290
291 \begin{code}
292 traceTc, traceRn :: SDoc -> TcRn ()
293 traceRn      = dumpOptTcRn Opt_D_dump_rn_trace
294 traceTc      = dumpOptTcRn Opt_D_dump_tc_trace
295 traceSplice  = dumpOptTcRn Opt_D_dump_splices
296
297
298 traceIf :: SDoc -> TcRnIf m n ()        
299 traceIf      = dumpOptIf Opt_D_dump_if_trace
300 traceHiDiffs = dumpOptIf Opt_D_dump_hi_diffs
301
302
303 dumpOptIf :: DynFlag -> SDoc -> TcRnIf m n ()  -- No RdrEnv available, so qualify everything
304 dumpOptIf flag doc = ifOptM flag $
305                      ioToIOEnv (printForUser stderr alwaysQualify doc)
306
307 dumpOptTcRn :: DynFlag -> SDoc -> TcRn ()
308 dumpOptTcRn flag doc = ifOptM flag (dumpTcRn doc)
309
310 dumpTcRn :: SDoc -> TcRn ()
311 dumpTcRn doc = do { rdr_env <- getGlobalRdrEnv ;
312                     ioToTcRn (printForUser stderr (unQualInScope rdr_env) doc) }
313 \end{code}
314
315
316 %************************************************************************
317 %*                                                                      *
318                 Typechecker global environment
319 %*                                                                      *
320 %************************************************************************
321
322 \begin{code}
323 getModule :: TcRn Module
324 getModule = do { env <- getGblEnv; return (tcg_mod env) }
325
326 getGlobalRdrEnv :: TcRn GlobalRdrEnv
327 getGlobalRdrEnv = do { env <- getGblEnv; return (tcg_rdr_env env) }
328
329 getImports :: TcRn ImportAvails
330 getImports = do { env <- getGblEnv; return (tcg_imports env) }
331
332 getFixityEnv :: TcRn FixityEnv
333 getFixityEnv = do { env <- getGblEnv; return (tcg_fix_env env) }
334
335 extendFixityEnv :: [(Name,FixItem)] -> RnM a -> RnM a
336 extendFixityEnv new_bit
337   = updGblEnv (\env@(TcGblEnv { tcg_fix_env = old_fix_env }) -> 
338                 env {tcg_fix_env = extendNameEnvList old_fix_env new_bit})           
339
340 getDefaultTys :: TcRn (Maybe [Type])
341 getDefaultTys = do { env <- getGblEnv; return (tcg_default env) }
342 \end{code}
343
344 %************************************************************************
345 %*                                                                      *
346                 Error management
347 %*                                                                      *
348 %************************************************************************
349
350 \begin{code}
351 getSrcLocM :: TcRn SrcLoc
352         -- Avoid clash with Name.getSrcLoc
353 getSrcLocM = do { env <- getLclEnv; return (tcl_loc env) }
354
355 addSrcLoc :: SrcLoc -> TcRn a -> TcRn a
356 addSrcLoc loc = updLclEnv (\env -> env { tcl_loc = loc })
357 \end{code}
358
359
360 \begin{code}
361 getErrsVar :: TcRn (TcRef Messages)
362 getErrsVar = do { env <- getLclEnv; return (tcl_errs env) }
363
364 setErrsVar :: TcRef Messages -> TcRn a -> TcRn a
365 setErrsVar v = updLclEnv (\ env -> env { tcl_errs =  v })
366
367 addErr :: Message -> TcRn ()
368 addErr msg = do { loc <- getSrcLocM ; addErrAt loc msg }
369
370 addErrAt :: SrcLoc -> Message -> TcRn ()
371 addErrAt loc msg
372  = do {  errs_var <- getErrsVar ;
373          rdr_env <- getGlobalRdrEnv ;
374          let { err = addShortErrLocLine loc (unQualInScope rdr_env) msg } ;
375          (warns, errs) <- readMutVar errs_var ;
376          writeMutVar errs_var (warns, errs `snocBag` err) }
377
378 addErrs :: [(SrcLoc,Message)] -> TcRn ()
379 addErrs msgs = mappM_ add msgs
380              where
381                add (loc,msg) = addErrAt loc msg
382
383 addWarn :: Message -> TcRn ()
384 addWarn msg
385   = do { errs_var <- getErrsVar ;
386          loc <- getSrcLocM ;
387          rdr_env <- getGlobalRdrEnv ;
388          let { warn = addShortWarnLocLine loc (unQualInScope rdr_env) msg } ;
389          (warns, errs) <- readMutVar errs_var ;
390          writeMutVar errs_var (warns `snocBag` warn, errs) }
391
392 checkErr :: Bool -> Message -> TcRn ()
393 -- Add the error if the bool is False
394 checkErr ok msg = checkM ok (addErr msg)
395
396 warnIf :: Bool -> Message -> TcRn ()
397 warnIf True  msg = addWarn msg
398 warnIf False msg = return ()
399
400 addMessages :: Messages -> TcRn ()
401 addMessages (m_warns, m_errs)
402   = do { errs_var <- getErrsVar ;
403          (warns, errs) <- readMutVar errs_var ;
404          writeMutVar errs_var (warns `unionBags` m_warns,
405                                errs  `unionBags` m_errs) }
406 \end{code}
407
408
409 \begin{code}
410 recoverM :: TcRn r      -- Recovery action; do this if the main one fails
411          -> TcRn r      -- Main action: do this first
412          -> TcRn r
413 recoverM recover thing 
414   = do { mb_res <- try_m thing ;
415          case mb_res of
416            Left exn  -> recover
417            Right res -> returnM res }
418
419 tryTc :: TcRn a -> TcRn (Messages, Maybe a)
420     -- (tryTc m) executes m, and returns
421     --  Just r,  if m succeeds (returning r) and caused no errors
422     --  Nothing, if m fails, or caused errors
423     -- It also returns all the errors accumulated by m
424     --  (even in the Just case, there might be warnings)
425     --
426     -- It always succeeds (never raises an exception)
427 tryTc m 
428  = do { errs_var <- newMutVar emptyMessages ;
429         
430         mb_r <- try_m (setErrsVar errs_var m) ; 
431
432         new_errs <- readMutVar errs_var ;
433
434         dflags <- getDOpts ;
435
436         return (new_errs, 
437                 case mb_r of
438                   Left exn -> Nothing
439                   Right r | errorsFound dflags new_errs -> Nothing
440                           | otherwise                   -> Just r) 
441    }
442
443 try_m :: TcRn r -> TcRn (Either Exception r)
444 -- Does try_m, with a debug-trace on failure
445 try_m thing 
446   = do { mb_r <- tryM thing ;
447          case mb_r of 
448              Left exn -> do { traceTc (exn_msg exn); return mb_r }
449              Right r  -> return mb_r }
450   where
451     exn_msg exn = text "tryTc/recoverM recovering from" <+> text (showException exn)
452
453 tryTcLIE :: TcM a -> TcM (Messages, Maybe a)
454 -- Just like tryTc, except that it ensures that the LIE
455 -- for the thing is propagated only if there are no errors
456 -- Hence it's restricted to the type-check monad
457 tryTcLIE thing_inside
458   = do { ((errs, mb_r), lie) <- getLIE (tryTc thing_inside) ;
459          ifM (isJust mb_r) (extendLIEs lie) ;
460          return (errs, mb_r) }
461
462 tryTcLIE_ :: TcM r -> TcM r -> TcM r
463 -- (tryTcLIE_ r m) tries m; if it succeeds it returns it,
464 -- otherwise it returns r.  Any error messages added by m are discarded,
465 -- whether or not m succeeds.
466 tryTcLIE_ recover main
467   = do { (_msgs, mb_res) <- tryTcLIE main ;
468          case mb_res of
469            Just res -> return res
470            Nothing  -> recover }
471
472 checkNoErrs :: TcM r -> TcM r
473 -- (checkNoErrs m) succeeds iff m succeeds and generates no errors
474 -- If m fails then (checkNoErrsTc m) fails.
475 -- If m succeeds, it checks whether m generated any errors messages
476 --      (it might have recovered internally)
477 --      If so, it fails too.
478 -- Regardless, any errors generated by m are propagated to the enclosing context.
479 checkNoErrs main
480   = do { (msgs, mb_res) <- tryTcLIE main ;
481          addMessages msgs ;
482          case mb_res of
483            Just r  -> return r
484            Nothing -> failM
485    }
486
487 ifErrsM :: TcRn r -> TcRn r -> TcRn r
488 --      ifErrsM bale_out main
489 -- does 'bale_out' if there are errors in errors collection
490 -- otherwise does 'main'
491 ifErrsM bale_out normal
492  = do { errs_var <- getErrsVar ;
493         msgs <- readMutVar errs_var ;
494         dflags <- getDOpts ;
495         if errorsFound dflags msgs then
496            bale_out
497         else    
498            normal }
499
500 failIfErrsM :: TcRn ()
501 -- Useful to avoid error cascades
502 failIfErrsM = ifErrsM failM (return ())
503 \end{code}
504
505
506 %************************************************************************
507 %*                                                                      *
508         Context management and error message generation
509                     for the type checker
510 %*                                                                      *
511 %************************************************************************
512
513 \begin{code}
514 setErrCtxtM, addErrCtxtM :: (TidyEnv -> TcM (TidyEnv, Message)) -> TcM a -> TcM a
515 setErrCtxtM msg = updCtxt (\ msgs -> [msg])
516 addErrCtxtM msg = updCtxt (\ msgs -> msg : msgs)
517
518 setErrCtxt, addErrCtxt :: Message -> TcM a -> TcM a
519 setErrCtxt msg = setErrCtxtM (\env -> returnM (env, msg))
520 addErrCtxt msg = addErrCtxtM (\env -> returnM (env, msg))
521
522 popErrCtxt :: TcM a -> TcM a
523 popErrCtxt = updCtxt (\ msgs -> case msgs of { [] -> []; (m:ms) -> ms })
524
525 getErrCtxt :: TcM ErrCtxt
526 getErrCtxt = do { env <- getLclEnv ; return (tcl_ctxt env) }
527
528 -- Helper function for the above
529 updCtxt :: (ErrCtxt -> ErrCtxt) -> TcM a -> TcM a
530 updCtxt upd = updLclEnv (\ env@(TcLclEnv { tcl_ctxt = ctxt }) -> 
531                            env { tcl_ctxt = upd ctxt })
532
533 getInstLoc :: InstOrigin -> TcM InstLoc
534 getInstLoc origin
535   = do { loc <- getSrcLocM ; env <- getLclEnv ;
536          return (InstLoc origin loc (tcl_ctxt env)) }
537
538 addInstCtxt :: InstLoc -> TcM a -> TcM a
539 -- Add the SrcLoc and context from the first Inst in the list
540 --      (they all have similar locations)
541 addInstCtxt (InstLoc _ src_loc ctxt) thing_inside
542   = addSrcLoc src_loc (updCtxt (\ old_ctxt -> ctxt) thing_inside)
543 \end{code}
544
545     The addErrTc functions add an error message, but do not cause failure.
546     The 'M' variants pass a TidyEnv that has already been used to
547     tidy up the message; we then use it to tidy the context messages
548
549 \begin{code}
550 addErrTc :: Message -> TcM ()
551 addErrTc err_msg = addErrTcM (emptyTidyEnv, err_msg)
552
553 addErrsTc :: [Message] -> TcM ()
554 addErrsTc err_msgs = mappM_ addErrTc err_msgs
555
556 addErrTcM :: (TidyEnv, Message) -> TcM ()
557 addErrTcM (tidy_env, err_msg)
558   = do { ctxt <- getErrCtxt ;
559          loc  <- getSrcLocM ;
560          add_err_tcm tidy_env err_msg loc ctxt }
561 \end{code}
562
563 The failWith functions add an error message and cause failure
564
565 \begin{code}
566 failWithTc :: Message -> TcM a               -- Add an error message and fail
567 failWithTc err_msg 
568   = addErrTc err_msg >> failM
569
570 failWithTcM :: (TidyEnv, Message) -> TcM a   -- Add an error message and fail
571 failWithTcM local_and_msg
572   = addErrTcM local_and_msg >> failM
573
574 checkTc :: Bool -> Message -> TcM ()         -- Check that the boolean is true
575 checkTc True  err = returnM ()
576 checkTc False err = failWithTc err
577 \end{code}
578
579         Warnings have no 'M' variant, nor failure
580
581 \begin{code}
582 addWarnTc :: Message -> TcM ()
583 addWarnTc msg
584  = do { ctxt <- getErrCtxt ;
585         ctxt_msgs <- do_ctxt emptyTidyEnv ctxt ;
586         addWarn (vcat (msg : ctxt_to_use ctxt_msgs)) }
587
588 warnTc :: Bool -> Message -> TcM ()
589 warnTc warn_if_true warn_msg
590   | warn_if_true = addWarnTc warn_msg
591   | otherwise    = return ()
592 \end{code}
593
594         Helper functions
595
596 \begin{code}
597 add_err_tcm tidy_env err_msg loc ctxt
598  = do { ctxt_msgs <- do_ctxt tidy_env ctxt ;
599         addErrAt loc (vcat (err_msg : ctxt_to_use ctxt_msgs)) }
600
601 do_ctxt tidy_env []
602  = return []
603 do_ctxt tidy_env (c:cs)
604  = do { (tidy_env', m) <- c tidy_env  ;
605         ms             <- do_ctxt tidy_env' cs  ;
606         return (m:ms) }
607
608 ctxt_to_use ctxt | opt_PprStyle_Debug = ctxt
609                  | otherwise          = take 3 ctxt
610 \end{code}
611
612 %************************************************************************
613 %*                                                                      *
614              Type constraints (the so-called LIE)
615 %*                                                                      *
616 %************************************************************************
617
618 \begin{code}
619 getLIEVar :: TcM (TcRef LIE)
620 getLIEVar = do { env <- getLclEnv; return (tcl_lie env) }
621
622 setLIEVar :: TcRef LIE -> TcM a -> TcM a
623 setLIEVar lie_var = updLclEnv (\ env -> env { tcl_lie = lie_var })
624
625 getLIE :: TcM a -> TcM (a, [Inst])
626 -- (getLIE m) runs m, and returns the type constraints it generates
627 getLIE thing_inside
628   = do { lie_var <- newMutVar emptyLIE ;
629          res <- updLclEnv (\ env -> env { tcl_lie = lie_var }) 
630                           thing_inside ;
631          lie <- readMutVar lie_var ;
632          return (res, lieToList lie) }
633
634 extendLIE :: Inst -> TcM ()
635 extendLIE inst
636   = do { lie_var <- getLIEVar ;
637          lie <- readMutVar lie_var ;
638          writeMutVar lie_var (inst `consLIE` lie) }
639
640 extendLIEs :: [Inst] -> TcM ()
641 extendLIEs [] 
642   = returnM ()
643 extendLIEs insts
644   = do { lie_var <- getLIEVar ;
645          lie <- readMutVar lie_var ;
646          writeMutVar lie_var (mkLIE insts `plusLIE` lie) }
647 \end{code}
648
649 \begin{code}
650 setLclTypeEnv :: TcLclEnv -> TcM a -> TcM a
651 -- Set the local type envt, but do *not* disturb other fields,
652 -- notably the lie_var
653 setLclTypeEnv lcl_env thing_inside
654   = updLclEnv upd thing_inside
655   where
656     upd env = env { tcl_env = tcl_env lcl_env,
657                     tcl_tyvars = tcl_tyvars lcl_env }
658 \end{code}
659
660
661 %************************************************************************
662 %*                                                                      *
663              Template Haskell context
664 %*                                                                      *
665 %************************************************************************
666
667 \begin{code}
668 getStage :: TcM ThStage
669 getStage = do { env <- getLclEnv; return (tcl_th_ctxt env) }
670
671 setStage :: ThStage -> TcM a -> TcM a 
672 setStage s = updLclEnv (\ env -> env { tcl_th_ctxt = s })
673 \end{code}
674
675
676 %************************************************************************
677 %*                                                                      *
678              Arrow context
679 %*                                                                      *
680 %************************************************************************
681
682 \begin{code}
683 popArrowBinders :: TcM a -> TcM a       -- Move to the left of a (-<); see comments in TcRnTypes
684 popArrowBinders 
685   = updLclEnv (\ env -> env { tcl_arrow_ctxt = pop (tcl_arrow_ctxt env)  })
686   where
687     pop (ArrCtxt {proc_level = curr_lvl, proc_banned = banned})
688         = ASSERT( not (curr_lvl `elem` banned) )
689           ArrCtxt {proc_level = curr_lvl, proc_banned = curr_lvl : banned}
690
691 getBannedProcLevels :: TcM [ProcLevel]
692   = do { env <- getLclEnv; return (proc_banned (tcl_arrow_ctxt env)) }
693
694 incProcLevel :: TcM a -> TcM a
695 incProcLevel 
696   = updLclEnv (\ env -> env { tcl_arrow_ctxt = inc (tcl_arrow_ctxt env) })
697   where
698     inc ctxt = ctxt { proc_level = proc_level ctxt + 1 }
699 \end{code}
700
701
702 %************************************************************************
703 %*                                                                      *
704              Stuff for the renamer's local env
705 %*                                                                      *
706 %************************************************************************
707
708 \begin{code}
709 getLocalRdrEnv :: RnM LocalRdrEnv
710 getLocalRdrEnv = do { env <- getLclEnv; return (tcl_rdr env) }
711
712 setLocalRdrEnv :: LocalRdrEnv -> RnM a -> RnM a
713 setLocalRdrEnv rdr_env thing_inside 
714   = updLclEnv (\env -> env {tcl_rdr = rdr_env}) thing_inside
715 \end{code}
716
717
718 %************************************************************************
719 %*                                                                      *
720              Stuff for interface decls
721 %*                                                                      *
722 %************************************************************************
723
724 \begin{code}
725 initIfaceTcRn :: IfG a -> TcRn a
726 initIfaceTcRn thing_inside
727   = do  { tcg_env <- getGblEnv 
728         ; let { if_env = IfGblEnv { 
729                         if_rec_types = Just (tcg_mod tcg_env, get_type_env),
730                         if_is_boot   = imp_dep_mods (tcg_imports tcg_env) }
731               ; get_type_env = readMutVar (tcg_type_env_var tcg_env) }
732         ; setEnvs (if_env, ()) thing_inside }
733
734 initIfaceExtCore :: IfL a -> TcRn a
735 initIfaceExtCore thing_inside
736   = do  { tcg_env <- getGblEnv 
737         ; let { mod = tcg_mod tcg_env
738               ; if_env = IfGblEnv { 
739                         if_rec_types = Just (mod, return (tcg_type_env tcg_env)), 
740                         if_is_boot   = imp_dep_mods (tcg_imports tcg_env) }
741               ; if_lenv = IfLclEnv { if_mod     = moduleName mod,
742                                      if_tv_env  = emptyOccEnv,
743                                      if_id_env  = emptyOccEnv }
744           }
745         ; setEnvs (if_env, if_lenv) thing_inside }
746
747 initIfaceCheck :: HscEnv -> IfG a -> IO a
748 -- Used when checking the up-to-date-ness of the old Iface
749 -- Initialise the environment with no useful info at all
750 initIfaceCheck hsc_env do_this
751  = do   { let { gbl_env = IfGblEnv { if_is_boot   = emptyModuleEnv,
752                                      if_rec_types = Nothing } ;
753            }
754         ; initTcRnIf 'i' hsc_env gbl_env () do_this
755     }
756
757 initIfaceTc :: HscEnv -> ModIface -> IfG a -> IO a
758 -- Used when type-checking checking an up-to-date interface file
759 -- No type envt from the current module, but we do know the module dependencies
760 initIfaceTc hsc_env iface do_this
761  = do   { let { gbl_env = IfGblEnv { if_is_boot   = mkModDeps (dep_mods (mi_deps iface)),
762                                      if_rec_types = Nothing } ;
763            }
764         ; initTcRnIf 'i' hsc_env gbl_env () do_this
765     }
766
767 initIfaceRules :: HscEnv -> ModGuts -> IfG a -> IO a
768 -- Used when sucking in new Rules in SimplCore
769 -- We have available the type envt of the module being compiled, and we must use it
770 initIfaceRules hsc_env guts do_this
771  = do   { let {
772              is_boot = mkModDeps (dep_mods (mg_deps guts))
773                         -- Urgh!  But we do somehow need to get the info
774                         -- on whether (for this particular compilation) we should
775                         -- import a hi-boot file or not.
776            ; type_info = (mg_module guts, return (mg_types guts))
777            ; gbl_env = IfGblEnv { if_is_boot   = is_boot,
778                                   if_rec_types = Just type_info } ;
779            }
780
781         -- Run the thing; any exceptions just bubble out from here
782         ; initTcRnIf 'i' hsc_env gbl_env () do_this
783     }
784
785 initIfaceLcl :: ModuleName -> IfL a -> IfM lcl a
786 initIfaceLcl mod thing_inside 
787   = setLclEnv (IfLclEnv { if_mod      = mod,
788                            if_tv_env  = emptyOccEnv,
789                            if_id_env  = emptyOccEnv })
790               thing_inside
791
792
793 --------------------
794 forkM_maybe :: SDoc -> IfL a -> IfL (Maybe a)
795 -- Run thing_inside in an interleaved thread.  
796 -- It shares everything with the parent thread, so this is DANGEROUS.  
797 --
798 -- It returns Nothing if the computation fails
799 -- 
800 -- It's used for lazily type-checking interface
801 -- signatures, which is pretty benign
802
803 forkM_maybe doc thing_inside
804  = do { unsafeInterleaveM $
805         do { traceIf (text "Starting fork {" <+> doc)
806            ; mb_res <- tryM thing_inside ;
807              case mb_res of
808                 Right r  -> do  { traceIf (text "} ending fork" <+> doc)
809                                 ; return (Just r) }
810                 Left exn -> do {
811
812                     -- Bleat about errors in the forked thread, if -ddump-if-trace is on
813                     -- Otherwise we silently discard errors. Errors can legitimately
814                     -- happen when compiling interface signatures (see tcInterfaceSigs)
815                       ifOptM Opt_D_dump_if_trace 
816                              (print_errs (hang (text "forkM failed:" <+> doc)
817                                              4 (text (show exn))))
818
819                     ; traceIf (text "} ending fork (badly)" <+> doc)
820                     ; return Nothing }
821         }}
822   where
823     print_errs sdoc = ioToIOEnv (printErrs (sdoc defaultErrStyle))
824
825 forkM :: SDoc -> IfL a -> IfL a
826 forkM doc thing_inside
827  = do   { mb_res <- forkM_maybe doc thing_inside
828         ; return (case mb_res of 
829                         Nothing -> pprPanic "forkM" doc
830                         Just r  -> r) }
831 \end{code}