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