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