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