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