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