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