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