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