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