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