[project @ 2004-08-26 15:44:50 by simonpj]
[ghc-hetmet.git] / ghc / compiler / main / HscTypes.lhs
1
2 % (c) The University of Glasgow, 2000
3 %
4 \section[HscTypes]{Types for the per-module compiler}
5
6 \begin{code}
7 module HscTypes ( 
8         HscEnv(..), hscEPS,
9         GhciMode(..), isOneShot,
10
11         ModDetails(..), 
12         ModGuts(..), ModImports(..), ForeignStubs(..),
13
14         HomePackageTable, HomeModInfo(..), emptyHomePackageTable,
15
16         ExternalPackageState(..), EpsStats(..), addEpsInStats,
17         PackageTypeEnv, PackageIfaceTable, emptyPackageIfaceTable,
18         lookupIface, lookupIfaceByModName, moduleNameToModule,
19         emptyModIface,
20
21         InteractiveContext(..), emptyInteractiveContext, 
22         icPrintUnqual, unQualInScope,
23
24         ModIface(..), mkIfaceDepCache, mkIfaceVerCache, mkIfaceFixCache,
25                       emptyIfaceDepCache, 
26
27         Deprecs(..), IfaceDeprecs,
28
29         FixityEnv, FixItem(..), lookupFixity, emptyFixityEnv,
30
31         implicitTyThings, 
32
33         TyThing(..), tyThingClass, tyThingTyCon, tyThingDataCon, tyThingId,
34         TypeEnv, lookupType, mkTypeEnv, emptyTypeEnv,
35         extendTypeEnv, extendTypeEnvList, extendTypeEnvWithIds, lookupTypeEnv,
36         typeEnvElts, typeEnvClasses, typeEnvTyCons, typeEnvIds,
37
38         WhetherHasOrphans, IsBootInterface, Usage(..), 
39         Dependencies(..), noDependencies,
40         InstPool, Gated, addInstsToPool, 
41         RulePool, addRulesToPool, 
42         NameCache(..), OrigNameCache, OrigIParamCache,
43         Avails, availsToNameSet, availName, availNames,
44         GenAvailInfo(..), AvailInfo, RdrAvailInfo, 
45         IfaceExport,
46
47         Deprecations, DeprecTxt, lookupDeprec, plusDeprecs,
48
49         InstEnv, DFunId,
50         PackageInstEnv, PackageRuleBase,
51
52         -- Linker stuff
53         Linkable(..), isObjectLinkable,
54         Unlinked(..), CompiledByteCode,
55         isObject, nameOfObject, isInterpretable, byteCodeOfObject
56     ) where
57
58 #include "HsVersions.h"
59
60 #ifdef GHCI
61 import ByteCodeAsm      ( CompiledByteCode )
62 #endif
63
64 import RdrName          ( GlobalRdrEnv, emptyGlobalRdrEnv,
65                           LocalRdrEnv, emptyLocalRdrEnv,
66                           GlobalRdrElt(..), mkRdrUnqual, lookupGRE_RdrName )
67 import Name             ( Name, NamedThing, getName, nameOccName, nameModule, nameModuleName )
68 import NameEnv
69 import NameSet  
70 import OccName          ( OccName, OccEnv, lookupOccEnv, mkOccEnv, emptyOccEnv, 
71                           extendOccEnv, foldOccEnv )
72 import Module
73 import InstEnv          ( InstEnv, DFunId )
74 import Rules            ( RuleBase )
75 import CoreSyn          ( CoreBind )
76 import Id               ( Id )
77 import Type             ( TyThing(..) )
78
79 import Class            ( Class, classSelIds, classTyCon )
80 import TyCon            ( TyCon, isClassTyCon, tyConSelIds, tyConDataCons )
81 import DataCon          ( dataConImplicitIds )
82 import Packages         ( PackageName )
83 import CmdLineOpts      ( DynFlags )
84
85 import BasicTypes       ( Version, initialVersion, IPName, 
86                           Fixity, defaultFixity, DeprecTxt )
87
88 import IfaceSyn         ( IfaceInst, IfaceRule, IfaceDecl(ifName) )
89
90 import FiniteMap        ( FiniteMap )
91 import CoreSyn          ( IdCoreRule )
92 import Maybes           ( orElse )
93 import Outputable
94 import SrcLoc           ( SrcSpan )
95 import UniqSupply       ( UniqSupply )
96 import Maybe            ( fromJust )
97 import FastString       ( FastString )
98
99 import DATA_IOREF       ( IORef, readIORef )
100 import Time             ( ClockTime )
101 \end{code}
102
103
104 %************************************************************************
105 %*                                                                      *
106 \subsection{Compilation environment}
107 %*                                                                      *
108 %************************************************************************
109
110 The HscEnv gives the environment in which to compile a chunk of code.
111
112 \begin{code}
113 data HscEnv 
114   = HscEnv { hsc_mode   :: GhciMode,
115              hsc_dflags :: DynFlags,
116
117              hsc_HPT    :: HomePackageTable,
118                 -- The home package table describes already-compiled
119                 -- home-packge modules, *excluding* the module we 
120                 -- are compiling right now.
121                 -- (In one-shot mode the current module is the only
122                 --  home-package module, so hsc_HPT is empty.  All other
123                 --  modules count as "external-package" modules.)
124                 -- hsc_HPT is not mutable because we only demand-load 
125                 -- external packages; the home package is eagerly 
126                 -- loaded by the compilation manager.
127         
128                 -- The next two are side-effected by compiling
129                 -- to reflect sucking in interface files
130              hsc_EPS    :: IORef ExternalPackageState,
131              hsc_NC     :: IORef NameCache }
132
133 hscEPS :: HscEnv -> IO ExternalPackageState
134 hscEPS hsc_env = readIORef (hsc_EPS hsc_env)
135 \end{code}
136
137 The GhciMode is self-explanatory:
138
139 \begin{code}
140 data GhciMode = Batch           -- ghc --make Main
141               | Interactive     -- ghc --interactive
142               | OneShot         -- ghc Foo.hs
143               | IDE             -- Visual Studio etc
144               deriving Eq
145
146 isOneShot :: GhciMode -> Bool
147 isOneShot OneShot = True
148 isOneShot _other  = False
149 \end{code}
150
151 \begin{code}
152 type HomePackageTable  = ModuleEnv HomeModInfo  -- Domain = modules in the home package
153 type PackageIfaceTable = ModuleEnv ModIface     -- Domain = modules in the imported packages
154
155 emptyHomePackageTable  = emptyModuleEnv
156 emptyPackageIfaceTable = emptyModuleEnv
157
158 data HomeModInfo 
159   = HomeModInfo { hm_iface    :: ModIface,
160                   hm_globals  :: Maybe GlobalRdrEnv,    -- Its top level environment
161                                                         -- Nothing <-> compiled module
162                   hm_details  :: ModDetails,
163                   hm_linkable :: Linkable }
164 \end{code}
165
166 Simple lookups in the symbol table.
167
168 \begin{code}
169 lookupIface :: HomePackageTable -> PackageIfaceTable -> Module -> Maybe ModIface
170 -- We often have two IfaceTables, and want to do a lookup
171 lookupIface hpt pit mod
172   = case lookupModuleEnv hpt mod of
173         Just mod_info -> Just (hm_iface mod_info)
174         Nothing       -> lookupModuleEnv pit mod
175
176 lookupIfaceByModName :: HomePackageTable -> PackageIfaceTable -> ModuleName -> Maybe ModIface
177 -- We often have two IfaceTables, and want to do a lookup
178 lookupIfaceByModName hpt pit mod
179   = case lookupModuleEnvByName hpt mod of
180         Just mod_info -> Just (hm_iface mod_info)
181         Nothing       -> lookupModuleEnvByName pit mod
182 \end{code}
183
184 \begin{code}
185 -- Use instead of Finder.findModule if possible: this way doesn't
186 -- require filesystem operations, and it is guaranteed not to fail
187 -- when the IfaceTables are properly populated (i.e. after the renamer).
188 moduleNameToModule :: HomePackageTable -> PackageIfaceTable -> ModuleName -> Module
189 moduleNameToModule hpt pit mod 
190    = mi_module (fromJust (lookupIfaceByModName hpt pit mod))
191 \end{code}
192
193
194 %************************************************************************
195 %*                                                                      *
196 \subsection{Symbol tables and Module details}
197 %*                                                                      *
198 %************************************************************************
199
200 A @ModIface@ plus a @ModDetails@ summarises everything we know 
201 about a compiled module.  The @ModIface@ is the stuff *before* linking,
202 and can be written out to an interface file.  (The @ModDetails@ is after 
203 linking; it is the "linked" form of the mi_decls field.)
204
205 When we *read* an interface file, we also construct a @ModIface@ from it,
206 except that the mi_decls part is empty; when reading we consolidate
207 the declarations into a single indexed map in the @PersistentRenamerState@.
208
209 \begin{code}
210 data ModIface 
211    = ModIface {
212         mi_package  :: !PackageName,        -- Which package the module comes from
213         mi_module   :: !Module,
214         mi_mod_vers :: !Version,            -- Module version: changes when anything changes
215
216         mi_orphan   :: !WhetherHasOrphans,  -- Whether this module has orphans
217         mi_boot     :: !IsBootInterface,    -- Read from an hi-boot file?
218
219         mi_deps     :: Dependencies,
220                 -- This is consulted for directly-imported modules,
221                 -- but not for anything else (hence lazy)
222
223                 -- Usages; kept sorted so that it's easy to decide
224                 -- whether to write a new iface file (changing usages
225                 -- doesn't affect the version of this module)
226         mi_usages   :: [Usage],
227                 -- NOT STRICT!  we read this field lazily from the interface file
228                 -- It is *only* consulted by the recompilation checker
229
230                 -- Exports
231                 -- Kept sorted by (mod,occ), to make version comparisons easier
232         mi_exports  :: ![IfaceExport],
233         mi_exp_vers :: !Version,        -- Version number of export list
234
235                 -- Fixities
236         mi_fixities :: [(OccName,Fixity)],
237                 -- NOT STRICT!  we read this field lazily from the interface file
238
239                 -- Deprecations
240         mi_deprecs  :: IfaceDeprecs,
241                 -- NOT STRICT!  we read this field lazily from the interface file
242
243                 -- Type, class and variable declarations
244                 -- The version of an Id changes if its fixity or deprecations change
245                 --      (as well as its type of course)
246                 -- Ditto data constructors, class operations, except that 
247                 -- the version of the parent class/tycon changes
248         mi_decls :: [(Version,IfaceDecl)],      -- Sorted
249
250                 -- Instance declarations and rules
251         mi_insts     :: [IfaceInst],    -- Sorted
252         mi_rules     :: [IfaceRule],    -- Sorted
253         mi_rule_vers :: !Version,       -- Version number for rules and instances combined
254
255                 -- Cached environments for easy lookup
256                 -- These are computed (lazily) from other fields
257                 -- and are not put into the interface file
258         mi_dep_fn  :: Name -> Maybe DeprecTxt,  -- Cached lookup for mi_deprecs
259         mi_fix_fn  :: OccName -> Fixity,        -- Cached lookup for mi_fixities
260         mi_ver_fn  :: OccName -> Maybe Version  -- Cached lookup for mi_decls
261                         -- The Nothing in mi_ver_fn means that the thing
262                         -- isn't in decls. It's useful to know that when
263                         -- seeing if we are up to date wrt the old interface
264      }
265
266 -- Should be able to construct ModDetails from mi_decls in ModIface
267 data ModDetails
268    = ModDetails {
269         -- The next three fields are created by the typechecker
270         md_types    :: !TypeEnv,
271         md_insts    :: ![DFunId],       -- Dfun-ids for the instances in this module
272         md_rules    :: ![IdCoreRule]    -- Domain may include Ids from other modules
273      }
274
275 -- A ModGuts is carried through the compiler, accumulating stuff as it goes
276 -- There is only one ModGuts at any time, the one for the module
277 -- being compiled right now.  Once it is compiled, a ModIface and 
278 -- ModDetails are extracted and the ModGuts is dicarded.
279
280 data ModGuts
281   = ModGuts {
282         mg_module   :: !Module,
283         mg_exports  :: !NameSet,        -- What it exports
284         mg_deps     :: !Dependencies,   -- What is below it, directly or otherwise
285         mg_dir_imps :: ![Module],       -- Directly-imported modules; used to
286                                         --      generate initialisation code
287         mg_usages   :: ![Usage],        -- Version info for what it needed
288
289         mg_rdr_env  :: !GlobalRdrEnv,   -- Top-level lexical environment
290         mg_fix_env  :: !FixityEnv,      -- Fixity env, for things declared in this module
291         mg_deprecs  :: !Deprecations,   -- Deprecations declared in the module
292
293         mg_types    :: !TypeEnv,
294         mg_insts    :: ![DFunId],       -- Instances 
295         mg_rules    :: ![IdCoreRule],   -- Rules from this module
296         mg_binds    :: ![CoreBind],     -- Bindings for this module
297         mg_foreign  :: !ForeignStubs
298     }
299
300 -- The ModGuts takes on several slightly different forms:
301 --
302 -- After simplification, the following fields change slightly:
303 --      mg_rules        Orphan rules only (local ones now attached to binds)
304 --      mg_binds        With rules attached
305 --
306 -- After CoreTidy, the following fields change slightly:
307 --      mg_types        Now contains Ids as well, replete with final IdInfo
308 --                         The Ids are only the ones that are visible from
309 --                         importing modules.  Without -O that means only
310 --                         exported Ids, but with -O importing modules may
311 --                         see ids mentioned in unfoldings of exported Ids
312 --
313 --      mg_insts        Same DFunIds as before, but with final IdInfo,
314 --                         and the unique might have changed; remember that
315 --                         CoreTidy links up the uniques of old and new versions
316 --
317 --      mg_rules        All rules for exported things, substituted with final Ids
318 --
319 --      mg_binds        Tidied
320
321
322
323 data ModImports
324   = ModImports {
325         imp_direct     :: ![(Module,Bool)],     -- Explicitly-imported modules
326                                                 -- Boolean is true if we imported the whole
327                                                 --      module (apart, perhaps, from hiding some)
328         imp_pkg_mods   :: !ModuleSet,           -- Non-home-package modules on which we depend,
329                                                 --      directly or indirectly
330         imp_home_names :: !NameSet              -- Home package things on which we depend,
331                                                 --      directly or indirectly
332     }
333
334 data ForeignStubs = NoStubs
335                   | ForeignStubs
336                         SDoc            -- Header file prototypes for
337                                         --      "foreign exported" functions
338                         SDoc            -- C stubs to use when calling
339                                         --      "foreign exported" functions
340                         [FastString]    -- Headers that need to be included
341                                         --      into C code generated for this module
342                         [Id]            -- Foreign-exported binders
343                                         --      we have to generate code to register these
344
345 \end{code}
346
347 \begin{code}
348 emptyModIface :: PackageName -> ModuleName -> ModIface
349 emptyModIface pkg mod
350   = ModIface { mi_package  = pkg,
351                mi_module   = mkModule pkg mod,
352                mi_mod_vers = initialVersion,
353                mi_orphan   = False,
354                mi_boot     = False,
355                mi_deps     = noDependencies,
356                mi_usages   = [],
357                mi_exports  = [],
358                mi_exp_vers = initialVersion,
359                mi_fixities = [],
360                mi_deprecs  = NoDeprecs,
361                mi_insts = [],
362                mi_rules = [],
363                mi_decls = [],
364                mi_rule_vers = initialVersion,
365                mi_dep_fn = emptyIfaceDepCache,
366                mi_fix_fn = emptyIfaceFixCache,
367                mi_ver_fn = emptyIfaceVerCache
368     }           
369 \end{code}
370
371
372 %************************************************************************
373 %*                                                                      *
374 \subsection{The interactive context}
375 %*                                                                      *
376 %************************************************************************
377
378 \begin{code}
379 data InteractiveContext 
380   = InteractiveContext { 
381         ic_toplev_scope :: [String],    -- Include the "top-level" scope of
382                                         -- these modules
383
384         ic_exports :: [String],         -- Include just the exports of these
385                                         -- modules
386
387         ic_rn_gbl_env :: GlobalRdrEnv,  -- The cached GlobalRdrEnv, built from
388                                         -- ic_toplev_scope and ic_exports
389
390         ic_rn_local_env :: LocalRdrEnv, -- Lexical context for variables bound
391                                         -- during interaction
392
393         ic_type_env :: TypeEnv          -- Ditto for types
394     }
395
396 emptyInteractiveContext
397   = InteractiveContext { ic_toplev_scope = [],
398                          ic_exports = [],
399                          ic_rn_gbl_env = emptyGlobalRdrEnv,
400                          ic_rn_local_env = emptyLocalRdrEnv,
401                          ic_type_env = emptyTypeEnv }
402
403 icPrintUnqual :: InteractiveContext -> PrintUnqualified
404 icPrintUnqual ictxt = unQualInScope (ic_rn_gbl_env ictxt)
405 \end{code}
406
407 @unQualInScope@ returns a function that takes a @Name@ and tells whether
408 its unqualified name is in scope.  This is put as a boolean flag in
409 the @Name@'s provenance to guide whether or not to print the name qualified
410 in error messages.
411
412 \begin{code}
413 unQualInScope :: GlobalRdrEnv -> PrintUnqualified
414 -- True if 'f' is in scope, and has only one binding,
415 -- and the thing it is bound to is the name we are looking for
416 -- (i.e. false if A.f and B.f are both in scope as unqualified 'f')
417 --
418 -- [Out of date] Also checks for built-in syntax, which is always 'in scope'
419 unQualInScope env mod occ
420   = case lookupGRE_RdrName (mkRdrUnqual occ) env of
421         [gre] -> nameModuleName (gre_name gre) == mod
422         other -> False
423 \end{code}
424
425
426 %************************************************************************
427 %*                                                                      *
428                 TyThing
429 %*                                                                      *
430 %************************************************************************
431
432 \begin{code}
433 implicitTyThings :: TyThing -> [TyThing]
434 implicitTyThings (AnId id)   = []
435
436         -- For type constructors, add the data cons (and their extras),
437         -- and the selectors and generic-programming Ids too
438         --
439         -- Newtypes don't have a worker Id, so don't generate that?
440 implicitTyThings (ATyCon tc) = map AnId (tyConSelIds tc) ++ 
441                                concatMap (extras_plus . ADataCon) (tyConDataCons tc)
442                      
443         -- For classes, add the class TyCon too (and its extras)
444         -- and the class selector Ids
445 implicitTyThings (AClass cl) = map AnId (classSelIds cl) ++
446                                extras_plus (ATyCon (classTyCon cl))
447                          
448
449         -- For data cons add the worker and wrapper (if any)
450 implicitTyThings (ADataCon dc) = map AnId (dataConImplicitIds dc)
451
452 extras_plus thing = thing : implicitTyThings thing
453
454 extendTypeEnvWithIds :: TypeEnv -> [Id] -> TypeEnv
455 extendTypeEnvWithIds env ids
456   = extendNameEnvList env [(getName id, AnId id) | id <- ids]
457 \end{code}
458
459 %************************************************************************
460 %*                                                                      *
461                 TypeEnv
462 %*                                                                      *
463 %************************************************************************
464
465 \begin{code}
466 type TypeEnv = NameEnv TyThing
467
468 emptyTypeEnv   :: TypeEnv
469 typeEnvElts    :: TypeEnv -> [TyThing]
470 typeEnvClasses :: TypeEnv -> [Class]
471 typeEnvTyCons  :: TypeEnv -> [TyCon]
472 typeEnvIds     :: TypeEnv -> [Id]
473 lookupTypeEnv  :: TypeEnv -> Name -> Maybe TyThing
474
475 emptyTypeEnv       = emptyNameEnv
476 typeEnvElts    env = nameEnvElts env
477 typeEnvClasses env = [cl | AClass cl <- typeEnvElts env]
478 typeEnvTyCons  env = [tc | ATyCon tc <- typeEnvElts env] 
479 typeEnvIds     env = [id | AnId id   <- typeEnvElts env] 
480
481 mkTypeEnv :: [TyThing] -> TypeEnv
482 mkTypeEnv things = extendTypeEnvList emptyTypeEnv things
483                 
484 lookupTypeEnv = lookupNameEnv
485
486 -- Extend the type environment
487 extendTypeEnv :: TypeEnv -> TyThing -> TypeEnv
488 extendTypeEnv env thing = extendNameEnv env (getName thing) thing 
489
490 extendTypeEnvList :: TypeEnv -> [TyThing] -> TypeEnv
491 extendTypeEnvList env things = foldl extendTypeEnv env things
492 \end{code}
493
494 \begin{code}
495 lookupType :: HomePackageTable -> PackageTypeEnv -> Name -> Maybe TyThing
496 lookupType hpt pte name
497   = case lookupModuleEnv hpt (nameModule name) of
498         Just details -> lookupNameEnv (md_types (hm_details details)) name
499         Nothing      -> lookupNameEnv pte name
500 \end{code}
501
502
503 \begin{code}
504 tyThingTyCon (ATyCon tc) = tc
505 tyThingTyCon other       = pprPanic "tyThingTyCon" (ppr other)
506
507 tyThingClass (AClass cls) = cls
508 tyThingClass other        = pprPanic "tyThingClass" (ppr other)
509
510 tyThingDataCon (ADataCon dc) = dc
511 tyThingDataCon other         = pprPanic "tyThingDataCon" (ppr other)
512
513 tyThingId (AnId id) = id
514 tyThingId other     = pprPanic "tyThingId" (ppr other)
515 \end{code}
516
517 %************************************************************************
518 %*                                                                      *
519 \subsection{Auxiliary types}
520 %*                                                                      *
521 %************************************************************************
522
523 These types are defined here because they are mentioned in ModDetails,
524 but they are mostly elaborated elsewhere
525
526 \begin{code}
527 mkIfaceVerCache :: [(Version,IfaceDecl)] -> OccName -> Maybe Version
528 mkIfaceVerCache pairs 
529   = \occ -> lookupOccEnv env occ
530   where
531     env = foldl add emptyOccEnv pairs
532     add env (v,d) = extendOccEnv env (ifName d) v
533
534 emptyIfaceVerCache :: OccName -> Maybe Version
535 emptyIfaceVerCache occ = Nothing
536
537 ------------------ Deprecations -------------------------
538 data Deprecs a
539   = NoDeprecs
540   | DeprecAll DeprecTxt -- Whole module deprecated
541   | DeprecSome a        -- Some specific things deprecated
542   deriving( Eq )
543
544 type IfaceDeprecs = Deprecs [(OccName,DeprecTxt)]
545 type Deprecations = Deprecs (NameEnv (OccName,DeprecTxt))
546
547 mkIfaceDepCache:: IfaceDeprecs -> Name -> Maybe DeprecTxt
548 mkIfaceDepCache NoDeprecs         = \n -> Nothing
549 mkIfaceDepCache (DeprecAll t)     = \n -> Just t
550 mkIfaceDepCache (DeprecSome pairs) = lookupOccEnv (mkOccEnv pairs) . nameOccName
551
552 emptyIfaceDepCache :: Name -> Maybe DeprecTxt
553 emptyIfaceDepCache n = Nothing
554
555 lookupDeprec :: Deprecations -> Name -> Maybe DeprecTxt
556 lookupDeprec NoDeprecs        name = Nothing
557 lookupDeprec (DeprecAll  txt) name = Just txt
558 lookupDeprec (DeprecSome env) name = case lookupNameEnv env name of
559                                             Just (_, txt) -> Just txt
560                                             Nothing       -> Nothing
561
562 plusDeprecs :: Deprecations -> Deprecations -> Deprecations
563 plusDeprecs d NoDeprecs = d
564 plusDeprecs NoDeprecs d = d
565 plusDeprecs d (DeprecAll t) = DeprecAll t
566 plusDeprecs (DeprecAll t) d = DeprecAll t
567 plusDeprecs (DeprecSome v1) (DeprecSome v2) = DeprecSome (v1 `plusNameEnv` v2)
568 \end{code}
569
570
571 \begin{code}
572 type Avails       = [AvailInfo]
573 type AvailInfo    = GenAvailInfo Name
574 type RdrAvailInfo = GenAvailInfo OccName
575
576 data GenAvailInfo name  = Avail name     -- An ordinary identifier
577                         | AvailTC name   -- The name of the type or class
578                                   [name] -- The available pieces of type/class.
579                                          -- NB: If the type or class is itself
580                                          -- to be in scope, it must be in this list.
581                                          -- Thus, typically: AvailTC Eq [Eq, ==, /=]
582                         deriving( Eq )
583                         -- Equality used when deciding if the interface has changed
584
585 type IfaceExport = (ModuleName, [GenAvailInfo OccName])
586
587 availsToNameSet :: [AvailInfo] -> NameSet
588 availsToNameSet avails = foldl add emptyNameSet avails
589                        where
590                          add set avail = addListToNameSet set (availNames avail)
591
592 availName :: GenAvailInfo name -> name
593 availName (Avail n)     = n
594 availName (AvailTC n _) = n
595
596 availNames :: GenAvailInfo name -> [name]
597 availNames (Avail n)      = [n]
598 availNames (AvailTC n ns) = ns
599
600 instance Outputable n => Outputable (GenAvailInfo n) where
601    ppr = pprAvail
602
603 pprAvail :: Outputable n => GenAvailInfo n -> SDoc
604 pprAvail (AvailTC n ns) = ppr n <> case {- filter (/= n) -} ns of
605                                         []  -> empty
606                                         ns' -> braces (hsep (punctuate comma (map ppr ns')))
607
608 pprAvail (Avail n) = ppr n
609 \end{code}
610
611 \begin{code}
612 mkIfaceFixCache :: [(OccName, Fixity)] -> OccName -> Fixity
613 mkIfaceFixCache pairs 
614   = \n -> lookupOccEnv env n `orElse` defaultFixity
615   where
616    env = mkOccEnv pairs
617
618 emptyIfaceFixCache :: OccName -> Fixity
619 emptyIfaceFixCache n = defaultFixity
620
621 -- This fixity environment is for source code only
622 type FixityEnv = NameEnv FixItem
623
624 -- We keep the OccName in the range so that we can generate an interface from it
625 data FixItem = FixItem OccName Fixity SrcSpan
626
627 instance Outputable FixItem where
628   ppr (FixItem occ fix loc) = ppr fix <+> ppr occ <+> parens (ppr loc)
629
630 emptyFixityEnv :: FixityEnv
631 emptyFixityEnv = emptyNameEnv
632
633 lookupFixity :: FixityEnv -> Name -> Fixity
634 lookupFixity env n = case lookupNameEnv env n of
635                         Just (FixItem _ fix _) -> fix
636                         Nothing                -> defaultFixity
637 \end{code}
638
639
640 %************************************************************************
641 %*                                                                      *
642 \subsection{WhatsImported}
643 %*                                                                      *
644 %************************************************************************
645
646 \begin{code}
647 type WhetherHasOrphans   = Bool
648         -- An "orphan" is 
649         --      * an instance decl in a module other than the defn module for 
650         --              one of the tycons or classes in the instance head
651         --      * a transformation rule in a module other than the one defining
652         --              the function in the head of the rule.
653
654 type IsBootInterface = Bool
655
656 -- Dependency info about modules and packages below this one
657 -- in the import hierarchy.  See TcRnTypes.ImportAvails for details.
658 --
659 -- Invariant: the dependencies of a module M never includes M
660 -- Invariant: the lists are unordered, with no duplicates
661 data Dependencies
662   = Deps { dep_mods  :: [(ModuleName,IsBootInterface)], -- Home-package module dependencies
663            dep_pkgs  :: [PackageName],                  -- External package dependencies
664            dep_orphs :: [ModuleName] }                  -- Orphan modules (whether home or external pkg)
665
666 noDependencies :: Dependencies
667 noDependencies = Deps [] [] []
668           
669 data Usage
670   = Usage { usg_name     :: ModuleName,                 -- Name of the module
671             usg_mod      :: Version,                    -- Module version
672             usg_entities :: [(OccName,Version)],        -- Sorted by occurrence name
673             usg_exports  :: Maybe Version,              -- Export-list version, if we depend on it
674             usg_rules    :: Version                     -- Orphan-rules version (for non-orphan
675                                                         -- modules this will always be initialVersion)
676     }       deriving( Eq )
677         -- This type doesn't let you say "I imported f but none of the rules in
678         -- the module". If you use anything in the module you get its rule version
679         -- So if the rules change, you'll recompile, even if you don't use them.
680         -- This is easy to implement, and it's safer: you might not have used the rules last
681         -- time round, but if someone has added a new rule you might need it this time
682
683         -- The export list field is (Just v) if we depend on the export list:
684         --      i.e. we imported the module without saying exactly what we imported
685         -- We need to recompile if the module exports changes, because we might
686         -- now have a name clash in the importing module.
687 \end{code}
688
689
690 %************************************************************************
691 %*                                                                      *
692                 The External Package State
693 %*                                                                      *
694 %************************************************************************
695
696 \begin{code}
697 type PackageTypeEnv  = TypeEnv
698 type PackageRuleBase = RuleBase
699 type PackageInstEnv  = InstEnv
700
701 data ExternalPackageState
702   = EPS {
703         eps_is_boot :: !(ModuleEnv (ModuleName, IsBootInterface)),
704                 -- In OneShot mode (only), home-package modules accumulate in the
705                 -- external package state, and are sucked in lazily.
706                 -- For these home-pkg modules (only) we need to record which are
707                 -- boot modules.  We set this field after loading all the 
708                 -- explicitly-imported interfaces, but before doing anything else
709                 --
710                 -- The ModuleName part is not necessary, but it's useful for
711                 -- debug prints, and it's convenient because this field comes
712                 -- direct from TcRnTypes.ImportAvails.imp_dep_mods
713
714         eps_PIT :: !PackageIfaceTable,
715                 -- The ModuleIFaces for modules in external packages
716                 -- whose interfaces we have opened
717                 -- The declarations in these interface files are held in
718                 -- eps_decls, eps_insts, eps_rules (below), not in the 
719                 -- mi_decls fields of the iPIT.  
720                 -- What _is_ in the iPIT is:
721                 --      * The Module 
722                 --      * Version info
723                 --      * Its exports
724                 --      * Fixities
725                 --      * Deprecations
726
727         eps_PTE :: !PackageTypeEnv,             -- Domain = external-package modules
728
729         eps_inst_env :: !PackageInstEnv,        -- The total InstEnv accumulated from
730                                                 --   all the external-package modules
731         eps_rule_base :: !PackageRuleBase,      -- Ditto RuleEnv
732
733
734         -- Holding pens for stuff that has been read in from file,
735         -- but not yet slurped into the renamer
736         eps_insts :: !InstPool,
737                 -- The as-yet un-slurped instance decls
738                 -- Decls move from here to eps_inst_env
739                 -- Each instance is 'gated' by the names that must be 
740                 -- available before this instance decl is needed.
741
742         eps_rules :: !RulePool,
743                 -- The as-yet un-slurped rules
744
745         eps_stats :: !EpsStats
746   }
747
748 -- "In" means read from iface files
749 -- "Out" means actually sucked in and type-checked
750 data EpsStats = EpsStats { n_ifaces_in
751                          , n_decls_in, n_decls_out 
752                          , n_rules_in, n_rules_out
753                          , n_insts_in, n_insts_out :: !Int }
754 \end{code}
755
756 The NameCache makes sure that there is just one Unique assigned for
757 each original name; i.e. (module-name, occ-name) pair.  The Name is
758 always stored as a Global, and has the SrcLoc of its binding location.
759 Actually that's not quite right.  When we first encounter the original
760 name, we might not be at its binding site (e.g. we are reading an
761 interface file); so we give it 'noSrcLoc' then.  Later, when we find
762 its binding site, we fix it up.
763
764 Exactly the same is true of the Module stored in the Name.  When we first
765 encounter the occurrence, we may not know the details of the module, so
766 we just store junk.  Then when we find the binding site, we fix it up.
767
768 \begin{code}
769 data NameCache
770  = NameCache {  nsUniqs :: UniqSupply,
771                 -- Supply of uniques
772                 nsNames :: OrigNameCache,
773                 -- Ensures that one original name gets one unique
774                 nsIPs   :: OrigIParamCache
775                 -- Ensures that one implicit parameter name gets one unique
776    }
777
778 type OrigNameCache   = ModuleEnv (OccEnv Name)
779 type OrigIParamCache = FiniteMap (IPName OccName) (IPName Name)
780 \end{code}
781
782 \begin{code}
783 type Gated d = ([Name], (ModuleName, d))        -- The [Name] 'gate' the declaration; always non-empty
784                                                 -- ModuleName records which iface file this
785                                                 -- decl came from
786
787 type RulePool = [Gated IfaceRule]
788
789 addRulesToPool :: RulePool
790               -> [Gated IfaceRule]
791               -> RulePool
792 addRulesToPool rules new_rules = new_rules ++ rules
793
794 -------------------------
795 addEpsInStats :: EpsStats -> Int -> Int -> Int -> EpsStats
796 -- Add stats for one newly-read interface
797 addEpsInStats stats n_decls n_insts n_rules
798   = stats { n_ifaces_in = n_ifaces_in stats + 1
799           , n_decls_in  = n_decls_in stats + n_decls
800           , n_insts_in  = n_insts_in stats + n_insts
801           , n_rules_in  = n_rules_in stats + n_rules }
802
803 -------------------------
804 type InstPool = NameEnv [Gated IfaceInst]
805         -- The key of the Pool is the Class
806         -- The Names are the TyCons in the instance head
807         -- For example, suppose this is in an interface file
808         --      instance C T where ...
809         -- We want to slurp this decl if both C and T are "visible" in 
810         -- the importing module.  See "The gating story" in RnIfaces for details.
811
812
813 addInstsToPool :: InstPool -> [(Name, Gated IfaceInst)] -> InstPool
814 addInstsToPool insts new_insts
815   = foldr add insts new_insts
816   where
817     add :: (Name, Gated IfaceInst) -> NameEnv [Gated IfaceInst] -> NameEnv [Gated IfaceInst]
818     add (cls,new_inst) insts = extendNameEnv_C combine insts cls [new_inst]
819         where
820           combine old_insts _ = new_inst : old_insts
821 \end{code}
822
823
824 %************************************************************************
825 %*                                                                      *
826 \subsection{Linkable stuff}
827 %*                                                                      *
828 %************************************************************************
829
830 This stuff is in here, rather than (say) in Linker.lhs, because the Linker.lhs
831 stuff is the *dynamic* linker, and isn't present in a stage-1 compiler
832
833 \begin{code}
834 data Linkable = LM {
835   linkableTime     :: ClockTime,        -- Time at which this linkable was built
836                                         -- (i.e. when the bytecodes were produced,
837                                         --       or the mod date on the files)
838   linkableModName  :: ModuleName,       -- Should be Module, but see below
839   linkableUnlinked :: [Unlinked]
840  }
841
842 isObjectLinkable :: Linkable -> Bool
843 isObjectLinkable l = all isObject (linkableUnlinked l)
844
845 instance Outputable Linkable where
846    ppr (LM when_made mod unlinkeds)
847       = (text "LinkableM" <+> parens (text (show when_made)) <+> ppr mod)
848         $$ nest 3 (ppr unlinkeds)
849
850 -------------------------------------------
851 data Unlinked
852    = DotO FilePath
853    | DotA FilePath
854    | DotDLL FilePath
855    | BCOs CompiledByteCode
856
857 #ifndef GHCI
858 data CompiledByteCode = NoByteCode
859 #endif
860
861 instance Outputable Unlinked where
862    ppr (DotO path)   = text "DotO" <+> text path
863    ppr (DotA path)   = text "DotA" <+> text path
864    ppr (DotDLL path) = text "DotDLL" <+> text path
865 #ifdef GHCI
866    ppr (BCOs bcos)   = text "BCOs" <+> ppr bcos
867 #else
868    ppr (BCOs bcos)   = text "No byte code"
869 #endif
870
871 isObject (DotO _)   = True
872 isObject (DotA _)   = True
873 isObject (DotDLL _) = True
874 isObject _          = False
875
876 isInterpretable = not . isObject
877
878 nameOfObject (DotO fn)   = fn
879 nameOfObject (DotA fn)   = fn
880 nameOfObject (DotDLL fn) = fn
881
882 byteCodeOfObject (BCOs bc) = bc
883 \end{code}
884
885
886