Change 'handleFlagWarnings' to throw exceptions instead of dying.
[ghc-hetmet.git] / compiler / main / HscTypes.lhs
1 %
2 % (c) The University of Glasgow, 2006
3 %
4 \section[HscTypes]{Types for the per-module compiler}
5
6 \begin{code}
7 -- | Types for the per-module compiler
8 module HscTypes ( 
9         -- * 'Ghc' monad stuff
10         Ghc(..), GhcT(..), liftGhcT,
11         GhcMonad(..), WarnLogMonad(..),
12         liftIO,
13         ioMsgMaybe, ioMsg,
14         logWarnings, clearWarnings, hasWarnings,
15         SourceError, GhcApiError, mkSrcErr, srcErrorMessages, mkApiErr,
16         throwOneError, handleSourceError,
17         reflectGhc, reifyGhc,
18         handleFlagWarnings,
19
20         -- * Sessions and compilation state
21         Session(..), withSession, modifySession,
22         HscEnv(..), hscEPS,
23         FinderCache, FindResult(..), ModLocationCache,
24         Target(..), TargetId(..), pprTarget, pprTargetId,
25         ModuleGraph, emptyMG,
26
27         -- * Information about modules
28         ModDetails(..), emptyModDetails,
29         ModGuts(..), CoreModule(..), CgGuts(..), ForeignStubs(..),
30         ImportedMods,
31
32         ModSummary(..), ms_mod_name, showModMsg, isBootSummary,
33         msHsFilePath, msHiFilePath, msObjFilePath,
34
35         -- * Information about the module being compiled
36         HscSource(..), isHsBoot, hscSourceString,       -- Re-exported from DriverPhases
37         
38         -- * State relating to modules in this package
39         HomePackageTable, HomeModInfo(..), emptyHomePackageTable,
40         hptInstances, hptRules, hptVectInfo,
41         
42         -- * State relating to known packages
43         ExternalPackageState(..), EpsStats(..), addEpsInStats,
44         PackageTypeEnv, PackageIfaceTable, emptyPackageIfaceTable,
45         lookupIfaceByModule, emptyModIface,
46         
47         PackageInstEnv, PackageRuleBase,
48
49
50         -- * Annotations
51         prepareAnnotations,
52
53         -- * Interactive context
54         InteractiveContext(..), emptyInteractiveContext, 
55         icPrintUnqual, mkPrintUnqualified, extendInteractiveContext,
56         substInteractiveContext,
57
58         -- * Interfaces
59         ModIface(..), mkIfaceWarnCache, mkIfaceHashCache, mkIfaceFixCache,
60         emptyIfaceWarnCache,
61
62         -- * Fixity
63         FixityEnv, FixItem(..), lookupFixity, emptyFixityEnv,
64
65         -- * TyThings and type environments
66         TyThing(..),
67         tyThingClass, tyThingTyCon, tyThingDataCon, tyThingId,
68         implicitTyThings, isImplicitTyThing,
69         
70         TypeEnv, lookupType, lookupTypeHscEnv, mkTypeEnv, emptyTypeEnv,
71         extendTypeEnv, extendTypeEnvList, extendTypeEnvWithIds, lookupTypeEnv,
72         typeEnvElts, typeEnvClasses, typeEnvTyCons, typeEnvIds,
73         typeEnvDataCons,
74
75         -- * MonadThings
76         MonadThings(..),
77
78         -- * Information on imports and exports
79         WhetherHasOrphans, IsBootInterface, Usage(..), 
80         Dependencies(..), noDependencies,
81         NameCache(..), OrigNameCache, OrigIParamCache,
82         Avails, availsToNameSet, availsToNameEnv, availName, availNames,
83         GenAvailInfo(..), AvailInfo, RdrAvailInfo, 
84         IfaceExport,
85
86         -- * Warnings
87         Warnings(..), WarningTxt(..), plusWarns,
88
89         -- * Linker stuff
90         Linkable(..), isObjectLinkable,
91         Unlinked(..), CompiledByteCode,
92         isObject, nameOfObject, isInterpretable, byteCodeOfObject,
93         
94         -- * Program coverage
95         HpcInfo(..), emptyHpcInfo, isHpcUsed, AnyHpcUsage,
96
97         -- * Breakpoints
98         ModBreaks (..), BreakIndex, emptyModBreaks,
99
100         -- * Vectorisation information
101         VectInfo(..), IfaceVectInfo(..), noVectInfo, plusVectInfo, 
102         noIfaceVectInfo
103     ) where
104
105 #include "HsVersions.h"
106
107 #ifdef GHCI
108 import ByteCodeAsm      ( CompiledByteCode )
109 import {-# SOURCE #-}  InteractiveEval ( Resume )
110 #endif
111
112 import RdrName
113 import Name
114 import NameEnv
115 import NameSet  
116 import OccName          ( OccName, OccEnv, lookupOccEnv, mkOccEnv, emptyOccEnv, 
117                           extendOccEnv )
118 import Module
119 import InstEnv          ( InstEnv, Instance )
120 import FamInstEnv       ( FamInstEnv, FamInst )
121 import Rules            ( RuleBase )
122 import CoreSyn          ( CoreBind )
123 import VarEnv
124 import VarSet
125 import Var
126 import Id
127 import Type             
128
129 import Annotations
130 import Class            ( Class, classSelIds, classATs, classTyCon )
131 import TyCon
132 import DataCon          ( DataCon, dataConImplicitIds, dataConWrapId )
133 import PrelNames        ( gHC_PRIM )
134 import Packages hiding ( Version(..) )
135 import DynFlags         ( DynFlags(..), isOneShot, HscTarget (..), dopt,
136                           DynFlag(..) )
137 import DriverPhases     ( HscSource(..), isHsBoot, hscSourceString, Phase )
138 import BasicTypes       ( IPName, Fixity, defaultFixity, WarningTxt(..) )
139 import OptimizationFuel ( OptFuelState )
140 import IfaceSyn
141 import FiniteMap        ( FiniteMap )
142 import CoreSyn          ( CoreRule )
143 import Maybes           ( orElse, expectJust, catMaybes )
144 import Outputable
145 import BreakArray
146 import SrcLoc           ( SrcSpan, Located(..) )
147 import LazyUniqFM               ( lookupUFM, eltsUFM, emptyUFM )
148 import UniqSupply       ( UniqSupply )
149 import FastString
150 import StringBuffer     ( StringBuffer )
151 import Fingerprint
152 import MonadUtils
153 import Data.Dynamic     ( Typeable )
154 import qualified Data.Dynamic as Dyn
155 import Bag
156 import ErrUtils
157
158 import System.FilePath
159 import System.Time      ( ClockTime )
160 import Data.IORef
161 import Data.Array       ( Array, array )
162 import Data.List
163 import Control.Monad    ( mplus, guard, liftM, when )
164 import Exception
165 \end{code}
166
167
168 %************************************************************************
169 %*                                                                      *
170 \subsection{Compilation environment}
171 %*                                                                      *
172 %************************************************************************
173
174
175 \begin{code}
176 -- | The Session is a handle to the complete state of a compilation
177 -- session.  A compilation session consists of a set of modules
178 -- constituting the current program or library, the context for
179 -- interactive evaluation, and various caches.
180 data Session = Session !(IORef HscEnv) !(IORef WarningMessages)
181
182 mkSrcErr :: ErrorMessages -> SourceError
183 srcErrorMessages :: SourceError -> ErrorMessages
184 mkApiErr :: SDoc -> GhcApiError
185
186 throwOneError :: MonadIO m => ErrMsg -> m ab
187 throwOneError err = liftIO $ throwIO $ mkSrcErr $ unitBag err
188
189 -- | A source error is an error that is caused by one or more errors in the
190 -- source code.  A 'SourceError' is thrown by many functions in the
191 -- compilation pipeline.  Inside GHC these errors are merely printed via
192 -- 'log_action', but API clients may treat them differently, for example,
193 -- insert them into a list box.  If you want the default behaviour, use the
194 -- idiom:
195 --
196 -- > handleSourceError printExceptionAndWarnings $ do
197 -- >   ... api calls that may fail ...
198 --
199 -- The 'SourceError's error messages can be accessed via 'srcErrorMessages'.
200 -- This list may be empty if the compiler failed due to @-Werror@
201 -- ('Opt_WarnIsError').
202 --
203 -- See 'printExceptionAndWarnings' for more information on what to take care
204 -- of when writing a custom error handler.
205 data SourceError = SourceError ErrorMessages
206
207 instance Show SourceError where
208   show (SourceError msgs) = unlines . map show . bagToList $ msgs
209     -- ToDo: is there some nicer way to print this?
210
211 sourceErrorTc :: Dyn.TyCon
212 sourceErrorTc = Dyn.mkTyCon "SourceError"
213 {-# NOINLINE sourceErrorTc #-}
214 instance Typeable SourceError where
215   typeOf _ = Dyn.mkTyConApp sourceErrorTc []
216
217 instance Exception SourceError
218
219 mkSrcErr = SourceError
220
221 -- | Perform the given action and call the exception handler if the action
222 -- throws a 'SourceError'.  See 'SourceError' for more information.
223 handleSourceError :: (ExceptionMonad m) =>
224                      (SourceError -> m a) -- ^ exception handler
225                   -> m a -- ^ action to perform
226                   -> m a
227 handleSourceError handler act =
228   gcatch act (\(e :: SourceError) -> handler e)
229
230 srcErrorMessages (SourceError msgs) = msgs
231
232 -- | XXX: what exactly is an API error?
233 data GhcApiError = GhcApiError SDoc
234
235 instance Show GhcApiError where
236   show (GhcApiError msg) = showSDoc msg
237
238 ghcApiErrorTc :: Dyn.TyCon
239 ghcApiErrorTc = Dyn.mkTyCon "GhcApiError"
240 {-# NOINLINE ghcApiErrorTc #-}
241 instance Typeable GhcApiError where
242   typeOf _ = Dyn.mkTyConApp ghcApiErrorTc []
243
244 instance Exception GhcApiError
245
246 mkApiErr = GhcApiError
247
248 -- | A monad that allows logging of warnings.
249 class Monad m => WarnLogMonad m where
250   setWarnings  :: WarningMessages -> m ()
251   getWarnings :: m WarningMessages
252
253 logWarnings :: WarnLogMonad m => WarningMessages -> m ()
254 logWarnings warns = do
255     warns0 <- getWarnings
256     setWarnings (unionBags warns warns0)
257
258 -- | Clear the log of 'Warnings'.
259 clearWarnings :: WarnLogMonad m => m ()
260 clearWarnings = setWarnings emptyBag
261
262 -- | Returns true if there were any warnings.
263 hasWarnings :: WarnLogMonad m => m Bool
264 hasWarnings = getWarnings >>= return . not . isEmptyBag
265
266 -- | A monad that has all the features needed by GHC API calls.
267 --
268 -- In short, a GHC monad
269 --
270 --   - allows embedding of IO actions,
271 --
272 --   - can log warnings,
273 --
274 --   - allows handling of (extensible) exceptions, and
275 --
276 --   - maintains a current session.
277 --
278 -- If you do not use 'Ghc' or 'GhcT', make sure to call 'GHC.initGhcMonad'
279 -- before any call to the GHC API functions can occur.
280 --
281 class (Functor m, MonadIO m, WarnLogMonad m, ExceptionMonad m)
282     => GhcMonad m where
283   getSession :: m HscEnv
284   setSession :: HscEnv -> m ()
285
286 -- | Call the argument with the current session.
287 withSession :: GhcMonad m => (HscEnv -> m a) -> m a
288 withSession f = getSession >>= f
289
290 -- | Set the current session to the result of applying the current session to
291 -- the argument.
292 modifySession :: GhcMonad m => (HscEnv -> HscEnv) -> m ()
293 modifySession f = do h <- getSession
294                      setSession $! f h
295
296 -- | A minimal implementation of a 'GhcMonad'.  If you need a custom monad,
297 -- e.g., to maintain additional state consider wrapping this monad or using
298 -- 'GhcT'.
299 newtype Ghc a = Ghc { unGhc :: Session -> IO a }
300
301 instance Functor Ghc where
302   fmap f m = Ghc $ \s -> f `fmap` unGhc m s
303
304 instance Monad Ghc where
305   return a = Ghc $ \_ -> return a
306   m >>= g  = Ghc $ \s -> do a <- unGhc m s; unGhc (g a) s
307
308 instance MonadIO Ghc where
309   liftIO ioA = Ghc $ \_ -> ioA
310
311 instance ExceptionMonad Ghc where
312   gcatch act handle =
313       Ghc $ \s -> unGhc act s `gcatch` \e -> unGhc (handle e) s
314   gblock (Ghc m)   = Ghc $ \s -> gblock (m s)
315   gunblock (Ghc m) = Ghc $ \s -> gunblock (m s)
316
317 instance WarnLogMonad Ghc where
318   setWarnings warns = Ghc $ \(Session _ wref) -> writeIORef wref warns
319   -- | Return 'Warnings' accumulated so far.
320   getWarnings       = Ghc $ \(Session _ wref) -> readIORef wref
321
322 instance GhcMonad Ghc where
323   getSession = Ghc $ \(Session r _) -> readIORef r
324   setSession s' = Ghc $ \(Session r _) -> writeIORef r s'
325
326 -- | A monad transformer to add GHC specific features to another monad.
327 --
328 -- Note that the wrapped monad must support IO and handling of exceptions.
329 newtype GhcT m a = GhcT { unGhcT :: Session -> m a }
330 liftGhcT :: Monad m => m a -> GhcT m a
331 liftGhcT m = GhcT $ \_ -> m
332
333 instance Functor m => Functor (GhcT m) where
334   fmap f m = GhcT $ \s -> f `fmap` unGhcT m s
335
336 instance Monad m => Monad (GhcT m) where
337   return x = GhcT $ \_ -> return x
338   m >>= k  = GhcT $ \s -> do a <- unGhcT m s; unGhcT (k a) s
339
340 instance MonadIO m => MonadIO (GhcT m) where
341   liftIO ioA = GhcT $ \_ -> liftIO ioA
342
343 instance ExceptionMonad m => ExceptionMonad (GhcT m) where
344   gcatch act handle =
345       GhcT $ \s -> unGhcT act s `gcatch` \e -> unGhcT (handle e) s
346   gblock (GhcT m) = GhcT $ \s -> gblock (m s)
347   gunblock (GhcT m) = GhcT $ \s -> gunblock (m s)
348
349 instance MonadIO m => WarnLogMonad (GhcT m) where
350   setWarnings warns = GhcT $ \(Session _ wref) -> liftIO $ writeIORef wref warns
351   -- | Return 'Warnings' accumulated so far.
352   getWarnings       = GhcT $ \(Session _ wref) -> liftIO $ readIORef wref
353
354 instance (Functor m, ExceptionMonad m, MonadIO m) => GhcMonad (GhcT m) where
355   getSession = GhcT $ \(Session r _) -> liftIO $ readIORef r
356   setSession s' = GhcT $ \(Session r _) -> liftIO $ writeIORef r s'
357
358 -- | Lift an IO action returning errors messages into a 'GhcMonad'.
359 --
360 -- In order to reduce dependencies to other parts of the compiler, functions
361 -- outside the "main" parts of GHC return warnings and errors as a parameter
362 -- and signal success via by wrapping the result in a 'Maybe' type.  This
363 -- function logs the returned warnings and propagates errors as exceptions
364 -- (of type 'SourceError').
365 --
366 -- This function assumes the following invariants:
367 --
368 --  1. If the second result indicates success (is of the form 'Just x'),
369 --     there must be no error messages in the first result.
370 --
371 --  2. If there are no error messages, but the second result indicates failure
372 --     there should be warnings in the first result.  That is, if the action
373 --     failed, it must have been due to the warnings (i.e., @-Werror@).
374 ioMsgMaybe :: GhcMonad m =>
375               IO (Messages, Maybe a) -> m a
376 ioMsgMaybe ioA = do
377   ((warns,errs), mb_r) <- liftIO ioA
378   logWarnings warns
379   case mb_r of
380     Nothing -> liftIO $ throwIO (mkSrcErr errs)
381     Just r  -> ASSERT( isEmptyBag errs ) return r
382
383 -- | Lift a non-failing IO action into a 'GhcMonad'.
384 --
385 -- Like 'ioMsgMaybe', but assumes that the action will never return any error
386 -- messages.
387 ioMsg :: GhcMonad m => IO (Messages, a) -> m a
388 ioMsg ioA = do
389     ((warns,errs), r) <- liftIO ioA
390     logWarnings warns
391     ASSERT( isEmptyBag errs ) return r
392
393 -- | Reflect a computation in the 'Ghc' monad into the 'IO' monad.
394 --
395 -- You can use this to call functions returning an action in the 'Ghc' monad
396 -- inside an 'IO' action.  This is needed for some (too restrictive) callback
397 -- arguments of some library functions:
398 --
399 -- > libFunc :: String -> (Int -> IO a) -> IO a
400 -- > ghcFunc :: Int -> Ghc a
401 -- >
402 -- > ghcFuncUsingLibFunc :: String -> Ghc a -> Ghc a
403 -- > ghcFuncUsingLibFunc str =
404 -- >   reifyGhc $ \s ->
405 -- >     libFunc $ \i -> do
406 -- >       reflectGhc (ghcFunc i) s
407 --
408 reflectGhc :: Ghc a -> Session -> IO a
409 reflectGhc m = unGhc m
410
411 -- > Dual to 'reflectGhc'.  See its documentation.
412 reifyGhc :: (Session -> IO a) -> Ghc a
413 reifyGhc act = Ghc $ act
414
415 handleFlagWarnings :: GhcMonad m => DynFlags -> [Located String] -> m ()
416 handleFlagWarnings dflags warns
417  = when (dopt Opt_WarnDeprecatedFlags dflags)
418         (handleFlagWarnings' dflags warns)
419
420 handleFlagWarnings' :: GhcMonad m => DynFlags -> [Located String] -> m ()
421 handleFlagWarnings' _ [] = return ()
422 handleFlagWarnings' dflags warns
423  = do -- It would be nicer if warns :: [Located Message], but that has circular
424       -- import problems.
425       logWarnings $ listToBag (map mkFlagWarning warns)
426       when (dopt Opt_WarnIsError dflags) $
427         liftIO $ throwIO $ mkSrcErr emptyBag
428
429 mkFlagWarning :: Located String -> WarnMsg
430 mkFlagWarning (L loc warn)
431  = mkPlainWarnMsg loc (text warn)
432 \end{code}
433
434 \begin{code}
435 -- | HscEnv is like 'Session', except that some of the fields are immutable.
436 -- An HscEnv is used to compile a single module from plain Haskell source
437 -- code (after preprocessing) to either C, assembly or C--.  Things like
438 -- the module graph don't change during a single compilation.
439 --
440 -- Historical note: \"hsc\" used to be the name of the compiler binary,
441 -- when there was a separate driver and compiler.  To compile a single
442 -- module, the driver would invoke hsc on the source code... so nowadays
443 -- we think of hsc as the layer of the compiler that deals with compiling
444 -- a single module.
445 data HscEnv 
446   = HscEnv { 
447         hsc_dflags :: DynFlags,
448                 -- ^ The dynamic flag settings
449
450         hsc_targets :: [Target],
451                 -- ^ The targets (or roots) of the current session
452
453         hsc_mod_graph :: ModuleGraph,
454                 -- ^ The module graph of the current session
455
456         hsc_IC :: InteractiveContext,
457                 -- ^ The context for evaluating interactive statements
458
459         hsc_HPT    :: HomePackageTable,
460                 -- ^ The home package table describes already-compiled
461                 -- home-package modules, /excluding/ the module we 
462                 -- are compiling right now.
463                 -- (In one-shot mode the current module is the only
464                 --  home-package module, so hsc_HPT is empty.  All other
465                 --  modules count as \"external-package\" modules.
466                 --  However, even in GHCi mode, hi-boot interfaces are
467                 --  demand-loaded into the external-package table.)
468                 --
469                 -- 'hsc_HPT' is not mutable because we only demand-load 
470                 -- external packages; the home package is eagerly 
471                 -- loaded, module by module, by the compilation manager.
472                 --      
473                 -- The HPT may contain modules compiled earlier by @--make@
474                 -- but not actually below the current module in the dependency
475                 -- graph.
476
477                 -- (This changes a previous invariant: changed Jan 05.)
478         
479         hsc_EPS :: {-# UNPACK #-} !(IORef ExternalPackageState),
480                 -- ^ Information about the currently loaded external packages.
481                 -- This is mutable because packages will be demand-loaded during
482                 -- a compilation run as required.
483         
484         hsc_NC  :: {-# UNPACK #-} !(IORef NameCache),
485                 -- ^ As with 'hsc_EPS', this is side-effected by compiling to
486                 -- reflect sucking in interface files.  They cache the state of
487                 -- external interface files, in effect.
488
489         hsc_FC   :: {-# UNPACK #-} !(IORef FinderCache),
490                 -- ^ The cached result of performing finding in the file system
491         hsc_MLC  :: {-# UNPACK #-} !(IORef ModLocationCache),
492                 -- ^ This caches the location of modules, so we don't have to 
493                 -- search the filesystem multiple times. See also 'hsc_FC'.
494
495         hsc_OptFuel :: OptFuelState,
496                 -- ^ Settings to control the use of \"optimization fuel\":
497                 -- by limiting the number of transformations,
498                 -- we can use binary search to help find compiler bugs.
499
500         hsc_type_env_var :: Maybe (Module, IORef TypeEnv),
501                 -- ^ Used for one-shot compilation only, to initialise
502                 -- the 'IfGblEnv'. See 'TcRnTypes.tcg_type_env_var' for 
503                 -- 'TcRunTypes.TcGblEnv'
504
505         hsc_global_rdr_env :: GlobalRdrEnv,
506                 -- ^ A mapping from 'RdrName's that are in global scope during
507                 -- the compilation of the current file to more detailed
508                 -- information about those names. Not necessarily just the
509                 -- names directly imported by the module being compiled!
510         
511         hsc_global_type_env :: TypeEnv
512                 -- ^ Typing information about all those things in global scope.
513                 -- Not necessarily just the things directly imported by the module 
514                 -- being compiled!
515  }
516
517 hscEPS :: HscEnv -> IO ExternalPackageState
518 hscEPS hsc_env = readIORef (hsc_EPS hsc_env)
519
520 -- | A compilation target.
521 --
522 -- A target may be supplied with the actual text of the
523 -- module.  If so, use this instead of the file contents (this
524 -- is for use in an IDE where the file hasn't been saved by
525 -- the user yet).
526 data Target = Target
527       { targetId           :: TargetId  -- ^ module or filename
528       , targetAllowObjCode :: Bool      -- ^ object code allowed?
529       , targetContents     :: Maybe (StringBuffer,ClockTime)
530                                         -- ^ in-memory text buffer?
531       }
532
533 data TargetId
534   = TargetModule ModuleName
535         -- ^ A module name: search for the file
536   | TargetFile FilePath (Maybe Phase)
537         -- ^ A filename: preprocess & parse it to find the module name.
538         -- If specified, the Phase indicates how to compile this file
539         -- (which phase to start from).  Nothing indicates the starting phase
540         -- should be determined from the suffix of the filename.
541   deriving Eq
542
543 pprTarget :: Target -> SDoc
544 pprTarget (Target id obj _) = 
545    (if obj then char '*' else empty) <> pprTargetId id
546
547 instance Outputable Target where
548     ppr = pprTarget
549
550 pprTargetId :: TargetId -> SDoc
551 pprTargetId (TargetModule m) = ppr m
552 pprTargetId (TargetFile f _) = text f
553
554 instance Outputable TargetId where
555     ppr = pprTargetId
556
557 -- | Helps us find information about modules in the home package
558 type HomePackageTable  = ModuleNameEnv HomeModInfo
559         -- Domain = modules in the home package that have been fully compiled
560         -- "home" package name cached here for convenience
561
562 -- | Helps us find information about modules in the imported packages
563 type PackageIfaceTable = ModuleEnv ModIface
564         -- Domain = modules in the imported packages
565
566 emptyHomePackageTable :: HomePackageTable
567 emptyHomePackageTable  = emptyUFM
568
569 emptyPackageIfaceTable :: PackageIfaceTable
570 emptyPackageIfaceTable = emptyModuleEnv
571
572 -- | Information about modules in the package being compiled
573 data HomeModInfo 
574   = HomeModInfo {
575       hm_iface    :: !ModIface,
576         -- ^ The basic loaded interface file: every loaded module has one of
577         -- these, even if it is imported from another package
578       hm_details  :: !ModDetails,
579         -- ^ Extra information that has been created from the 'ModIface' for
580         -- the module, typically during typechecking
581       hm_linkable :: !(Maybe Linkable)
582         -- ^ The actual artifact we would like to link to access things in
583         -- this module.
584         --
585         -- 'hm_linkable' might be Nothing:
586         --
587         --   1. If this is an .hs-boot module
588         --
589         --   2. Temporarily during compilation if we pruned away
590         --      the old linkable because it was out of date.
591         --
592         -- After a complete compilation ('GHC.load'), all 'hm_linkable' fields
593         -- in the 'HomePackageTable' will be @Just@.
594         --
595         -- When re-linking a module ('HscMain.HscNoRecomp'), we construct the
596         -- 'HomeModInfo' by building a new 'ModDetails' from the old
597         -- 'ModIface' (only).
598     }
599
600 -- | Find the 'ModIface' for a 'Module', searching in both the loaded home
601 -- and external package module information
602 lookupIfaceByModule
603         :: DynFlags
604         -> HomePackageTable
605         -> PackageIfaceTable
606         -> Module
607         -> Maybe ModIface
608 lookupIfaceByModule dflags hpt pit mod
609   | modulePackageId mod == thisPackage dflags
610   =     -- The module comes from the home package, so look first
611         -- in the HPT.  If it's not from the home package it's wrong to look
612         -- in the HPT, because the HPT is indexed by *ModuleName* not Module
613     fmap hm_iface (lookupUFM hpt (moduleName mod)) 
614     `mplus` lookupModuleEnv pit mod
615
616   | otherwise = lookupModuleEnv pit mod         -- Look in PIT only 
617
618 -- If the module does come from the home package, why do we look in the PIT as well?
619 -- (a) In OneShot mode, even home-package modules accumulate in the PIT
620 -- (b) Even in Batch (--make) mode, there is *one* case where a home-package
621 --     module is in the PIT, namely GHC.Prim when compiling the base package.
622 -- We could eliminate (b) if we wanted, by making GHC.Prim belong to a package
623 -- of its own, but it doesn't seem worth the bother.
624 \end{code}
625
626
627 \begin{code}
628 hptInstances :: HscEnv -> (ModuleName -> Bool) -> ([Instance], [FamInst])
629 -- ^ Find all the instance declarations (of classes and families) that are in
630 -- modules imported by this one, directly or indirectly, and are in the Home
631 -- Package Table.  This ensures that we don't see instances from modules @--make@
632 -- compiled before this one, but which are not below this one.
633 hptInstances hsc_env want_this_module
634   = let (insts, famInsts) = unzip $ flip hptAllThings hsc_env $ \mod_info -> do
635                 guard (want_this_module (moduleName (mi_module (hm_iface mod_info))))
636                 let details = hm_details mod_info
637                 return (md_insts details, md_fam_insts details)
638     in (concat insts, concat famInsts)
639
640 hptVectInfo :: HscEnv -> VectInfo
641 -- ^ Get the combined VectInfo of all modules in the home package table.  In
642 -- contrast to instances and rules, we don't care whether the modules are
643 -- \"below\" us in the dependency sense.  The VectInfo of those modules not \"below\" 
644 -- us does not affect the compilation of the current module.
645 hptVectInfo = concatVectInfo . hptAllThings ((: []) . md_vect_info . hm_details)
646
647 hptRules :: HscEnv -> [(ModuleName, IsBootInterface)] -> [CoreRule]
648 -- ^ Get rules from modules \"below\" this one (in the dependency sense)
649 hptRules = hptSomeThingsBelowUs (md_rules . hm_details) False
650
651
652 hptAnns :: HscEnv -> Maybe [(ModuleName, IsBootInterface)] -> [Annotation]
653 -- ^ Get annotations from modules \"below\" this one (in the dependency sense)
654 hptAnns hsc_env (Just deps) = hptSomeThingsBelowUs (md_anns . hm_details) False hsc_env deps
655 hptAnns hsc_env Nothing = hptAllThings (md_anns . hm_details) hsc_env
656
657 hptAllThings :: (HomeModInfo -> [a]) -> HscEnv -> [a]
658 hptAllThings extract hsc_env = concatMap extract (eltsUFM (hsc_HPT hsc_env))
659
660 hptSomeThingsBelowUs :: (HomeModInfo -> [a]) -> Bool -> HscEnv -> [(ModuleName, IsBootInterface)] -> [a]
661 -- Get things from modules \"below\" this one (in the dependency sense)
662 -- C.f Inst.hptInstances
663 hptSomeThingsBelowUs extract include_hi_boot hsc_env deps
664  | isOneShot (ghcMode (hsc_dflags hsc_env)) = []
665   | otherwise
666   = let 
667         hpt = hsc_HPT hsc_env
668     in
669     [ thing
670     |   -- Find each non-hi-boot module below me
671       (mod, is_boot_mod) <- deps
672     , include_hi_boot || not is_boot_mod
673
674         -- unsavoury: when compiling the base package with --make, we
675         -- sometimes try to look up RULES etc for GHC.Prim.  GHC.Prim won't
676         -- be in the HPT, because we never compile it; it's in the EPT
677         -- instead.  ToDo: clean up, and remove this slightly bogus
678         -- filter:
679     , mod /= moduleName gHC_PRIM
680
681         -- Look it up in the HPT
682     , let things = case lookupUFM hpt mod of
683                     Just info -> extract info
684                     Nothing -> pprTrace "WARNING in hptSomeThingsBelowUs" msg [] 
685           msg = vcat [ptext (sLit "missing module") <+> ppr mod,
686                       ptext (sLit "Probable cause: out-of-date interface files")]
687                         -- This really shouldn't happen, but see Trac #962
688
689         -- And get its dfuns
690     , thing <- things ]
691 \end{code}
692
693 %************************************************************************
694 %*                                                                      *
695 \subsection{Dealing with Annotations}
696 %*                                                                      *
697 %************************************************************************
698
699 \begin{code}
700 prepareAnnotations :: HscEnv -> Maybe ModGuts -> IO AnnEnv
701 -- ^ Deal with gathering annotations in from all possible places 
702 --   and combining them into a single 'AnnEnv'
703 prepareAnnotations hsc_env mb_guts
704   = do { eps <- hscEPS hsc_env
705        ; let -- Extract annotations from the module being compiled if supplied one
706             mb_this_module_anns = fmap (mkAnnEnv . mg_anns) mb_guts
707         -- Extract dependencies of the module if we are supplied one,
708         -- otherwise load annotations from all home package table
709         -- entries regardless of dependency ordering.
710             home_pkg_anns  = (mkAnnEnv . hptAnns hsc_env) $ fmap (dep_mods . mg_deps) mb_guts
711             other_pkg_anns = eps_ann_env eps
712             ann_env        = foldl1' plusAnnEnv $ catMaybes [mb_this_module_anns, 
713                                                              Just home_pkg_anns, 
714                                                              Just other_pkg_anns]
715
716        ; return ann_env }
717 \end{code}
718
719 %************************************************************************
720 %*                                                                      *
721 \subsection{The Finder cache}
722 %*                                                                      *
723 %************************************************************************
724
725 \begin{code}
726 -- | The 'FinderCache' maps home module names to the result of
727 -- searching for that module.  It records the results of searching for
728 -- modules along the search path.  On @:load@, we flush the entire
729 -- contents of this cache.
730 --
731 -- Although the @FinderCache@ range is 'FindResult' for convenience ,
732 -- in fact it will only ever contain 'Found' or 'NotFound' entries.
733 --
734 type FinderCache = ModuleNameEnv FindResult
735
736 -- | The result of searching for an imported module.
737 data FindResult
738   = Found ModLocation Module
739         -- ^ The module was found
740   | NoPackage PackageId
741         -- ^ The requested package was not found
742   | FoundMultiple [PackageId]
743         -- ^ _Error_: both in multiple packages
744   | PackageHidden PackageId
745         -- ^ For an explicit source import, the package containing the module is
746         -- not exposed.
747   | ModuleHidden  PackageId
748         -- ^ For an explicit source import, the package containing the module is
749         -- exposed, but the module itself is hidden.
750   | NotFound [FilePath] (Maybe PackageId)
751         -- ^ The module was not found, the specified places were searched
752   | NotFoundInPackage PackageId
753         -- ^ The module was not found in this package
754
755 -- | Cache that remembers where we found a particular module.  Contains both
756 -- home modules and package modules.  On @:load@, only home modules are
757 -- purged from this cache.
758 type ModLocationCache = ModuleEnv ModLocation
759 \end{code}
760
761 %************************************************************************
762 %*                                                                      *
763 \subsection{Symbol tables and Module details}
764 %*                                                                      *
765 %************************************************************************
766
767 \begin{code}
768 -- | A 'ModIface' plus a 'ModDetails' summarises everything we know 
769 -- about a compiled module.  The 'ModIface' is the stuff *before* linking,
770 -- and can be written out to an interface file. The 'ModDetails is after 
771 -- linking and can be completely recovered from just the 'ModIface'.
772 -- 
773 -- When we read an interface file, we also construct a 'ModIface' from it,
774 -- except that we explicitly make the 'mi_decls' and a few other fields empty;
775 -- as when reading we consolidate the declarations etc. into a number of indexed
776 -- maps and environments in the 'ExternalPackageState'.
777 data ModIface 
778    = ModIface {
779         mi_module   :: !Module,             -- ^ Name of the module we are for
780         mi_iface_hash :: !Fingerprint,      -- ^ Hash of the whole interface
781         mi_mod_hash :: !Fingerprint,        -- ^ Hash of the ABI only
782
783         mi_orphan   :: !WhetherHasOrphans,  -- ^ Whether this module has orphans
784         mi_finsts   :: !WhetherHasFamInst,  -- ^ Whether this module has family instances
785         mi_boot     :: !IsBootInterface,    -- ^ Read from an hi-boot file?
786
787         mi_deps     :: Dependencies,
788                 -- ^ The dependencies of the module, consulted for directly
789                 -- imported modules only
790         
791                 -- This is consulted for directly-imported modules,
792                 -- but not for anything else (hence lazy)
793         mi_usages   :: [Usage],
794                 -- ^ Usages; kept sorted so that it's easy to decide
795                 -- whether to write a new iface file (changing usages
796                 -- doesn't affect the hash of this module)
797         
798                 -- NOT STRICT!  we read this field lazily from the interface file
799                 -- It is *only* consulted by the recompilation checker
800
801                 -- Exports
802                 -- Kept sorted by (mod,occ), to make version comparisons easier
803         mi_exports  :: ![IfaceExport],
804                 -- ^ Records the modules that are the declaration points for things
805                 -- exported by this module, and the 'OccName's of those things
806         
807         mi_exp_hash :: !Fingerprint,    -- ^ Hash of export list
808
809         mi_fixities :: [(OccName,Fixity)],
810                 -- ^ Fixities
811         
812                 -- NOT STRICT!  we read this field lazily from the interface file
813
814         mi_warns  :: Warnings,
815                 -- ^ Warnings
816                 
817                 -- NOT STRICT!  we read this field lazily from the interface file
818
819         mi_anns  :: [IfaceAnnotation],
820                 -- ^ Annotations
821         
822                 -- NOT STRICT!  we read this field lazily from the interface file
823
824                 -- Type, class and variable declarations
825                 -- The hash of an Id changes if its fixity or deprecations change
826                 --      (as well as its type of course)
827                 -- Ditto data constructors, class operations, except that 
828                 -- the hash of the parent class/tycon changes
829         mi_decls :: [(Fingerprint,IfaceDecl)],  -- ^ Sorted type, variable, class etc. declarations
830
831         mi_globals  :: !(Maybe GlobalRdrEnv),
832                 -- ^ Binds all the things defined at the top level in
833                 -- the /original source/ code for this module. which
834                 -- is NOT the same as mi_exports, nor mi_decls (which
835                 -- may contains declarations for things not actually
836                 -- defined by the user).  Used for GHCi and for inspecting
837                 -- the contents of modules via the GHC API only.
838                 --
839                 -- (We need the source file to figure out the
840                 -- top-level environment, if we didn't compile this module
841                 -- from source then this field contains @Nothing@).
842                 --
843                 -- Strictly speaking this field should live in the
844                 -- 'HomeModInfo', but that leads to more plumbing.
845
846                 -- Instance declarations and rules
847         mi_insts     :: [IfaceInst],                    -- ^ Sorted class instance
848         mi_fam_insts :: [IfaceFamInst],                 -- ^ Sorted family instances
849         mi_rules     :: [IfaceRule],                    -- ^ Sorted rules
850         mi_orphan_hash :: !Fingerprint, -- ^ Hash for orphan rules and 
851                                         -- class and family instances
852                                         -- combined
853
854         mi_vect_info :: !IfaceVectInfo, -- ^ Vectorisation information
855
856                 -- Cached environments for easy lookup
857                 -- These are computed (lazily) from other fields
858                 -- and are not put into the interface file
859         mi_warn_fn  :: Name -> Maybe WarningTxt,        -- ^ Cached lookup for 'mi_warns'
860         mi_fix_fn  :: OccName -> Fixity,                -- ^ Cached lookup for 'mi_fixities'
861         mi_hash_fn :: OccName -> Maybe (OccName, Fingerprint),
862                         -- ^ Cached lookup for 'mi_decls'.
863                         -- The @Nothing@ in 'mi_hash_fn' means that the thing
864                         -- isn't in decls. It's useful to know that when
865                         -- seeing if we are up to date wrt. the old interface.
866                         -- The 'OccName' is the parent of the name, if it has one.
867         mi_hpc    :: !AnyHpcUsage
868                 -- ^ True if this program uses Hpc at any point in the program.
869      }
870
871 -- | The 'ModDetails' is essentially a cache for information in the 'ModIface'
872 -- for home modules only. Information relating to packages will be loaded into
873 -- global environments in 'ExternalPackageState'.
874 data ModDetails
875    = ModDetails {
876         -- The next two fields are created by the typechecker
877         md_exports   :: [AvailInfo],
878         md_types     :: !TypeEnv,       -- ^ Local type environment for this particular module
879         md_insts     :: ![Instance],    -- ^ 'DFunId's for the instances in this module
880         md_fam_insts :: ![FamInst],
881         md_rules     :: ![CoreRule],    -- ^ Domain may include 'Id's from other modules
882         md_anns      :: ![Annotation],  -- ^ Annotations present in this module: currently 
883                                         -- they only annotate things also declared in this module
884         md_vect_info :: !VectInfo       -- ^ Module vectorisation information
885      }
886
887 emptyModDetails :: ModDetails
888 emptyModDetails = ModDetails { md_types = emptyTypeEnv,
889                                md_exports = [],
890                                md_insts     = [],
891                                md_rules     = [],
892                                md_fam_insts = [],
893                                md_anns      = [],
894                                md_vect_info = noVectInfo
895                              } 
896
897 -- | Records the modules directly imported by a module for extracting e.g. usage information
898 type ImportedMods = ModuleEnv [(ModuleName, Bool, SrcSpan)]
899 -- TODO: we are not actually using the codomain of this type at all, so it can be
900 -- replaced with ModuleEnv ()
901
902 -- | A ModGuts is carried through the compiler, accumulating stuff as it goes
903 -- There is only one ModGuts at any time, the one for the module
904 -- being compiled right now.  Once it is compiled, a 'ModIface' and 
905 -- 'ModDetails' are extracted and the ModGuts is dicarded.
906 data ModGuts
907   = ModGuts {
908         mg_module    :: !Module,         -- ^ Module being compiled
909         mg_boot      :: IsBootInterface, -- ^ Whether it's an hs-boot module
910         mg_exports   :: ![AvailInfo],    -- ^ What it exports
911         mg_deps      :: !Dependencies,   -- ^ What it depends on, directly or
912                                          -- otherwise
913         mg_dir_imps  :: !ImportedMods,   -- ^ Directly-imported modules; used to
914                                          -- generate initialisation code
915         mg_used_names:: !NameSet,        -- ^ What the module needed (used in 'MkIface.mkIface')
916
917         mg_rdr_env   :: !GlobalRdrEnv,   -- ^ Top-level lexical environment
918
919         -- These fields all describe the things **declared in this module**
920         mg_fix_env   :: !FixityEnv,      -- ^ Fixities declared in this module
921                                          -- TODO: I'm unconvinced this is actually used anywhere
922         mg_types     :: !TypeEnv,        -- ^ Types declared in this module
923         mg_insts     :: ![Instance],     -- ^ Class instances declared in this module
924         mg_fam_insts :: ![FamInst],      -- ^ Family instances declared in this module
925         mg_rules     :: ![CoreRule],     -- ^ Before the core pipeline starts, contains 
926                                          -- rules declared in this module. After the core
927                                          -- pipeline starts, it is changed to contain all
928                                          -- known rules for those things imported
929         mg_binds     :: ![CoreBind],     -- ^ Bindings for this module
930         mg_foreign   :: !ForeignStubs,   -- ^ Foreign exports declared in this module
931         mg_warns     :: !Warnings,       -- ^ Warnings declared in the module
932         mg_anns      :: [Annotation],    -- ^ Annotations declared in this module
933         mg_hpc_info  :: !HpcInfo,        -- ^ Coverage tick boxes in the module
934         mg_modBreaks :: !ModBreaks,      -- ^ Breakpoints for the module
935         mg_vect_info :: !VectInfo,       -- ^ Pool of vectorised declarations in the module
936
937         -- The next two fields are unusual, because they give instance
938         -- environments for *all* modules in the home package, including
939         -- this module, rather than for *just* this module.  
940         -- Reason: when looking up an instance we don't want to have to
941         --        look at each module in the home package in turn
942         mg_inst_env     :: InstEnv,
943         -- ^ Class instance environment from /home-package/ modules (including
944         -- this one); c.f. 'tcg_inst_env'
945         mg_fam_inst_env :: FamInstEnv
946         -- ^ Type-family instance enviroment for /home-package/ modules
947         -- (including this one); c.f. 'tcg_fam_inst_env'
948     }
949
950 -- The ModGuts takes on several slightly different forms:
951 --
952 -- After simplification, the following fields change slightly:
953 --      mg_rules        Orphan rules only (local ones now attached to binds)
954 --      mg_binds        With rules attached
955
956 -- | A CoreModule consists of just the fields of a 'ModGuts' that are needed for
957 -- the 'GHC.compileToCoreModule' interface.
958 data CoreModule
959   = CoreModule {
960       -- | Module name
961       cm_module   :: !Module,
962       -- | Type environment for types declared in this module
963       cm_types    :: !TypeEnv,
964       -- | Declarations
965       cm_binds    :: [CoreBind],
966       -- | Imports
967       cm_imports  :: ![Module]
968     }
969
970 instance Outputable CoreModule where
971    ppr (CoreModule {cm_module = mn, cm_types = te, cm_binds = cb}) =
972       text "%module" <+> ppr mn <+> ppr te $$ vcat (map ppr cb)
973
974 -- The ModGuts takes on several slightly different forms:
975 --
976 -- After simplification, the following fields change slightly:
977 --      mg_rules        Orphan rules only (local ones now attached to binds)
978 --      mg_binds        With rules attached
979
980
981 ---------------------------------------------------------
982 -- The Tidy pass forks the information about this module: 
983 --      * one lot goes to interface file generation (ModIface)
984 --        and later compilations (ModDetails)
985 --      * the other lot goes to code generation (CgGuts)
986
987 -- | A restricted form of 'ModGuts' for code generation purposes
988 data CgGuts 
989   = CgGuts {
990         cg_module   :: !Module, -- ^ Module being compiled
991
992         cg_tycons   :: [TyCon],
993                 -- ^ Algebraic data types (including ones that started
994                 -- life as classes); generate constructors and info
995                 -- tables. Includes newtypes, just for the benefit of
996                 -- External Core
997
998         cg_binds    :: [CoreBind],
999                 -- ^ The tidied main bindings, including
1000                 -- previously-implicit bindings for record and class
1001                 -- selectors, and data construtor wrappers.  But *not*
1002                 -- data constructor workers; reason: we we regard them
1003                 -- as part of the code-gen of tycons
1004
1005         cg_dir_imps :: ![Module],
1006                 -- ^ Directly-imported modules; used to generate
1007                 -- initialisation code
1008
1009         cg_foreign  :: !ForeignStubs,   -- ^ Foreign export stubs
1010         cg_dep_pkgs :: ![PackageId],    -- ^ Dependent packages, used to 
1011                                         -- generate #includes for C code gen
1012         cg_hpc_info :: !HpcInfo,        -- ^ Program coverage tick box information
1013         cg_modBreaks :: !ModBreaks      -- ^ Module breakpoints
1014     }
1015
1016 -----------------------------------
1017 -- | Foreign export stubs
1018 data ForeignStubs = NoStubs             -- ^ We don't have any stubs
1019                   | ForeignStubs
1020                         SDoc            
1021                         SDoc            
1022                    -- ^ There are some stubs. Parameters:
1023                    --
1024                    --  1) Header file prototypes for
1025                    --     "foreign exported" functions
1026                    --
1027                    --  2) C stubs to use when calling
1028                    --     "foreign exported" functions
1029 \end{code}
1030
1031 \begin{code}
1032 emptyModIface :: Module -> ModIface
1033 emptyModIface mod
1034   = ModIface { mi_module   = mod,
1035                mi_iface_hash = fingerprint0,
1036                mi_mod_hash = fingerprint0,
1037                mi_orphan   = False,
1038                mi_finsts   = False,
1039                mi_boot     = False,
1040                mi_deps     = noDependencies,
1041                mi_usages   = [],
1042                mi_exports  = [],
1043                mi_exp_hash = fingerprint0,
1044                mi_fixities = [],
1045                mi_warns    = NoWarnings,
1046                mi_anns     = [],
1047                mi_insts     = [],
1048                mi_fam_insts = [],
1049                mi_rules     = [],
1050                mi_decls     = [],
1051                mi_globals   = Nothing,
1052                mi_orphan_hash = fingerprint0,
1053                mi_vect_info = noIfaceVectInfo,
1054                mi_warn_fn    = emptyIfaceWarnCache,
1055                mi_fix_fn    = emptyIfaceFixCache,
1056                mi_hash_fn   = emptyIfaceHashCache,
1057                mi_hpc       = False
1058     }           
1059 \end{code}
1060
1061
1062 %************************************************************************
1063 %*                                                                      *
1064 \subsection{The interactive context}
1065 %*                                                                      *
1066 %************************************************************************
1067
1068 \begin{code}
1069 -- | Interactive context, recording information relevant to GHCi
1070 data InteractiveContext 
1071   = InteractiveContext { 
1072         ic_toplev_scope :: [Module],    -- ^ The context includes the "top-level" scope of
1073                                         -- these modules
1074
1075         ic_exports :: [Module],         -- ^ The context includes just the exports of these
1076                                         -- modules
1077
1078         ic_rn_gbl_env :: GlobalRdrEnv,  -- ^ The contexts' cached 'GlobalRdrEnv', built from
1079                                         -- 'ic_toplev_scope' and 'ic_exports'
1080
1081         ic_tmp_ids :: [Id],             -- ^ Names bound during interaction with the user.
1082                                         -- Later Ids shadow earlier ones with the same OccName.
1083
1084         ic_tyvars :: TyVarSet           -- ^ Skolem type variables free in
1085                                         -- 'ic_tmp_ids'.  These arise at
1086                                         -- breakpoints in a polymorphic 
1087                                         -- context, where we have only partial
1088                                         -- type information.
1089
1090 #ifdef GHCI
1091         , ic_resume :: [Resume]         -- ^ The stack of breakpoint contexts
1092 #endif
1093     }
1094
1095
1096 emptyInteractiveContext :: InteractiveContext
1097 emptyInteractiveContext
1098   = InteractiveContext { ic_toplev_scope = [],
1099                          ic_exports = [],
1100                          ic_rn_gbl_env = emptyGlobalRdrEnv,
1101                          ic_tmp_ids = [],
1102                          ic_tyvars = emptyVarSet
1103 #ifdef GHCI
1104                          , ic_resume = []
1105 #endif
1106                        }
1107
1108 icPrintUnqual :: DynFlags -> InteractiveContext -> PrintUnqualified
1109 icPrintUnqual dflags ictxt = mkPrintUnqualified dflags (ic_rn_gbl_env ictxt)
1110
1111
1112 extendInteractiveContext
1113         :: InteractiveContext
1114         -> [Id]
1115         -> TyVarSet
1116         -> InteractiveContext
1117 extendInteractiveContext ictxt ids tyvars
1118   = ictxt { ic_tmp_ids =  snub((ic_tmp_ids ictxt \\ ids) ++ ids),
1119                           -- NB. must be this way around, because we want
1120                           -- new ids to shadow existing bindings.
1121             ic_tyvars   = ic_tyvars ictxt `unionVarSet` tyvars }
1122     where snub = map head . group . sort
1123
1124 substInteractiveContext :: InteractiveContext -> TvSubst -> InteractiveContext
1125 substInteractiveContext ictxt subst | isEmptyTvSubst subst = ictxt
1126 substInteractiveContext ictxt@InteractiveContext{ic_tmp_ids=ids} subst =
1127    let ids'     = map (\id -> id `setIdType` substTy subst (idType id)) ids
1128        subst_dom= varEnvKeys$ getTvSubstEnv subst
1129        subst_ran= varEnvElts$ getTvSubstEnv subst
1130        new_tvs  = [ tv | Just tv <- map getTyVar_maybe subst_ran]  
1131        ic_tyvars'= (`delVarSetListByKey` subst_dom) 
1132                  . (`extendVarSetList`   new_tvs)
1133                    $ ic_tyvars ictxt
1134     in ictxt { ic_tmp_ids = ids'
1135              , ic_tyvars   = ic_tyvars' }
1136
1137           where delVarSetListByKey = foldl' delVarSetByKey
1138 \end{code}
1139
1140 %************************************************************************
1141 %*                                                                      *
1142         Building a PrintUnqualified             
1143 %*                                                                      *
1144 %************************************************************************
1145
1146 Deciding how to print names is pretty tricky.  We are given a name
1147 P:M.T, where P is the package name, M is the defining module, and T is
1148 the occurrence name, and we have to decide in which form to display
1149 the name given a GlobalRdrEnv describing the current scope.
1150
1151 Ideally we want to display the name in the form in which it is in
1152 scope.  However, the name might not be in scope at all, and that's
1153 where it gets tricky.  Here are the cases:
1154
1155  1. T   uniquely maps to  P:M.T                         --->  "T"
1156  2. there is an X for which X.T uniquely maps to  P:M.T --->  "X.T"
1157  3. there is no binding for "M.T"                       --->  "M.T"
1158  4. otherwise                                           --->  "P:M.T"
1159
1160 3 and 4 apply when P:M.T is not in scope.  In these cases we want to
1161 refer to the name as "M.T", but "M.T" might mean something else in the
1162 current scope (e.g. if there's an "import X as M"), so to avoid
1163 confusion we avoid using "M.T" if there's already a binding for it.
1164
1165 There's one further subtlety: if the module M cannot be imported
1166 because it is not exposed by any package, then we must refer to it as
1167 "P:M".  This is handled by the qual_mod component of PrintUnqualified.
1168
1169 \begin{code}
1170 -- | Creates some functions that work out the best ways to format
1171 -- names for the user according to a set of heuristics
1172 mkPrintUnqualified :: DynFlags -> GlobalRdrEnv -> PrintUnqualified
1173 mkPrintUnqualified dflags env = (qual_name, qual_mod)
1174   where
1175   qual_name mod occ     -- The (mod,occ) pair is the original name of the thing
1176         | [gre] <- unqual_gres, right_name gre = NameUnqual
1177                 -- If there's a unique entity that's in scope unqualified with 'occ'
1178                 -- AND that entity is the right one, then we can use the unqualified name
1179
1180         | [gre] <- qual_gres = NameQual (get_qual_mod (gre_prov gre))
1181
1182         | null qual_gres = 
1183               if null (lookupGRE_RdrName (mkRdrQual (moduleName mod) occ) env)
1184                    then NameNotInScope1
1185                    else NameNotInScope2
1186
1187         | otherwise = panic "mkPrintUnqualified"
1188       where
1189         right_name gre = nameModule_maybe (gre_name gre) == Just mod
1190
1191         unqual_gres = lookupGRE_RdrName (mkRdrUnqual occ) env
1192         qual_gres   = filter right_name (lookupGlobalRdrEnv env occ)
1193
1194         get_qual_mod LocalDef      = moduleName mod
1195         get_qual_mod (Imported is) = ASSERT( not (null is) ) is_as (is_decl (head is))
1196
1197     -- we can mention a module P:M without the P: qualifier iff
1198     -- "import M" would resolve unambiguously to P:M.  (if P is the
1199     -- current package we can just assume it is unqualified).
1200
1201   qual_mod mod
1202      | modulePackageId mod == thisPackage dflags = False
1203
1204      | [pkgconfig] <- [pkg | (pkg,exposed_module) <- lookup, 
1205                              exposed pkg && exposed_module],
1206        packageConfigId pkgconfig == modulePackageId mod
1207         -- this says: we are given a module P:M, is there just one exposed package
1208         -- that exposes a module M, and is it package P?
1209      = False
1210
1211      | otherwise = True
1212      where lookup = lookupModuleInAllPackages dflags (moduleName mod)
1213 \end{code}
1214
1215
1216 %************************************************************************
1217 %*                                                                      *
1218                 TyThing
1219 %*                                                                      *
1220 %************************************************************************
1221
1222 \begin{code}
1223 -- | Determine the 'TyThing's brought into scope by another 'TyThing'
1224 -- /other/ than itself. For example, Id's don't have any implicit TyThings
1225 -- as they just bring themselves into scope, but classes bring their
1226 -- dictionary datatype, type constructor and some selector functions into
1227 -- scope, just for a start!
1228
1229 -- N.B. the set of TyThings returned here *must* match the set of
1230 -- names returned by LoadIface.ifaceDeclSubBndrs, in the sense that
1231 -- TyThing.getOccName should define a bijection between the two lists.
1232 -- This invariant is used in LoadIface.loadDecl (see note [Tricky iface loop])
1233 -- The order of the list does not matter.
1234 implicitTyThings :: TyThing -> [TyThing]
1235
1236 -- For data and newtype declarations:
1237 implicitTyThings (ATyCon tc) = 
1238     -- fields (names of selectors)
1239     map AnId (tyConSelIds tc) ++ 
1240     -- (possibly) implicit coercion and family coercion
1241     --   depending on whether it's a newtype or a family instance or both
1242     implicitCoTyCon tc ++
1243     -- for each data constructor in order,
1244     --   the contructor, worker, and (possibly) wrapper
1245     concatMap (extras_plus . ADataCon) (tyConDataCons tc)
1246                      
1247 implicitTyThings (AClass cl) 
1248   = -- dictionary datatype:
1249     --    [extras_plus:]
1250     --      type constructor 
1251     --    [recursive call:]
1252     --      (possibly) newtype coercion; definitely no family coercion here
1253     --      data constructor
1254     --      worker
1255     --      (no wrapper by invariant)
1256     extras_plus (ATyCon (classTyCon cl)) ++
1257     -- associated types 
1258     --    No extras_plus (recursive call) for the classATs, because they
1259     --    are only the family decls; they have no implicit things
1260     map ATyCon (classATs cl) ++
1261     -- superclass and operation selectors
1262     map AnId (classSelIds cl)
1263
1264 implicitTyThings (ADataCon dc) = 
1265     -- For data cons add the worker and (possibly) wrapper
1266     map AnId (dataConImplicitIds dc)
1267
1268 implicitTyThings (AnId _)   = []
1269
1270 -- add a thing and recursive call
1271 extras_plus :: TyThing -> [TyThing]
1272 extras_plus thing = thing : implicitTyThings thing
1273
1274 -- For newtypes and indexed data types (and both),
1275 -- add the implicit coercion tycon
1276 implicitCoTyCon :: TyCon -> [TyThing]
1277 implicitCoTyCon tc 
1278   = map ATyCon . catMaybes $ [-- Just if newtype, Nothing if not
1279                               newTyConCo_maybe tc, 
1280                               -- Just if family instance, Nothing if not
1281                                 tyConFamilyCoercion_maybe tc] 
1282
1283 -- sortByOcc = sortBy (\ x -> \ y -> getOccName x < getOccName y)
1284
1285
1286 -- | Returns @True@ if there should be no interface-file declaration
1287 -- for this thing on its own: either it is built-in, or it is part
1288 -- of some other declaration, or it is generated implicitly by some
1289 -- other declaration.
1290 isImplicitTyThing :: TyThing -> Bool
1291 isImplicitTyThing (ADataCon _)  = True
1292 isImplicitTyThing (AnId     id) = isImplicitId id
1293 isImplicitTyThing (AClass   _)  = False
1294 isImplicitTyThing (ATyCon   tc) = isImplicitTyCon tc
1295
1296 extendTypeEnvWithIds :: TypeEnv -> [Id] -> TypeEnv
1297 extendTypeEnvWithIds env ids
1298   = extendNameEnvList env [(getName id, AnId id) | id <- ids]
1299 \end{code}
1300
1301 %************************************************************************
1302 %*                                                                      *
1303                 TypeEnv
1304 %*                                                                      *
1305 %************************************************************************
1306
1307 \begin{code}
1308 -- | A map from 'Name's to 'TyThing's, constructed by typechecking
1309 -- local declarations or interface files
1310 type TypeEnv = NameEnv TyThing
1311
1312 emptyTypeEnv    :: TypeEnv
1313 typeEnvElts     :: TypeEnv -> [TyThing]
1314 typeEnvClasses  :: TypeEnv -> [Class]
1315 typeEnvTyCons   :: TypeEnv -> [TyCon]
1316 typeEnvIds      :: TypeEnv -> [Id]
1317 typeEnvDataCons :: TypeEnv -> [DataCon]
1318 lookupTypeEnv   :: TypeEnv -> Name -> Maybe TyThing
1319
1320 emptyTypeEnv        = emptyNameEnv
1321 typeEnvElts     env = nameEnvElts env
1322 typeEnvClasses  env = [cl | AClass cl   <- typeEnvElts env]
1323 typeEnvTyCons   env = [tc | ATyCon tc   <- typeEnvElts env] 
1324 typeEnvIds      env = [id | AnId id     <- typeEnvElts env] 
1325 typeEnvDataCons env = [dc | ADataCon dc <- typeEnvElts env] 
1326
1327 mkTypeEnv :: [TyThing] -> TypeEnv
1328 mkTypeEnv things = extendTypeEnvList emptyTypeEnv things
1329                 
1330 lookupTypeEnv = lookupNameEnv
1331
1332 -- Extend the type environment
1333 extendTypeEnv :: TypeEnv -> TyThing -> TypeEnv
1334 extendTypeEnv env thing = extendNameEnv env (getName thing) thing 
1335
1336 extendTypeEnvList :: TypeEnv -> [TyThing] -> TypeEnv
1337 extendTypeEnvList env things = foldl extendTypeEnv env things
1338 \end{code}
1339
1340 \begin{code}
1341 -- | Find the 'TyThing' for the given 'Name' by using all the resources
1342 -- at our disposal: the compiled modules in the 'HomePackageTable' and the
1343 -- compiled modules in other packages that live in 'PackageTypeEnv'. Note
1344 -- that this does NOT look up the 'TyThing' in the module being compiled: you
1345 -- have to do that yourself, if desired
1346 lookupType :: DynFlags
1347            -> HomePackageTable
1348            -> PackageTypeEnv
1349            -> Name
1350            -> Maybe TyThing
1351
1352 lookupType dflags hpt pte name
1353   -- in one-shot, we don't use the HPT
1354   | not (isOneShot (ghcMode dflags)) && modulePackageId mod == this_pkg 
1355   = do hm <- lookupUFM hpt (moduleName mod) -- Maybe monad
1356        lookupNameEnv (md_types (hm_details hm)) name
1357   | otherwise
1358   = lookupNameEnv pte name
1359   where mod = ASSERT( isExternalName name ) nameModule name
1360         this_pkg = thisPackage dflags
1361
1362 -- | As 'lookupType', but with a marginally easier-to-use interface
1363 -- if you have a 'HscEnv'
1364 lookupTypeHscEnv :: HscEnv -> Name -> IO (Maybe TyThing)
1365 lookupTypeHscEnv hsc_env name = do
1366     eps <- readIORef (hsc_EPS hsc_env)
1367     return $! lookupType dflags hpt (eps_PTE eps) name
1368   where 
1369     dflags = hsc_dflags hsc_env
1370     hpt = hsc_HPT hsc_env
1371 \end{code}
1372
1373 \begin{code}
1374 -- | Get the 'TyCon' from a 'TyThing' if it is a type constructor thing. Panics otherwise
1375 tyThingTyCon :: TyThing -> TyCon
1376 tyThingTyCon (ATyCon tc) = tc
1377 tyThingTyCon other       = pprPanic "tyThingTyCon" (pprTyThing other)
1378
1379 -- | Get the 'Class' from a 'TyThing' if it is a class thing. Panics otherwise
1380 tyThingClass :: TyThing -> Class
1381 tyThingClass (AClass cls) = cls
1382 tyThingClass other        = pprPanic "tyThingClass" (pprTyThing other)
1383
1384 -- | Get the 'DataCon' from a 'TyThing' if it is a data constructor thing. Panics otherwise
1385 tyThingDataCon :: TyThing -> DataCon
1386 tyThingDataCon (ADataCon dc) = dc
1387 tyThingDataCon other         = pprPanic "tyThingDataCon" (pprTyThing other)
1388
1389 -- | Get the 'Id' from a 'TyThing' if it is a id *or* data constructor thing. Panics otherwise
1390 tyThingId :: TyThing -> Id
1391 tyThingId (AnId id)     = id
1392 tyThingId (ADataCon dc) = dataConWrapId dc
1393 tyThingId other         = pprPanic "tyThingId" (pprTyThing other)
1394 \end{code}
1395
1396 %************************************************************************
1397 %*                                                                      *
1398 \subsection{MonadThings and friends}
1399 %*                                                                      *
1400 %************************************************************************
1401
1402 \begin{code}
1403 -- | Class that abstracts out the common ability of the monads in GHC
1404 -- to lookup a 'TyThing' in the monadic environment by 'Name'. Provides
1405 -- a number of related convenience functions for accessing particular
1406 -- kinds of 'TyThing'
1407 class Monad m => MonadThings m where
1408         lookupThing :: Name -> m TyThing
1409
1410         lookupId :: Name -> m Id
1411         lookupId = liftM tyThingId . lookupThing
1412
1413         lookupDataCon :: Name -> m DataCon
1414         lookupDataCon = liftM tyThingDataCon . lookupThing
1415
1416         lookupTyCon :: Name -> m TyCon
1417         lookupTyCon = liftM tyThingTyCon . lookupThing
1418
1419         lookupClass :: Name -> m Class
1420         lookupClass = liftM tyThingClass . lookupThing
1421 \end{code}
1422
1423 \begin{code}
1424 -- | Constructs cache for the 'mi_hash_fn' field of a 'ModIface'
1425 mkIfaceHashCache :: [(Fingerprint,IfaceDecl)]
1426                  -> (OccName -> Maybe (OccName, Fingerprint))
1427 mkIfaceHashCache pairs 
1428   = \occ -> lookupOccEnv env occ
1429   where
1430     env = foldr add_decl emptyOccEnv pairs
1431     add_decl (v,d) env0 = foldr add_imp env1 (ifaceDeclSubBndrs d)
1432       where
1433           decl_name = ifName d
1434           env1 = extendOccEnv env0 decl_name (decl_name, v)
1435           add_imp bndr env = extendOccEnv env bndr (decl_name, v)
1436
1437 emptyIfaceHashCache :: OccName -> Maybe (OccName, Fingerprint)
1438 emptyIfaceHashCache _occ = Nothing
1439 \end{code}
1440
1441 %************************************************************************
1442 %*                                                                      *
1443 \subsection{Auxiliary types}
1444 %*                                                                      *
1445 %************************************************************************
1446
1447 These types are defined here because they are mentioned in ModDetails,
1448 but they are mostly elaborated elsewhere
1449
1450 \begin{code}
1451 ------------------ Warnings -------------------------
1452 -- | Warning information for a module
1453 data Warnings
1454   = NoWarnings                          -- ^ Nothing deprecated
1455   | WarnAll WarningTxt                  -- ^ Whole module deprecated
1456   | WarnSome [(OccName,WarningTxt)]     -- ^ Some specific things deprecated
1457
1458      -- Only an OccName is needed because
1459      --    (1) a deprecation always applies to a binding
1460      --        defined in the module in which the deprecation appears.
1461      --    (2) deprecations are only reported outside the defining module.
1462      --        this is important because, otherwise, if we saw something like
1463      --
1464      --        {-# DEPRECATED f "" #-}
1465      --        f = ...
1466      --        h = f
1467      --        g = let f = undefined in f
1468      --
1469      --        we'd need more information than an OccName to know to say something
1470      --        about the use of f in h but not the use of the locally bound f in g
1471      --
1472      --        however, because we only report about deprecations from the outside,
1473      --        and a module can only export one value called f,
1474      --        an OccName suffices.
1475      --
1476      --        this is in contrast with fixity declarations, where we need to map
1477      --        a Name to its fixity declaration.
1478   deriving( Eq )
1479
1480 -- | Constructs the cache for the 'mi_warn_fn' field of a 'ModIface'
1481 mkIfaceWarnCache :: Warnings -> Name -> Maybe WarningTxt
1482 mkIfaceWarnCache NoWarnings  = \_ -> Nothing
1483 mkIfaceWarnCache (WarnAll t) = \_ -> Just t
1484 mkIfaceWarnCache (WarnSome pairs) = lookupOccEnv (mkOccEnv pairs) . nameOccName
1485
1486 emptyIfaceWarnCache :: Name -> Maybe WarningTxt
1487 emptyIfaceWarnCache _ = Nothing
1488
1489 plusWarns :: Warnings -> Warnings -> Warnings
1490 plusWarns d NoWarnings = d
1491 plusWarns NoWarnings d = d
1492 plusWarns _ (WarnAll t) = WarnAll t
1493 plusWarns (WarnAll t) _ = WarnAll t
1494 plusWarns (WarnSome v1) (WarnSome v2) = WarnSome (v1 ++ v2)
1495 \end{code}
1496 \begin{code}
1497 -- | A collection of 'AvailInfo' - several things that are \"available\"
1498 type Avails       = [AvailInfo]
1499 -- | 'Name'd things that are available
1500 type AvailInfo    = GenAvailInfo Name
1501 -- | 'RdrName'd things that are available
1502 type RdrAvailInfo = GenAvailInfo OccName
1503
1504 -- | Records what things are "available", i.e. in scope
1505 data GenAvailInfo name  = Avail name     -- ^ An ordinary identifier in scope
1506                         | AvailTC name
1507                                   [name] -- ^ A type or class in scope. Parameters:
1508                                          --
1509                                          --  1) The name of the type or class
1510                                          --
1511                                          --  2) The available pieces of type or class.
1512                                          --     NB: If the type or class is itself
1513                                          --     to be in scope, it must be in this list.
1514                                          --     Thus, typically: @AvailTC Eq [Eq, ==, \/=]@
1515                         deriving( Eq )
1516                         -- Equality used when deciding if the interface has changed
1517
1518 -- | The original names declared of a certain module that are exported
1519 type IfaceExport = (Module, [GenAvailInfo OccName])
1520
1521 availsToNameSet :: [AvailInfo] -> NameSet
1522 availsToNameSet avails = foldr add emptyNameSet avails
1523       where add avail set = addListToNameSet set (availNames avail)
1524
1525 availsToNameEnv :: [AvailInfo] -> NameEnv AvailInfo
1526 availsToNameEnv avails = foldr add emptyNameEnv avails
1527      where add avail env = extendNameEnvList env
1528                                 (zip (availNames avail) (repeat avail))
1529
1530 -- | Just the main name made available, i.e. not the available pieces
1531 -- of type or class brought into scope by the 'GenAvailInfo'
1532 availName :: GenAvailInfo name -> name
1533 availName (Avail n)     = n
1534 availName (AvailTC n _) = n
1535
1536 -- | All names made available by the availability information
1537 availNames :: GenAvailInfo name -> [name]
1538 availNames (Avail n)      = [n]
1539 availNames (AvailTC _ ns) = ns
1540
1541 instance Outputable n => Outputable (GenAvailInfo n) where
1542    ppr = pprAvail
1543
1544 pprAvail :: Outputable n => GenAvailInfo n -> SDoc
1545 pprAvail (Avail n)      = ppr n
1546 pprAvail (AvailTC n ns) = ppr n <> braces (hsep (punctuate comma (map ppr ns)))
1547 \end{code}
1548
1549 \begin{code}
1550 -- | Creates cached lookup for the 'mi_fix_fn' field of 'ModIface'
1551 mkIfaceFixCache :: [(OccName, Fixity)] -> OccName -> Fixity
1552 mkIfaceFixCache pairs 
1553   = \n -> lookupOccEnv env n `orElse` defaultFixity
1554   where
1555    env = mkOccEnv pairs
1556
1557 emptyIfaceFixCache :: OccName -> Fixity
1558 emptyIfaceFixCache _ = defaultFixity
1559
1560 -- | Fixity environment mapping names to their fixities
1561 type FixityEnv = NameEnv FixItem
1562
1563 -- | Fixity information for an 'Name'. We keep the OccName in the range 
1564 -- so that we can generate an interface from it
1565 data FixItem = FixItem OccName Fixity
1566
1567 instance Outputable FixItem where
1568   ppr (FixItem occ fix) = ppr fix <+> ppr occ
1569
1570 emptyFixityEnv :: FixityEnv
1571 emptyFixityEnv = emptyNameEnv
1572
1573 lookupFixity :: FixityEnv -> Name -> Fixity
1574 lookupFixity env n = case lookupNameEnv env n of
1575                         Just (FixItem _ fix) -> fix
1576                         Nothing         -> defaultFixity
1577 \end{code}
1578
1579
1580 %************************************************************************
1581 %*                                                                      *
1582 \subsection{WhatsImported}
1583 %*                                                                      *
1584 %************************************************************************
1585
1586 \begin{code}
1587 -- | Records whether a module has orphans. An \"orphan\" is one of:
1588 --
1589 -- * An instance declaration in a module other than the definition
1590 --   module for one of the type constructors or classes in the instance head
1591 --
1592 -- * A transformation rule in a module other than the one defining
1593 --   the function in the head of the rule
1594 type WhetherHasOrphans   = Bool
1595
1596 -- | Does this module define family instances?
1597 type WhetherHasFamInst = Bool
1598
1599 -- | Did this module originate from a *-boot file?
1600 type IsBootInterface = Bool
1601
1602 -- | Dependency information about modules and packages below this one
1603 -- in the import hierarchy.
1604 --
1605 -- Invariant: the dependencies of a module @M@ never includes @M@.
1606 --
1607 -- Invariant: none of the lists contain duplicates.
1608 data Dependencies
1609   = Deps { dep_mods   :: [(ModuleName, IsBootInterface)]
1610                         -- ^ Home-package module dependencies
1611          , dep_pkgs   :: [PackageId]
1612                         -- ^ External package dependencies
1613          , dep_orphs  :: [Module]           
1614                         -- ^ Orphan modules (whether home or external pkg),
1615                         -- *not* including family instance orphans as they
1616                         -- are anyway included in 'dep_finsts'
1617          , dep_finsts :: [Module]           
1618                         -- ^ Modules that contain family instances (whether the
1619                         -- instances are from the home or an external package)
1620          }
1621   deriving( Eq )
1622         -- Equality used only for old/new comparison in MkIface.addVersionInfo
1623
1624         -- See 'TcRnTypes.ImportAvails' for details on dependencies.
1625
1626 noDependencies :: Dependencies
1627 noDependencies = Deps [] [] [] []
1628
1629 -- | Records modules that we depend on by making a direct import from
1630 data Usage
1631   = UsagePackageModule {
1632         usg_mod      :: Module,
1633            -- ^ External package module depended on
1634         usg_mod_hash :: Fingerprint
1635     }                                           -- ^ Module from another package
1636   | UsageHomeModule {
1637         usg_mod_name :: ModuleName,
1638             -- ^ Name of the module
1639         usg_mod_hash :: Fingerprint,
1640             -- ^ Cached module fingerprint
1641         usg_entities :: [(OccName,Fingerprint)],
1642             -- ^ Entities we depend on, sorted by occurrence name and fingerprinted.
1643             -- NB: usages are for parent names only, e.g. type constructors 
1644             -- but not the associated data constructors.
1645         usg_exports  :: Maybe Fingerprint
1646             -- ^ Fingerprint for the export list we used to depend on this module,
1647             -- if we depend on the export list
1648     }                                           -- ^ Module from the current package
1649     deriving( Eq )
1650         -- The export list field is (Just v) if we depend on the export list:
1651         --      i.e. we imported the module directly, whether or not we
1652         --           enumerated the things we imported, or just imported 
1653         --           everything
1654         -- We need to recompile if M's exports change, because 
1655         -- if the import was    import M,       we might now have a name clash
1656         --                                      in the importing module.
1657         -- if the import was    import M(x)     M might no longer export x
1658         -- The only way we don't depend on the export list is if we have
1659         --                      import M()
1660         -- And of course, for modules that aren't imported directly we don't
1661         -- depend on their export lists
1662 \end{code}
1663
1664
1665 %************************************************************************
1666 %*                                                                      *
1667                 The External Package State
1668 %*                                                                      *
1669 %************************************************************************
1670
1671 \begin{code}
1672 type PackageTypeEnv    = TypeEnv
1673 type PackageRuleBase   = RuleBase
1674 type PackageInstEnv    = InstEnv
1675 type PackageFamInstEnv = FamInstEnv
1676 type PackageVectInfo   = VectInfo
1677 type PackageAnnEnv     = AnnEnv
1678
1679 -- | Information about other packages that we have slurped in by reading
1680 -- their interface files
1681 data ExternalPackageState
1682   = EPS {
1683         eps_is_boot :: !(ModuleNameEnv (ModuleName, IsBootInterface)),
1684                 -- ^ In OneShot mode (only), home-package modules
1685                 -- accumulate in the external package state, and are
1686                 -- sucked in lazily.  For these home-pkg modules
1687                 -- (only) we need to record which are boot modules.
1688                 -- We set this field after loading all the
1689                 -- explicitly-imported interfaces, but before doing
1690                 -- anything else
1691                 --
1692                 -- The 'ModuleName' part is not necessary, but it's useful for
1693                 -- debug prints, and it's convenient because this field comes
1694                 -- direct from 'TcRnTypes.imp_dep_mods'
1695
1696         eps_PIT :: !PackageIfaceTable,
1697                 -- ^ The 'ModIface's for modules in external packages
1698                 -- whose interfaces we have opened.
1699                 -- The declarations in these interface files are held in the
1700                 -- 'eps_decls', 'eps_inst_env', 'eps_fam_inst_env' and 'eps_rules'
1701                 -- fields of this record, not in the 'mi_decls' fields of the 
1702                 -- interface we have sucked in.
1703                 --
1704                 -- What /is/ in the PIT is:
1705                 --
1706                 -- * The Module
1707                 --
1708                 -- * Fingerprint info
1709                 --
1710                 -- * Its exports
1711                 --
1712                 -- * Fixities
1713                 --
1714                 -- * Deprecations and warnings
1715
1716         eps_PTE :: !PackageTypeEnv,        
1717                 -- ^ Result of typechecking all the external package
1718                 -- interface files we have sucked in. The domain of
1719                 -- the mapping is external-package modules
1720                 
1721         eps_inst_env     :: !PackageInstEnv,   -- ^ The total 'InstEnv' accumulated
1722                                                -- from all the external-package modules
1723         eps_fam_inst_env :: !PackageFamInstEnv,-- ^ The total 'FamInstEnv' accumulated
1724                                                -- from all the external-package modules
1725         eps_rule_base    :: !PackageRuleBase,  -- ^ The total 'RuleEnv' accumulated
1726                                                -- from all the external-package modules
1727         eps_vect_info    :: !PackageVectInfo,  -- ^ The total 'VectInfo' accumulated
1728                                                -- from all the external-package modules
1729         eps_ann_env      :: !PackageAnnEnv,    -- ^ The total 'AnnEnv' accumulated
1730                                                -- from all the external-package modules
1731
1732         eps_mod_fam_inst_env :: !(ModuleEnv FamInstEnv), -- ^ The family instances accumulated from external
1733                                                          -- packages, keyed off the module that declared them
1734
1735         eps_stats :: !EpsStats                 -- ^ Stastics about what was loaded from external packages
1736   }
1737
1738 -- | Accumulated statistics about what we are putting into the 'ExternalPackageState'.
1739 -- \"In\" means stuff that is just /read/ from interface files,
1740 -- \"Out\" means actually sucked in and type-checked
1741 data EpsStats = EpsStats { n_ifaces_in
1742                          , n_decls_in, n_decls_out 
1743                          , n_rules_in, n_rules_out
1744                          , n_insts_in, n_insts_out :: !Int }
1745
1746 addEpsInStats :: EpsStats -> Int -> Int -> Int -> EpsStats
1747 -- ^ Add stats for one newly-read interface
1748 addEpsInStats stats n_decls n_insts n_rules
1749   = stats { n_ifaces_in = n_ifaces_in stats + 1
1750           , n_decls_in  = n_decls_in stats + n_decls
1751           , n_insts_in  = n_insts_in stats + n_insts
1752           , n_rules_in  = n_rules_in stats + n_rules }
1753 \end{code}
1754
1755 Names in a NameCache are always stored as a Global, and have the SrcLoc 
1756 of their binding locations.
1757
1758 Actually that's not quite right.  When we first encounter the original
1759 name, we might not be at its binding site (e.g. we are reading an
1760 interface file); so we give it 'noSrcLoc' then.  Later, when we find
1761 its binding site, we fix it up.
1762
1763 \begin{code}
1764 -- | The NameCache makes sure that there is just one Unique assigned for
1765 -- each original name; i.e. (module-name, occ-name) pair and provides
1766 -- something of a lookup mechanism for those names.
1767 data NameCache
1768  = NameCache {  nsUniqs :: UniqSupply,
1769                 -- ^ Supply of uniques
1770                 nsNames :: OrigNameCache,
1771                 -- ^ Ensures that one original name gets one unique
1772                 nsIPs   :: OrigIParamCache
1773                 -- ^ Ensures that one implicit parameter name gets one unique
1774    }
1775
1776 -- | Per-module cache of original 'OccName's given 'Name's
1777 type OrigNameCache   = ModuleEnv (OccEnv Name)
1778
1779 -- | Module-local cache of implicit parameter 'OccName's given 'Name's
1780 type OrigIParamCache = FiniteMap (IPName OccName) (IPName Name)
1781 \end{code}
1782
1783
1784
1785 %************************************************************************
1786 %*                                                                      *
1787                 The module graph and ModSummary type
1788         A ModSummary is a node in the compilation manager's
1789         dependency graph, and it's also passed to hscMain
1790 %*                                                                      *
1791 %************************************************************************
1792
1793 \begin{code}
1794 -- | A ModuleGraph contains all the nodes from the home package (only).
1795 -- There will be a node for each source module, plus a node for each hi-boot
1796 -- module.
1797 --
1798 -- The graph is not necessarily stored in topologically-sorted order.
1799 type ModuleGraph = [ModSummary]
1800
1801 emptyMG :: ModuleGraph
1802 emptyMG = []
1803
1804 -- | A single node in a 'ModuleGraph. The nodes of the module graph are one of:
1805 --
1806 -- * A regular Haskell source module
1807 --
1808 -- * A hi-boot source module
1809 --
1810 -- * An external-core source module
1811 data ModSummary
1812    = ModSummary {
1813         ms_mod       :: Module,                 -- ^ Identity of the module
1814         ms_hsc_src   :: HscSource,              -- ^ The module source either plain Haskell, hs-boot or external core
1815         ms_location  :: ModLocation,            -- ^ Location of the various files belonging to the module
1816         ms_hs_date   :: ClockTime,              -- ^ Timestamp of source file
1817         ms_obj_date  :: Maybe ClockTime,        -- ^ Timestamp of object, if we have one
1818         ms_srcimps   :: [Located ModuleName],   -- ^ Source imports of the module
1819         ms_imps      :: [Located ModuleName],   -- ^ Non-source imports of the module
1820         ms_hspp_file :: FilePath,               -- ^ Filename of preprocessed source file
1821         ms_hspp_opts :: DynFlags,               -- ^ Cached flags from @OPTIONS@, @INCLUDE@
1822                                                 -- and @LANGUAGE@ pragmas in the modules source code
1823         ms_hspp_buf  :: Maybe StringBuffer      -- ^ The actual preprocessed source, if we have it
1824      }
1825
1826 ms_mod_name :: ModSummary -> ModuleName
1827 ms_mod_name = moduleName . ms_mod
1828
1829 -- The ModLocation contains both the original source filename and the
1830 -- filename of the cleaned-up source file after all preprocessing has been
1831 -- done.  The point is that the summariser will have to cpp/unlit/whatever
1832 -- all files anyway, and there's no point in doing this twice -- just 
1833 -- park the result in a temp file, put the name of it in the location,
1834 -- and let @compile@ read from that file on the way back up.
1835
1836 -- The ModLocation is stable over successive up-sweeps in GHCi, wheres
1837 -- the ms_hs_date and imports can, of course, change
1838
1839 msHsFilePath, msHiFilePath, msObjFilePath :: ModSummary -> FilePath
1840 msHsFilePath  ms = expectJust "msHsFilePath" (ml_hs_file  (ms_location ms))
1841 msHiFilePath  ms = ml_hi_file  (ms_location ms)
1842 msObjFilePath ms = ml_obj_file (ms_location ms)
1843
1844 -- | Did this 'ModSummary' originate from a hs-boot file?
1845 isBootSummary :: ModSummary -> Bool
1846 isBootSummary ms = isHsBoot (ms_hsc_src ms)
1847
1848 instance Outputable ModSummary where
1849    ppr ms
1850       = sep [text "ModSummary {",
1851              nest 3 (sep [text "ms_hs_date = " <> text (show (ms_hs_date ms)),
1852                           text "ms_mod =" <+> ppr (ms_mod ms) 
1853                                 <> text (hscSourceString (ms_hsc_src ms)) <> comma,
1854                           text "ms_imps =" <+> ppr (ms_imps ms),
1855                           text "ms_srcimps =" <+> ppr (ms_srcimps ms)]),
1856              char '}'
1857             ]
1858
1859 showModMsg :: HscTarget -> Bool -> ModSummary -> String
1860 showModMsg target recomp mod_summary
1861   = showSDoc $
1862         hsep [text (mod_str ++ replicate (max 0 (16 - length mod_str)) ' '),
1863               char '(', text (normalise $ msHsFilePath mod_summary) <> comma,
1864               case target of
1865                   HscInterpreted | recomp 
1866                              -> text "interpreted"
1867                   HscNothing -> text "nothing"
1868                   _          -> text (normalise $ msObjFilePath mod_summary),
1869               char ')']
1870  where 
1871     mod     = moduleName (ms_mod mod_summary)
1872     mod_str = showSDoc (ppr mod) ++ hscSourceString (ms_hsc_src mod_summary)
1873 \end{code}
1874
1875
1876 %************************************************************************
1877 %*                                                                      *
1878 \subsection{Hpc Support}
1879 %*                                                                      *
1880 %************************************************************************
1881
1882 \begin{code}
1883 -- | Information about a modules use of Haskell Program Coverage
1884 data HpcInfo
1885   = HpcInfo 
1886      { hpcInfoTickCount :: Int
1887      , hpcInfoHash      :: Int
1888      }
1889   | NoHpcInfo 
1890      { hpcUsed          :: AnyHpcUsage  -- ^ Is hpc used anywhere on the module \*tree\*?
1891      }
1892
1893 -- | This is used to signal if one of my imports used HPC instrumentation
1894 -- even if there is no module-local HPC usage
1895 type AnyHpcUsage = Bool
1896
1897 emptyHpcInfo :: AnyHpcUsage -> HpcInfo
1898 emptyHpcInfo = NoHpcInfo 
1899
1900 -- | Find out if HPC is used by this module or any of the modules
1901 -- it depends upon
1902 isHpcUsed :: HpcInfo -> AnyHpcUsage
1903 isHpcUsed (HpcInfo {})                   = True
1904 isHpcUsed (NoHpcInfo { hpcUsed = used }) = used
1905 \end{code}
1906
1907 %************************************************************************
1908 %*                                                                      *
1909 \subsection{Vectorisation Support}
1910 %*                                                                      *
1911 %************************************************************************
1912
1913 The following information is generated and consumed by the vectorisation
1914 subsystem.  It communicates the vectorisation status of declarations from one
1915 module to another.
1916
1917 Why do we need both f and f_v in the ModGuts/ModDetails/EPS version VectInfo
1918 below?  We need to know `f' when converting to IfaceVectInfo.  However, during
1919 vectorisation, we need to know `f_v', whose `Var' we cannot lookup based
1920 on just the OccName easily in a Core pass.
1921
1922 \begin{code}
1923 -- | Vectorisation information for 'ModGuts', 'ModDetails' and 'ExternalPackageState'.
1924 -- All of this information is always tidy, even in ModGuts.
1925 data VectInfo      
1926   = VectInfo {
1927       vectInfoVar     :: VarEnv  (Var    , Var  ),   -- ^ @(f, f_v)@ keyed on @f@
1928       vectInfoTyCon   :: NameEnv (TyCon  , TyCon),   -- ^ @(T, T_v)@ keyed on @T@
1929       vectInfoDataCon :: NameEnv (DataCon, DataCon), -- ^ @(C, C_v)@ keyed on @C@
1930       vectInfoPADFun  :: NameEnv (TyCon  , Var),     -- ^ @(T_v, paT)@ keyed on @T_v@
1931       vectInfoIso     :: NameEnv (TyCon  , Var)      -- ^ @(T, isoT)@ keyed on @T@
1932     }
1933
1934 -- | Vectorisation information for 'ModIface': a slightly less low-level view
1935 data IfaceVectInfo 
1936   = IfaceVectInfo {
1937       ifaceVectInfoVar        :: [Name],
1938         -- ^ All variables in here have a vectorised variant
1939       ifaceVectInfoTyCon      :: [Name],
1940         -- ^ All 'TyCon's in here have a vectorised variant;
1941         -- the name of the vectorised variant and those of its
1942         -- data constructors are determined by 'OccName.mkVectTyConOcc'
1943         -- and 'OccName.mkVectDataConOcc'; the names of
1944         -- the isomorphisms are determined by 'OccName.mkVectIsoOcc'
1945       ifaceVectInfoTyConReuse :: [Name]              
1946         -- ^ The vectorised form of all the 'TyCon's in here coincides with
1947         -- the unconverted form; the name of the isomorphisms is determined
1948         -- by 'OccName.mkVectIsoOcc'
1949     }
1950
1951 noVectInfo :: VectInfo
1952 noVectInfo = VectInfo emptyVarEnv emptyNameEnv emptyNameEnv emptyNameEnv emptyNameEnv
1953
1954 plusVectInfo :: VectInfo -> VectInfo -> VectInfo
1955 plusVectInfo vi1 vi2 = 
1956   VectInfo (vectInfoVar     vi1 `plusVarEnv`  vectInfoVar     vi2)
1957            (vectInfoTyCon   vi1 `plusNameEnv` vectInfoTyCon   vi2)
1958            (vectInfoDataCon vi1 `plusNameEnv` vectInfoDataCon vi2)
1959            (vectInfoPADFun  vi1 `plusNameEnv` vectInfoPADFun  vi2)
1960            (vectInfoIso     vi1 `plusNameEnv` vectInfoIso     vi2)
1961
1962 concatVectInfo :: [VectInfo] -> VectInfo
1963 concatVectInfo = foldr plusVectInfo noVectInfo
1964
1965 noIfaceVectInfo :: IfaceVectInfo
1966 noIfaceVectInfo = IfaceVectInfo [] [] []
1967 \end{code}
1968
1969 %************************************************************************
1970 %*                                                                      *
1971 \subsection{Linkable stuff}
1972 %*                                                                      *
1973 %************************************************************************
1974
1975 This stuff is in here, rather than (say) in Linker.lhs, because the Linker.lhs
1976 stuff is the *dynamic* linker, and isn't present in a stage-1 compiler
1977
1978 \begin{code}
1979 -- | Information we can use to dynamically link modules into the compiler
1980 data Linkable = LM {
1981   linkableTime     :: ClockTime,        -- ^ Time at which this linkable was built
1982                                         -- (i.e. when the bytecodes were produced,
1983                                         --       or the mod date on the files)
1984   linkableModule   :: Module,           -- ^ The linkable module itself
1985   linkableUnlinked :: [Unlinked]        -- ^ Those files and chunks of code we have
1986                                         -- yet to link
1987  }
1988
1989 isObjectLinkable :: Linkable -> Bool
1990 isObjectLinkable l = not (null unlinked) && all isObject unlinked
1991   where unlinked = linkableUnlinked l
1992         -- A linkable with no Unlinked's is treated as a BCO.  We can
1993         -- generate a linkable with no Unlinked's as a result of
1994         -- compiling a module in HscNothing mode, and this choice
1995         -- happens to work well with checkStability in module GHC.
1996
1997 instance Outputable Linkable where
1998    ppr (LM when_made mod unlinkeds)
1999       = (text "LinkableM" <+> parens (text (show when_made)) <+> ppr mod)
2000         $$ nest 3 (ppr unlinkeds)
2001
2002 -------------------------------------------
2003
2004 -- | Objects which have yet to be linked by the compiler
2005 data Unlinked
2006    = DotO FilePath      -- ^ An object file (.o)
2007    | DotA FilePath      -- ^ Static archive file (.a)
2008    | DotDLL FilePath    -- ^ Dynamically linked library file (.so, .dll, .dylib)
2009    | BCOs CompiledByteCode ModBreaks    -- ^ A byte-code object, lives only in memory
2010
2011 #ifndef GHCI
2012 data CompiledByteCode = CompiledByteCodeUndefined
2013 _unused :: CompiledByteCode
2014 _unused = CompiledByteCodeUndefined
2015 #endif
2016
2017 instance Outputable Unlinked where
2018    ppr (DotO path)   = text "DotO" <+> text path
2019    ppr (DotA path)   = text "DotA" <+> text path
2020    ppr (DotDLL path) = text "DotDLL" <+> text path
2021 #ifdef GHCI
2022    ppr (BCOs bcos _) = text "BCOs" <+> ppr bcos
2023 #else
2024    ppr (BCOs _ _)    = text "No byte code"
2025 #endif
2026
2027 -- | Is this an actual file on disk we can link in somehow?
2028 isObject :: Unlinked -> Bool
2029 isObject (DotO _)   = True
2030 isObject (DotA _)   = True
2031 isObject (DotDLL _) = True
2032 isObject _          = False
2033
2034 -- | Is this a bytecode linkable with no file on disk?
2035 isInterpretable :: Unlinked -> Bool
2036 isInterpretable = not . isObject
2037
2038 -- | Retrieve the filename of the linkable if possible. Panic if it is a byte-code object
2039 nameOfObject :: Unlinked -> FilePath
2040 nameOfObject (DotO fn)   = fn
2041 nameOfObject (DotA fn)   = fn
2042 nameOfObject (DotDLL fn) = fn
2043 nameOfObject other       = pprPanic "nameOfObject" (ppr other)
2044
2045 -- | Retrieve the compiled byte-code if possible. Panic if it is a file-based linkable
2046 byteCodeOfObject :: Unlinked -> CompiledByteCode
2047 byteCodeOfObject (BCOs bc _) = bc
2048 byteCodeOfObject other       = pprPanic "byteCodeOfObject" (ppr other)
2049 \end{code}
2050
2051 %************************************************************************
2052 %*                                                                      *
2053 \subsection{Breakpoint Support}
2054 %*                                                                      *
2055 %************************************************************************
2056
2057 \begin{code}
2058 -- | Breakpoint index
2059 type BreakIndex = Int
2060
2061 -- | All the information about the breakpoints for a given module
2062 data ModBreaks
2063    = ModBreaks
2064    { modBreaks_flags :: BreakArray
2065         -- ^ The array of flags, one per breakpoint, 
2066         -- indicating which breakpoints are enabled.
2067    , modBreaks_locs :: !(Array BreakIndex SrcSpan)
2068         -- ^ An array giving the source span of each breakpoint.
2069    , modBreaks_vars :: !(Array BreakIndex [OccName])
2070         -- ^ An array giving the names of the free variables at each breakpoint.
2071    }
2072
2073 emptyModBreaks :: ModBreaks
2074 emptyModBreaks = ModBreaks
2075    { modBreaks_flags = error "ModBreaks.modBreaks_array not initialised"
2076          -- Todo: can we avoid this? 
2077    , modBreaks_locs = array (0,-1) []
2078    , modBreaks_vars = array (0,-1) []
2079    }
2080 \end{code}