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