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