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