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