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