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