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