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