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