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