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