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