[project @ 2003-03-03 12:43:31 by simonmar]
[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(..), 
9         GhciMode(..),
10
11         ModDetails(..), ModIface(..), 
12         ModGuts(..), ModImports(..), ForeignStubs(..),
13         ParsedIface(..), IfaceDeprecs,
14
15         HomePackageTable, HomeModInfo(..), emptyHomePackageTable,
16
17         ExternalPackageState(..),  emptyExternalPackageState,
18         PackageTypeEnv, PackageIfaceTable, emptyPackageIfaceTable,
19         lookupIface, lookupIfaceByModName, moduleNameToModule,
20         emptyModIface,
21
22         InteractiveContext(..), emptyInteractiveContext, icPrintUnqual,
23
24         IfaceDecls, mkIfaceDecls, dcl_tycl, dcl_rules, dcl_insts,
25
26         VersionInfo(..), initialVersionInfo, lookupVersion,
27         FixityEnv, lookupFixity, collectFixities, emptyFixityEnv,
28
29         TyThing(..), implicitTyThings,
30
31         TypeEnv, lookupType, mkTypeEnv, emptyTypeEnv,
32         extendTypeEnvList, extendTypeEnvWithIds,
33         typeEnvElts, typeEnvClasses, typeEnvTyCons, typeEnvIds,
34
35         WhetherHasOrphans, IsBootInterface, DeclsMap, Usage(..), 
36         Dependencies(..), noDependencies,
37         IfaceInsts, IfaceRules, GatedDecl, GatedDecls, GateFn, 
38         NameCache(..), OrigNameCache, OrigIParamCache,
39         Avails, availsToNameSet, availName, availNames,
40         GenAvailInfo(..), AvailInfo, RdrAvailInfo, 
41         ExportItem, RdrExportItem,
42
43         PersistentCompilerState(..),
44
45         Deprecations(..), lookupDeprec, plusDeprecs,
46
47         InstEnv, ClsInstEnv, DFunId,
48         PackageInstEnv, PackageRuleBase,
49
50         GlobalRdrEnv, GlobalRdrElt(..), emptyGlobalRdrEnv, pprGlobalRdrEnv,
51         LocalRdrEnv, extendLocalRdrEnv, isLocalGRE, unQualInScope,
52         
53         -- Linker stuff
54         Linkable(..), isObjectLinkable,
55         Unlinked(..), CompiledByteCode,
56         isObject, nameOfObject, isInterpretable, byteCodeOfObject,
57
58         -- Provenance
59         Provenance(..), ImportReason(..), 
60         pprNameProvenance, hasBetterProv
61
62     ) where
63
64 #include "HsVersions.h"
65
66 #ifdef GHCI
67 import ByteCodeAsm      ( CompiledByteCode )
68 #endif
69
70 import RdrName          ( RdrName, mkRdrUnqual, 
71                           RdrNameEnv, addListToRdrEnv, foldRdrEnv, isUnqual,
72                           rdrEnvToList, emptyRdrEnv )
73 import Name             ( Name, NamedThing, getName, nameOccName, nameModule, nameSrcLoc )
74 import NameEnv
75 import NameSet  
76 import OccName          ( OccName )
77 import Module
78 import InstEnv          ( InstEnv, ClsInstEnv, DFunId )
79 import Rules            ( RuleBase )
80 import CoreSyn          ( CoreBind )
81 import Id               ( Id, idName )
82 import Class            ( Class, classSelIds, classTyCon )
83 import TyCon            ( TyCon, tyConName, isNewTyCon, tyConGenIds, tyConSelIds, tyConDataCons )
84 import TcType           ( TyThing(..) )
85 import DataCon          ( dataConWorkId, dataConWrapId, dataConWrapId_maybe )
86 import Packages         ( PackageName, basePackage )
87 import CmdLineOpts      ( DynFlags )
88
89 import BasicTypes       ( Version, initialVersion, IPName,
90                           Fixity, FixitySig(..), defaultFixity )
91
92 import HsSyn            ( DeprecTxt, TyClDecl, InstDecl, RuleDecl,
93                           tyClDeclName, ifaceRuleDeclName, tyClDeclNames,
94                           instDeclDFun )
95 import RnHsSyn          ( RenamedTyClDecl, RenamedRuleDecl, RenamedInstDecl )
96
97 import CoreSyn          ( IdCoreRule )
98 import PrelNames        ( isBuiltInSyntaxName )
99 import InstEnv          ( emptyInstEnv )
100 import Rules            ( emptyRuleBase )
101
102 import FiniteMap
103 import Bag              ( Bag, emptyBag )
104 import Maybes           ( orElse )
105 import Outputable
106 import SrcLoc           ( SrcLoc, isGoodSrcLoc )
107 import Util             ( thenCmp, sortLt )
108 import UniqSupply       ( UniqSupply )
109 import Maybe            ( fromJust )
110 import FastString       ( FastString )
111
112 import Time             ( ClockTime )
113 \end{code}
114
115
116 %************************************************************************
117 %*                                                                      *
118 \subsection{Compilation environment}
119 %*                                                                      *
120 %************************************************************************
121
122 The HscEnv gives the environment in which to compile a chunk of code.
123
124 \begin{code}
125 data HscEnv = HscEnv { hsc_mode   :: GhciMode,
126                        hsc_dflags :: DynFlags,
127                        hsc_HPT    :: HomePackageTable }
128 \end{code}
129
130 The GhciMode is self-explanatory:
131
132 \begin{code}
133 data GhciMode = Batch | Interactive | OneShot 
134               deriving Eq
135 \end{code}
136
137 \begin{code}
138 type HomePackageTable  = ModuleEnv HomeModInfo  -- Domain = modules in the home package
139 type PackageIfaceTable = ModuleEnv ModIface     -- Domain = modules in the imported packages
140
141 emptyHomePackageTable  = emptyModuleEnv
142 emptyPackageIfaceTable = emptyModuleEnv
143
144 data HomeModInfo = HomeModInfo { hm_iface    :: ModIface,
145                                  hm_details  :: ModDetails,
146                                  hm_linkable :: Linkable }
147 \end{code}
148
149 Simple lookups in the symbol table.
150
151 \begin{code}
152 lookupIface :: HomePackageTable -> PackageIfaceTable -> Module -> Maybe ModIface
153 -- We often have two IfaceTables, and want to do a lookup
154 lookupIface hpt pit mod
155   = case lookupModuleEnv hpt mod of
156         Just mod_info -> Just (hm_iface mod_info)
157         Nothing       -> lookupModuleEnv pit mod
158
159 lookupIfaceByModName :: HomePackageTable -> PackageIfaceTable -> ModuleName -> Maybe ModIface
160 -- We often have two IfaceTables, and want to do a lookup
161 lookupIfaceByModName hpt pit mod
162   = case lookupModuleEnvByName hpt mod of
163         Just mod_info -> Just (hm_iface mod_info)
164         Nothing       -> lookupModuleEnvByName pit mod
165 \end{code}
166
167 \begin{code}
168 -- Use instead of Finder.findModule if possible: this way doesn't
169 -- require filesystem operations, and it is guaranteed not to fail
170 -- when the IfaceTables are properly populated (i.e. after the renamer).
171 moduleNameToModule :: HomePackageTable -> PackageIfaceTable -> ModuleName -> Module
172 moduleNameToModule hpt pit mod 
173    = mi_module (fromJust (lookupIfaceByModName hpt pit mod))
174 \end{code}
175
176
177 %************************************************************************
178 %*                                                                      *
179 \subsection{Symbol tables and Module details}
180 %*                                                                      *
181 %************************************************************************
182
183 A @ModIface@ plus a @ModDetails@ summarises everything we know 
184 about a compiled module.  The @ModIface@ is the stuff *before* linking,
185 and can be written out to an interface file.  (The @ModDetails@ is after 
186 linking; it is the "linked" form of the mi_decls field.)
187
188 When we *read* an interface file, we also construct a @ModIface@ from it,
189 except that the mi_decls part is empty; when reading we consolidate
190 the declarations into a single indexed map in the @PersistentRenamerState@.
191
192 \begin{code}
193 data ModIface 
194    = ModIface {
195         mi_module   :: !Module,
196         mi_package  :: !PackageName,        -- Which package the module comes from
197         mi_version  :: !VersionInfo,        -- Version info for everything in this module
198         mi_orphan   :: !WhetherHasOrphans,  -- Whether this module has orphans
199         mi_boot     :: !IsBootInterface,    -- Read from an hi-boot file?
200
201         mi_deps     :: Dependencies,
202                 -- This is consulted for directly-imported modules, but
203                 -- not for anything else
204
205         mi_usages   :: [Usage Name],
206                 -- Usages; kept sorted so that it's easy to decide
207                 -- whether to write a new iface file (changing usages
208                 -- doesn't affect the version of this module)
209                 -- NOT STRICT!  we read this field lazily from the interface file
210                 -- It is *only* consulted by the recompilation checker
211
212         mi_exports  :: ![ExportItem],
213                 -- What it exports Kept sorted by (mod,occ), to make
214                 -- version comparisons easier
215
216         mi_globals  :: !(Maybe GlobalRdrEnv),
217                 -- Its top level environment or Nothing if we read this
218                 -- interface from an interface file.  (We need the source
219                 -- file to figure out the top-level environment.)
220
221         mi_fixities :: !FixityEnv,          -- Fixities
222         mi_deprecs  :: Deprecations,        -- Deprecations
223                 -- NOT STRICT!  we read this field lazilly from the interface file
224
225         mi_decls    :: IfaceDecls           -- The RnDecls form of ModDetails
226                 -- NOT STRICT!  we fill this field with _|_ sometimes
227      }
228
229 -- Should be able to construct ModDetails from mi_decls in ModIface
230 data ModDetails
231    = ModDetails {
232         -- The next three fields are created by the typechecker
233         md_types    :: !TypeEnv,
234         md_insts    :: ![DFunId],       -- Dfun-ids for the instances in this module
235         md_rules    :: ![IdCoreRule]    -- Domain may include Ids from other modules
236      }
237
238 -- A ModGuts is carried through the compiler, accumulating stuff as it goes
239 -- There is only one ModGuts at any time, the one for the module
240 -- being compiled right now.  Once it is compiled, a ModIface and 
241 -- ModDetails are extracted and the ModGuts is dicarded.
242
243 data ModGuts
244   = ModGuts {
245         mg_module   :: !Module,
246         mg_exports  :: !Avails,         -- What it exports
247         mg_deps     :: !Dependencies,   -- What is below it, directly or otherwise
248         mg_dir_imps :: ![Module],       -- Directly-imported modules; used to
249                                         --      generate initialisation code
250         mg_usages   :: ![Usage Name],   -- Version info for what it needed
251
252         mg_rdr_env  :: !GlobalRdrEnv,   -- Top-level lexical environment
253         mg_fix_env  :: !FixityEnv,      -- Fixity env, for things declared in this module
254         mg_deprecs  :: !Deprecations,   -- Deprecations declared in the module
255
256         mg_types    :: !TypeEnv,
257         mg_insts    :: ![DFunId],       -- Instances 
258         mg_rules    :: ![IdCoreRule],   -- Rules from this module
259         mg_binds    :: ![CoreBind],     -- Bindings for this module
260         mg_foreign  :: !ForeignStubs
261     }
262
263 -- The ModGuts takes on several slightly different forms:
264 --
265 -- After simplification, the following fields change slightly:
266 --      mg_rules        Orphan rules only (local ones now attached to binds)
267 --      mg_binds        With rules attached
268 --
269 -- After CoreTidy, the following fields change slightly:
270 --      mg_types        Now contains Ids as well, replete with final IdInfo
271 --                         The Ids are only the ones that are visible from
272 --                         importing modules.  Without -O that means only
273 --                         exported Ids, but with -O importing modules may
274 --                         see ids mentioned in unfoldings of exported Ids
275 --
276 --      mg_insts        Same DFunIds as before, but with final IdInfo,
277 --                         and the unique might have changed; remember that
278 --                         CoreTidy links up the uniques of old and new versions
279 --
280 --      mg_rules        All rules for exported things, substituted with final Ids
281 --
282 --      mg_binds        Tidied
283
284
285
286 data ModImports
287   = ModImports {
288         imp_direct     :: ![(Module,Bool)],     -- Explicitly-imported modules
289                                                 -- Boolean is true if we imported the whole
290                                                 --      module (apart, perhaps, from hiding some)
291         imp_pkg_mods   :: !ModuleSet,           -- Non-home-package modules on which we depend,
292                                                 --      directly or indirectly
293         imp_home_names :: !NameSet              -- Home package things on which we depend,
294                                                 --      directly or indirectly
295     }
296
297 data ForeignStubs = NoStubs
298                   | ForeignStubs
299                         SDoc            -- Header file prototypes for
300                                         --      "foreign exported" functions
301                         SDoc            -- C stubs to use when calling
302                                         --      "foreign exported" functions
303                         [FastString]    -- Headers that need to be included
304                                         --      into C code generated for this module
305                         [Id]            -- Foreign-exported binders
306                                         --      we have to generate code to register these
307
308
309 data IfaceDecls = IfaceDecls { dcl_tycl  :: [RenamedTyClDecl],  -- Sorted
310                                dcl_rules :: [RenamedRuleDecl],  -- Sorted
311                                dcl_insts :: [RenamedInstDecl] } -- Unsorted
312
313 mkIfaceDecls :: [RenamedTyClDecl] -> [RenamedRuleDecl] -> [RenamedInstDecl] -> IfaceDecls
314 -- Sort to put them in canonical order for version comparison
315 mkIfaceDecls tycls rules insts
316   = IfaceDecls { dcl_tycl  = sortLt lt_tycl tycls,
317                  dcl_rules = sortLt lt_rule rules,
318                  dcl_insts = sortLt lt_inst insts }
319   where
320     d1 `lt_tycl` d2 = tyClDeclName      d1 < tyClDeclName      d2
321     r1 `lt_rule` r2 = ifaceRuleDeclName r1 < ifaceRuleDeclName r2
322     i1 `lt_inst` i2 = instDeclDFun      i1 < instDeclDFun      i2
323 \end{code}
324
325 \begin{code}
326 emptyModIface :: Module -> ModIface
327 emptyModIface mod
328   = ModIface { mi_module   = mod,
329                mi_package  = basePackage, -- XXX fully bogus
330                mi_version  = initialVersionInfo,
331                mi_usages   = [],
332                mi_deps     = noDependencies,
333                mi_orphan   = False,
334                mi_boot     = False,
335                mi_exports  = [],
336                mi_fixities = emptyNameEnv,
337                mi_globals  = Nothing,
338                mi_deprecs  = NoDeprecs,
339                mi_decls    = panic "emptyModIface: decls"
340     }           
341 \end{code}
342
343
344 %************************************************************************
345 %*                                                                      *
346                 Parsed interface files
347 %*                                                                      *
348 %************************************************************************
349
350 A ParsedIface is exactly as read from an interface file.
351
352 \begin{code}
353 type IfaceDeprecs = Maybe (Either DeprecTxt [(RdrName,DeprecTxt)])
354         -- Nothing        => NoDeprecs
355         -- Just (Left t)  => DeprecAll
356         -- Just (Right p) => DeprecSome
357
358 data ParsedIface
359   = ParsedIface {
360       pi_mod       :: ModuleName,
361       pi_pkg       :: PackageName,
362       pi_vers      :: Version,                          -- Module version number
363       pi_orphan    :: WhetherHasOrphans,                -- Whether this module has orphans
364       pi_deps      :: Dependencies,                     -- What it depends on
365       pi_usages    :: [Usage OccName],                  -- Usages
366       pi_exports   :: (Version, [RdrExportItem]),       -- Exports
367       pi_decls     :: [(Version, TyClDecl RdrName)],    -- Local definitions
368       pi_fixity    :: [FixitySig RdrName],              -- Local fixity declarations,
369       pi_insts     :: [InstDecl RdrName],               -- Local instance declarations
370       pi_rules     :: (Version, [RuleDecl RdrName]),    -- Rules, with their version
371       pi_deprecs   :: IfaceDeprecs                      -- Deprecations
372     }
373 \end{code}
374
375
376 %************************************************************************
377 %*                                                                      *
378 \subsection{The interactive context}
379 %*                                                                      *
380 %************************************************************************
381
382 \begin{code}
383 data InteractiveContext 
384   = InteractiveContext { 
385         ic_toplev_scope :: [Module],    -- Include the "top-level" scope of
386                                         -- these modules
387
388         ic_exports :: [Module],         -- Include just the exports of these
389                                         -- modules
390
391         ic_rn_gbl_env :: GlobalRdrEnv,  -- The cached GlobalRdrEnv, built from
392                                         -- ic_toplev_scope and ic_exports
393
394         ic_rn_local_env :: LocalRdrEnv, -- Lexical context for variables bound
395                                         -- during interaction
396
397         ic_type_env :: TypeEnv          -- Ditto for types
398     }
399
400 emptyInteractiveContext
401   = InteractiveContext { ic_toplev_scope = [],
402                          ic_exports = [],
403                          ic_rn_gbl_env = emptyRdrEnv,
404                          ic_rn_local_env = emptyRdrEnv,
405                          ic_type_env = emptyTypeEnv }
406
407 icPrintUnqual :: InteractiveContext -> PrintUnqualified
408 icPrintUnqual ictxt = unQualInScope (ic_rn_gbl_env ictxt)
409 \end{code}
410
411
412 %************************************************************************
413 %*                                                                      *
414 \subsection{Type environment stuff}
415 %*                                                                      *
416 %************************************************************************
417
418 \begin{code}
419 typeEnvElts    :: TypeEnv -> [TyThing]
420 typeEnvClasses :: TypeEnv -> [Class]
421 typeEnvTyCons  :: TypeEnv -> [TyCon]
422 typeEnvIds     :: TypeEnv -> [Id]
423
424 typeEnvElts    env = nameEnvElts env
425 typeEnvClasses env = [cl | AClass cl <- typeEnvElts env]
426 typeEnvTyCons  env = [tc | ATyCon tc <- typeEnvElts env] 
427 typeEnvIds     env = [id | AnId id   <- typeEnvElts env] 
428 \end{code}
429
430
431 \begin{code}
432 type TypeEnv = NameEnv TyThing
433
434 emptyTypeEnv = emptyNameEnv
435
436 mkTypeEnv :: [TyThing] -> TypeEnv
437 mkTypeEnv things = extendTypeEnvList emptyTypeEnv things
438                 
439 extendTypeEnvList :: TypeEnv -> [TyThing] -> TypeEnv
440 -- Extend the type environment
441 extendTypeEnvList env things
442   = foldl extend env things
443   where
444     extend env thing = extendNameEnv env (getName thing) thing
445
446 implicitTyThings :: [TyThing] -> [TyThing]
447 implicitTyThings things
448   = concatMap extras things
449   where
450     extras_plus thing = thing : extras thing
451
452     extras (AnId id)   = []
453
454         -- For type constructors, add the data cons (and their extras),
455         -- and the selectors and generic-programming Ids too
456         --
457         -- Newtypes don't have a worker Id, so don't generate that
458     extras (ATyCon tc) = map AnId (tyConGenIds tc ++ tyConSelIds tc) ++ data_con_stuff
459        where
460         data_con_stuff | isNewTyCon tc = [ADataCon dc1, AnId (dataConWrapId dc1)]
461                        | otherwise     = concatMap (extras_plus . ADataCon) dcs
462         dcs = tyConDataCons tc
463         dc1 = head dcs
464                      
465         -- For classes, add the class TyCon too (and its extras)
466         -- and the class selector Ids
467     extras (AClass cl) = map AnId (classSelIds cl) ++
468                          extras_plus (ATyCon (classTyCon cl))
469                          
470
471         -- For data cons add the worker and wrapper (if any)
472     extras (ADataCon dc) 
473         = AnId (dataConWorkId dc) : wrap_id_stuff
474         where
475                 -- May or may not have a wrapper
476           wrap_id_stuff = case dataConWrapId_maybe dc of 
477                                 Just id -> [AnId id]
478                                 Nothing -> []
479
480 extendTypeEnvWithIds :: TypeEnv -> [Id] -> TypeEnv
481 extendTypeEnvWithIds env ids
482   = extendNameEnvList env [(getName id, AnId id) | id <- ids]
483 \end{code}
484
485 \begin{code}
486 lookupType :: HomePackageTable -> PackageTypeEnv -> Name -> Maybe TyThing
487 lookupType hpt pte name
488   = case lookupModuleEnv hpt (nameModule name) of
489         Just details -> lookupNameEnv (md_types (hm_details details)) name
490         Nothing      -> lookupNameEnv pte name
491 \end{code}
492
493 %************************************************************************
494 %*                                                                      *
495 \subsection{Auxiliary types}
496 %*                                                                      *
497 %************************************************************************
498
499 These types are defined here because they are mentioned in ModDetails,
500 but they are mostly elaborated elsewhere
501
502 \begin{code}
503 data VersionInfo 
504   = VersionInfo {
505         vers_module  :: Version,        -- Changes when anything changes
506         vers_exports :: Version,        -- Changes when export list changes
507         vers_rules   :: Version,        -- Changes when any rule changes
508         vers_decls   :: NameEnv Version
509                 -- Versions for "big" names only (not data constructors, class ops)
510                 -- The version of an Id changes if its fixity changes
511                 -- Ditto data constructors, class operations, except that the version of
512                 -- the parent class/tycon changes
513                 --
514                 -- If a name isn't in the map, it means 'initialVersion'
515     }
516
517 initialVersionInfo :: VersionInfo
518 initialVersionInfo = VersionInfo { vers_module  = initialVersion,
519                                    vers_exports = initialVersion,
520                                    vers_rules   = initialVersion,
521                                    vers_decls   = emptyNameEnv
522                         }
523
524 lookupVersion :: NameEnv Version -> Name -> Version
525 lookupVersion env name = lookupNameEnv env name `orElse` initialVersion
526
527 data Deprecations = NoDeprecs
528                   | DeprecAll DeprecTxt                         -- Whole module deprecated
529                   | DeprecSome (NameEnv (Name,DeprecTxt))       -- Some things deprecated
530                                                                 -- Just "big" names
531                 -- We keep the Name in the range, so we can print them out
532
533 lookupDeprec :: Deprecations -> Name -> Maybe DeprecTxt
534 lookupDeprec NoDeprecs        name = Nothing
535 lookupDeprec (DeprecAll  txt) name = Just txt
536 lookupDeprec (DeprecSome env) name = case lookupNameEnv env name of
537                                             Just (_, txt) -> Just txt
538                                             Nothing       -> Nothing
539
540 plusDeprecs :: Deprecations -> Deprecations -> Deprecations
541 plusDeprecs d NoDeprecs = d
542 plusDeprecs NoDeprecs d = d
543 plusDeprecs d (DeprecAll t) = DeprecAll t
544 plusDeprecs (DeprecAll t) d = DeprecAll t
545 plusDeprecs (DeprecSome v1) (DeprecSome v2) = DeprecSome (v1 `plusNameEnv` v2)
546
547 instance Eq Deprecations where
548   -- Used when checking whether we need write a new interface
549   NoDeprecs       == NoDeprecs       = True
550   (DeprecAll t1)  == (DeprecAll t2)  = t1 == t2
551   (DeprecSome e1) == (DeprecSome e2) = nameEnvElts e1 == nameEnvElts e2
552   d1              == d2              = False
553 \end{code}
554
555
556 \begin{code}
557 type Avails       = [AvailInfo]
558 type AvailInfo    = GenAvailInfo Name
559 type RdrAvailInfo = GenAvailInfo OccName
560
561 data GenAvailInfo name  = Avail name     -- An ordinary identifier
562                         | AvailTC name   -- The name of the type or class
563                                   [name] -- The available pieces of type/class.
564                                          -- NB: If the type or class is itself
565                                          -- to be in scope, it must be in this list.
566                                          -- Thus, typically: AvailTC Eq [Eq, ==, /=]
567                         deriving( Eq )
568                         -- Equality used when deciding if the interface has changed
569
570 type RdrExportItem = (ModuleName, [RdrAvailInfo])
571 type ExportItem    = (ModuleName, [AvailInfo])
572
573 availsToNameSet :: [AvailInfo] -> NameSet
574 availsToNameSet avails = foldl add emptyNameSet avails
575                        where
576                          add set avail = addListToNameSet set (availNames avail)
577
578 availName :: GenAvailInfo name -> name
579 availName (Avail n)     = n
580 availName (AvailTC n _) = n
581
582 availNames :: GenAvailInfo name -> [name]
583 availNames (Avail n)      = [n]
584 availNames (AvailTC n ns) = ns
585
586 instance Outputable n => Outputable (GenAvailInfo n) where
587    ppr = pprAvail
588
589 pprAvail :: Outputable n => GenAvailInfo n -> SDoc
590 pprAvail (AvailTC n ns) = ppr n <> case {- filter (/= n) -} ns of
591                                         []  -> empty
592                                         ns' -> braces (hsep (punctuate comma (map ppr ns')))
593
594 pprAvail (Avail n) = ppr n
595 \end{code}
596
597 \begin{code}
598 type FixityEnv = NameEnv (FixitySig Name)
599         -- We keep the whole fixity sig so that we
600         -- can report line-number info when there is a duplicate
601         -- fixity declaration
602
603 emptyFixityEnv :: FixityEnv
604 emptyFixityEnv = emptyNameEnv
605
606 lookupFixity :: FixityEnv -> Name -> Fixity
607 lookupFixity env n = case lookupNameEnv env n of
608                         Just (FixitySig _ fix _) -> fix
609                         Nothing                  -> defaultFixity
610
611 collectFixities :: FixityEnv -> [TyClDecl Name] -> [FixitySig Name]
612 -- Collect fixities for the specified declarations
613 collectFixities env decls
614   = [ fix
615     | d <- decls, (n,_) <- tyClDeclNames d,
616       Just fix <- [lookupNameEnv env n]
617     ]
618 \end{code}
619
620
621 %************************************************************************
622 %*                                                                      *
623 \subsection{WhatsImported}
624 %*                                                                      *
625 %************************************************************************
626
627 \begin{code}
628 type WhetherHasOrphans   = Bool
629         -- An "orphan" is 
630         --      * an instance decl in a module other than the defn module for 
631         --              one of the tycons or classes in the instance head
632         --      * a transformation rule in a module other than the one defining
633         --              the function in the head of the rule.
634
635 type IsBootInterface = Bool
636
637 -- Dependency info about modules and packages below this one
638 -- in the import hierarchy.  See TcRnTypes.ImportAvails for details.
639 --
640 -- Invariant: the dependencies of a module M never includes M
641 data Dependencies
642   = Deps { dep_mods  :: [(ModuleName,IsBootInterface)], -- Home-package module dependencies
643            dep_pkgs  :: [PackageName],                  -- External package dependencies
644            dep_orphs :: [ModuleName] }                  -- Orphan modules (whether home or external pkg)
645
646 noDependencies :: Dependencies
647 noDependencies = Deps [] [] []
648           
649 data Usage name 
650   = Usage { usg_name     :: ModuleName,         -- Name of the module
651             usg_mod      :: Version,            -- Module version
652             usg_exports  :: Maybe Version,      -- Export-list version, if we depend on it
653             usg_entities :: [(name,Version)],   -- Sorted by occurrence name
654             usg_rules    :: Version             -- Rules version
655     }       deriving( Eq )
656         -- This type doesn't let you say "I imported f but none of the rules in
657         -- the module". If you use anything in the module you get its rule version
658         -- So if the rules change, you'll recompile, even if you don't use them.
659         -- This is easy to implement, and it's safer: you might not have used the rules last
660         -- time round, but if someone has added a new rule you might need it this time
661
662         -- The export list field is (Just v) if we depend on the export list:
663         --      i.e. we imported the module without saying exactly what we imported
664         -- We need to recompile if the module exports changes, because we might
665         -- now have a name clash in the importing module.
666 \end{code}
667
668
669 %************************************************************************
670 %*                                                                      *
671 \subsection{The persistent compiler state}
672 %*                                                                      *
673 %************************************************************************
674
675 The @PersistentCompilerState@ persists across successive calls to the
676 compiler.
677
678 \begin{code}
679 data PersistentCompilerState 
680    = PCS {
681         pcs_nc  :: !NameCache,
682         pcs_EPS :: ExternalPackageState
683                 -- non-strict because we fill it with error in HscMain
684      }
685 \end{code}
686
687
688 \begin{code}
689 type PackageTypeEnv  = TypeEnv
690 type PackageRuleBase = RuleBase
691 type PackageInstEnv  = InstEnv
692
693 data ExternalPackageState
694   = EPS {
695         eps_PIT :: !PackageIfaceTable,
696                 -- The ModuleIFaces for modules in external packages
697                 -- whose interfaces we have opened
698                 -- The declarations in these interface files are held in
699                 -- eps_decls, eps_insts, eps_rules (below), not in the 
700                 -- mi_decls fields of the iPIT.  
701                 -- What _is_ in the iPIT is:
702                 --      * The Module 
703                 --      * Version info
704                 --      * Its exports
705                 --      * Fixities
706                 --      * Deprecations
707
708         eps_PTE :: !PackageTypeEnv,             -- Domain = external-package modules
709
710         eps_inst_env :: !PackageInstEnv,        -- The total InstEnv accumulated from
711                                                 --   all the external-package modules
712         eps_rule_base :: !PackageRuleBase,      -- Ditto RuleEnv
713
714
715         -- Holding pens for stuff that has been read in from file,
716         -- but not yet slurped into the renamer
717         eps_decls      :: !DeclsMap,
718                 -- A single, global map of Names to unslurped decls
719         eps_insts      :: !IfaceInsts,
720                 -- The as-yet un-slurped instance decls; this bag is depleted when we
721                 -- slurp an instance decl so that we don't slurp the same one twice.
722                 -- Each is 'gated' by the names that must be available before
723                 -- this instance decl is needed.
724         eps_rules      :: !IfaceRules,
725                 -- Similar to instance decls, only for rules
726
727         eps_inst_gates :: !NameSet      -- Gates for instance decls
728                 -- The instance gates must accumulate across
729                 -- all invocations of the renamer; 
730                 -- see "the gating story" in RnIfaces.lhs
731                 -- These names should all be from other packages;
732                 -- for the home package we have all the instance
733                 -- declarations anyhow
734   }
735
736 emptyExternalPackageState = EPS { 
737       eps_decls      = (emptyNameEnv, 0),
738       eps_insts      = (emptyBag, 0),
739       eps_inst_gates = emptyNameSet,
740       eps_rules      = (emptyBag, 0),
741       eps_PIT        = emptyPackageIfaceTable,
742       eps_PTE        = emptyTypeEnv,
743       eps_inst_env   = emptyInstEnv,
744       eps_rule_base  = emptyRuleBase
745    }
746 \end{code}
747
748 The NameCache makes sure that there is just one Unique assigned for
749 each original name; i.e. (module-name, occ-name) pair.  The Name is
750 always stored as a Global, and has the SrcLoc of its binding location.
751 Actually that's not quite right.  When we first encounter the original
752 name, we might not be at its binding site (e.g. we are reading an
753 interface file); so we give it 'noSrcLoc' then.  Later, when we find
754 its binding site, we fix it up.
755
756 Exactly the same is true of the Module stored in the Name.  When we first
757 encounter the occurrence, we may not know the details of the module, so
758 we just store junk.  Then when we find the binding site, we fix it up.
759
760 \begin{code}
761 data NameCache
762  = NameCache {  nsUniqs :: UniqSupply,
763                 -- Supply of uniques
764                 nsNames :: OrigNameCache,
765                 -- Ensures that one original name gets one unique
766                 nsIPs   :: OrigIParamCache
767                 -- Ensures that one implicit parameter name gets one unique
768    }
769
770 type OrigNameCache = ModuleEnv (Module, OccNameCache)
771         -- Maps a module *name* to a Module, 
772         -- plus the OccNameEnv fot that module
773 type OccNameCache = FiniteMap OccName Name
774         -- Maps the OccName to a Name
775         -- A FiniteMap because OccNames have a Namespace/Faststring pair
776
777 type OrigIParamCache = FiniteMap (IPName RdrName) (IPName Name)
778 \end{code}
779
780 A DeclsMap contains a binding for each Name in the declaration
781 including the constructors of a type decl etc.  The Bool is True just
782 for the 'main' Name.
783
784 \begin{code}
785 type DeclsMap = (NameEnv (AvailInfo, Bool, (Module, TyClDecl RdrName)), Int)
786                                                 -- The Int says how many have been sucked in
787
788 type IfaceInsts = GatedDecls (InstDecl RdrName)
789 type IfaceRules = GatedDecls (RuleDecl RdrName)
790
791 type GatedDecls d = (Bag (GatedDecl d), Int)    -- The Int says how many have been sucked in
792 type GatedDecl  d = (GateFn, (Module, d))
793 type GateFn       = (Name -> Bool) -> Bool      -- Returns True <=> gate is open
794                                                 -- The (Name -> Bool) fn returns True for visible Names
795         -- For example, suppose this is in an interface file
796         --      instance C T where ...
797         -- We want to slurp this decl if both C and T are "visible" in 
798         -- the importing module.  See "The gating story" in RnIfaces for details.
799 \end{code}
800
801
802 %************************************************************************
803 %*                                                                      *
804 \subsection{Linkable stuff}
805 %*                                                                      *
806 %************************************************************************
807
808 This stuff is in here, rather than (say) in Linker.lhs, because the Linker.lhs
809 stuff is the *dynamic* linker, and isn't present in a stage-1 compiler
810
811 \begin{code}
812 data Linkable = LM {
813   linkableTime     :: ClockTime,        -- Time at which this linkable was built
814                                         -- (i.e. when the bytecodes were produced,
815                                         --       or the mod date on the files)
816   linkableModName  :: ModuleName,       -- Should be Module, but see below
817   linkableUnlinked :: [Unlinked]
818  }
819
820 isObjectLinkable :: Linkable -> Bool
821 isObjectLinkable l = all isObject (linkableUnlinked l)
822
823 instance Outputable Linkable where
824    ppr (LM when_made mod unlinkeds)
825       = (text "LinkableM" <+> parens (text (show when_made)) <+> ppr mod)
826         $$ nest 3 (ppr unlinkeds)
827
828 -------------------------------------------
829 data Unlinked
830    = DotO FilePath
831    | DotA FilePath
832    | DotDLL FilePath
833    | BCOs CompiledByteCode
834
835 #ifndef GHCI
836 data CompiledByteCode = NoByteCode
837 #endif
838
839 instance Outputable Unlinked where
840    ppr (DotO path)   = text "DotO" <+> text path
841    ppr (DotA path)   = text "DotA" <+> text path
842    ppr (DotDLL path) = text "DotDLL" <+> text path
843 #ifdef GHCI
844    ppr (BCOs bcos)   = text "BCOs" <+> ppr bcos
845 #else
846    ppr (BCOs bcos)   = text "No byte code"
847 #endif
848
849 isObject (DotO _)   = True
850 isObject (DotA _)   = True
851 isObject (DotDLL _) = True
852 isObject _          = False
853
854 isInterpretable = not . isObject
855
856 nameOfObject (DotO fn)   = fn
857 nameOfObject (DotA fn)   = fn
858 nameOfObject (DotDLL fn) = fn
859
860 byteCodeOfObject (BCOs bc) = bc
861 \end{code}
862
863
864 %************************************************************************
865 %*                                                                      *
866 \subsection{Provenance and export info}
867 %*                                                                      *
868 %************************************************************************
869
870 A LocalRdrEnv is used for local bindings (let, where, lambda, case)
871 Also used in 
872
873 \begin{code}
874 type LocalRdrEnv = RdrNameEnv Name
875
876 extendLocalRdrEnv :: LocalRdrEnv -> [Name] -> LocalRdrEnv
877 extendLocalRdrEnv env names
878   = addListToRdrEnv env [(mkRdrUnqual (nameOccName n), n) | n <- names]
879 \end{code}
880
881 The GlobalRdrEnv gives maps RdrNames to Names.  There is a separate
882 one for each module, corresponding to that module's top-level scope.
883
884 \begin{code}
885 type GlobalRdrEnv = RdrNameEnv [GlobalRdrElt]
886         -- The list is because there may be name clashes
887         -- These only get reported on lookup, not on construction
888
889 emptyGlobalRdrEnv = emptyRdrEnv
890
891 data GlobalRdrElt 
892   = GRE { gre_name   :: Name,
893           gre_parent :: Maybe Name,     -- Name of the "parent" structure, for
894                                         --      * the tycon of a data con
895                                         --      * the class of a class op
896                                         -- For others it's Nothing
897                 -- Invariant: gre_name g /= gre_parent g
898                 --      when the latter is a Just
899
900           gre_prov   :: Provenance,     -- Why it's in scope
901           gre_deprec :: Maybe DeprecTxt -- Whether this name is deprecated
902     }
903
904 instance Outputable GlobalRdrElt where
905   ppr gre = ppr (gre_name gre) <+> 
906             parens (pp_parent (gre_parent gre) <+> pprNameProvenance gre)
907           where
908             pp_parent (Just p) = text "parent:" <+> ppr p <> comma
909             pp_parent Nothing  = empty
910
911 pprGlobalRdrEnv env
912   = vcat (map pp (rdrEnvToList env))
913   where
914     pp (rn, gres) = ppr rn <> colon <+> 
915                     vcat [ ppr (gre_name gre) <+> pprNameProvenance gre
916                          | gre <- gres]
917
918 isLocalGRE :: GlobalRdrElt -> Bool
919 isLocalGRE (GRE {gre_prov = LocalDef}) = True
920 isLocalGRE other                       = False
921 \end{code}
922
923 @unQualInScope@ returns a function that takes a @Name@ and tells whether
924 its unqualified name is in scope.  This is put as a boolean flag in
925 the @Name@'s provenance to guide whether or not to print the name qualified
926 in error messages.
927
928 \begin{code}
929 unQualInScope :: GlobalRdrEnv -> Name -> Bool
930 -- True if 'f' is in scope, and has only one binding,
931 -- and the thing it is bound to is the name we are looking for
932 -- (i.e. false if A.f and B.f are both in scope as unqualified 'f')
933 --
934 -- Also checks for built-in syntax, which is always 'in scope'
935 --
936 -- This fn is only efficient if the shared 
937 -- partial application is used a lot.
938 unQualInScope env
939   = \n -> n `elemNameSet` unqual_names || isBuiltInSyntaxName n
940   where
941     unqual_names :: NameSet
942     unqual_names = foldRdrEnv add emptyNameSet env
943     add rdr_name [gre] unquals | isUnqual rdr_name = addOneToNameSet unquals (gre_name gre)
944     add _        _     unquals                     = unquals
945 \end{code}
946
947 The "provenance" of something says how it came to be in scope.
948
949 \begin{code}
950 data Provenance
951   = LocalDef                    -- Defined locally
952
953   | NonLocalDef                 -- Defined non-locally
954         ImportReason
955
956 -- Just used for grouping error messages (in RnEnv.warnUnusedBinds)
957 instance Eq Provenance where
958   p1 == p2 = case p1 `compare` p2 of EQ -> True; _ -> False
959
960 instance Eq ImportReason where
961   p1 == p2 = case p1 `compare` p2 of EQ -> True; _ -> False
962
963 instance Ord Provenance where
964    compare LocalDef LocalDef = EQ
965    compare LocalDef (NonLocalDef _) = LT
966    compare (NonLocalDef _) LocalDef = GT
967
968    compare (NonLocalDef reason1) (NonLocalDef reason2) 
969       = compare reason1 reason2
970
971 instance Ord ImportReason where
972    compare ImplicitImport ImplicitImport = EQ
973    compare ImplicitImport (UserImport _ _ _) = LT
974    compare (UserImport _ _ _) ImplicitImport = GT
975    compare (UserImport m1 loc1 _) (UserImport m2 loc2 _) 
976       = (m1 `compare` m2) `thenCmp` (loc1 `compare` loc2)
977
978
979 data ImportReason
980   = UserImport Module SrcLoc Bool       -- Imported from module M on line L
981                                         -- Note the M may well not be the defining module
982                                         -- for this thing!
983         -- The Bool is true iff the thing was named *explicitly* in the import spec,
984         -- rather than being imported as part of a group; e.g.
985         --      import B
986         --      import C( T(..) )
987         -- Here, everything imported by B, and the constructors of T
988         -- are not named explicitly; only T is named explicitly.
989         -- This info is used when warning of unused names.
990
991   | ImplicitImport                      -- Imported implicitly for some other reason
992 \end{code}
993
994 \begin{code}
995 hasBetterProv :: Provenance -> Provenance -> Bool
996 -- Choose 
997 --      a local thing                 over an   imported thing
998 --      a user-imported thing         over a    non-user-imported thing
999 --      an explicitly-imported thing  over an   implicitly imported thing
1000 hasBetterProv LocalDef                            _                            = True
1001 hasBetterProv (NonLocalDef (UserImport _ _ _   )) (NonLocalDef ImplicitImport) = True
1002 hasBetterProv _                                   _                            = False
1003
1004 pprNameProvenance :: GlobalRdrElt -> SDoc
1005 pprNameProvenance (GRE {gre_name = name, gre_prov = prov})
1006   = case prov of
1007         LocalDef        -> ptext SLIT("defined at") <+> ppr (nameSrcLoc name)
1008         NonLocalDef why ->  sep [ppr_reason why, 
1009                                  nest 2 (ppr_defn (nameSrcLoc name))]
1010
1011 ppr_reason ImplicitImport         = ptext SLIT("implicitly imported")
1012 ppr_reason (UserImport mod loc _) = ptext SLIT("imported from") <+> ppr mod <+> ptext SLIT("at") <+> ppr loc
1013
1014 ppr_defn loc | isGoodSrcLoc loc = parens (ptext SLIT("defined at") <+> ppr loc)
1015              | otherwise        = empty
1016 \end{code}