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