[project @ 2000-10-17 10:27:58 by sewardj]
[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         ModDetails(..), GlobalSymbolTable, 
9         HomeSymbolTable, PackageSymbolTable,
10
11         TyThing(..), lookupTypeEnv,
12
13         WhetherHasOrphans, ImportVersion, ExportItem,
14         PersistentRenamerState(..), IsBootInterface, Avails, DeclsMap,
15         IfaceInsts, IfaceRules, DeprecationEnv, OrigNameEnv, 
16         AvailEnv, AvailInfo, GenAvailInfo(..),
17         PersistentCompilerState(..),
18
19         InstEnv, ClsInstEnv, DFunId,
20
21         GlobalRdrEnv, RdrAvailInfo,
22
23         -- Provenance
24         Provenance(..), ImportReason(..), PrintUnqualified,
25         pprNameProvenance, hasBetterProv
26
27     ) where
28
29 #include "HsVersions.h"
30
31 import Name             ( Name, NameEnv, NamedThing,
32                           unitNameEnv, extendNameEnv, plusNameEnv, 
33                           lookupNameEnv, emptyNameEnv, getName, nameModule,
34                           nameSrcLoc )
35 import Module           ( Module, ModuleName,
36                           extendModuleEnv, lookupModuleEnv )
37 import Class            ( Class )
38 import OccName          ( OccName )
39 import RdrName          ( RdrNameEnv, emptyRdrEnv )
40 import Outputable       ( SDoc )
41 import UniqFM           ( UniqFM )
42 import FiniteMap        ( FiniteMap, emptyFM, addToFM, lookupFM, foldFM )
43 import Bag              ( Bag )
44 import Id               ( Id )
45 import VarEnv           ( IdEnv, emptyVarEnv )
46 import BasicTypes       ( Version, Fixity, defaultFixity )
47 import TyCon            ( TyCon )
48 import ErrUtils         ( ErrMsg, WarnMsg )
49 import CmLink           ( Linkable )
50 import RdrHsSyn         ( RdrNameInstDecl, RdrNameRuleDecl, RdrNameHsDecl,
51                           RdrNameDeprecation, RdrNameFixitySig )
52 import UniqSupply       ( UniqSupply )
53 import HsDecls          ( DeprecTxt )
54 import CoreSyn          ( CoreRule )
55 import NameSet          ( NameSet )
56 import Type             ( Type )
57 import VarSet           ( TyVarSet )
58 import Panic            ( panic )
59 import Outputable
60 import SrcLoc           ( SrcLoc, isGoodSrcLoc )
61 \end{code}
62
63 %************************************************************************
64 %*                                                                      *
65 \subsection{Symbol tables and Module details}
66 %*                                                                      *
67 %************************************************************************
68
69 A @ModIface@ plus a @ModDetails@ summarises everything we know 
70 about a compiled module.  The @ModIface@ is the stuff *before* linking,
71 and can be written out to an interface file.  The @ModDetails@ is after
72 linking; it is the "linked" form of the mi_decls field.
73
74 \begin{code}
75 data ModDetails
76    = ModDetails {
77         md_module   :: Module,                  -- Complete with package info
78         md_version  :: VersionInfo,             -- Module version number
79         md_orphan   :: WhetherHasOrphans,       -- Whether this module has orphans
80         md_usages   :: [ImportVersion Name],    -- Usages
81
82         md_exports  :: Avails,                  -- What it exports
83         md_globals  :: GlobalRdrEnv,            -- Its top level environment
84
85         md_fixities :: NameEnv Fixity,          -- Fixities
86         md_deprecs  :: NameEnv DeprecTxt,       -- Deprecations
87
88         -- The next three fields are created by the typechecker
89         md_types    :: TypeEnv,
90         md_insts    :: [DFunId],        -- Dfun-ids for the instances in this module
91         md_rules    :: RuleEnv          -- Domain may include Ids from other modules
92      }
93
94 -- ModIFace is nearly the same as RnMonad.ParsedIface.
95 -- Right now it's identical :)
96 data ModIFace 
97    = ModIFace {
98         mi_mod       :: Module,                   -- Complete with package info
99         mi_vers      :: Version,                  -- Module version number
100         mi_orphan    :: WhetherHasOrphans,        -- Whether this module has orphans
101         mi_usages    :: [ImportVersion OccName],  -- Usages
102         mi_exports   :: [ExportItem],             -- Exports
103         mi_insts     :: [RdrNameInstDecl],        -- Local instance declarations
104         mi_decls     :: [(Version, RdrNameHsDecl)],    -- Local definitions
105         mi_fixity    :: (Version, [RdrNameFixitySig]), -- Local fixity declarations, 
106                                                        -- with their version
107         mi_rules     :: (Version, [RdrNameRuleDecl]),  -- Rules, with their version
108         mi_deprecs   :: [RdrNameDeprecation]           -- Deprecations
109      }
110
111 \end{code}
112
113 \begin{code}
114 emptyModDetails :: Module -> ModDetails
115 emptyModDetails mod
116   = ModDetails { md_module   = mod,
117                  md_exports  = [],
118                  md_globals  = emptyRdrEnv,
119                  md_fixities = emptyNameEnv,
120                  md_deprecs  = emptyNameEnv,
121                  md_types    = emptyNameEnv,
122                  md_insts    = [],
123                  md_rules    = emptyRuleEnv
124     }           
125 \end{code}
126
127 Symbol tables map modules to ModDetails:
128
129 \begin{code}
130 type SymbolTable        = ModuleEnv ModDetails
131 type HomeSymbolTable    = SymbolTable   -- Domain = modules in the home package
132 type PackageSymbolTable = SymbolTable   -- Domain = modules in the some other package
133 type GlobalSymbolTable  = SymbolTable   -- Domain = all modules
134 \end{code}
135
136 Simple lookups in the symbol table.
137
138 \begin{code}
139 lookupFixityEnv :: SymbolTable -> Name -> Maybe Fixity
140         -- Returns defaultFixity if there isn't an explicit fixity
141 lookupFixityEnv tbl name
142   = case lookupModuleEnv tbl (nameModule name) of
143         Nothing      -> Nothing
144         Just details -> lookupNameEnv (md_fixities details) name
145 \end{code}
146
147
148 %************************************************************************
149 %*                                                                      *
150 \subsection{Type environment stuff}
151 %*                                                                      *
152 %************************************************************************
153
154 \begin{code}
155 type TypeEnv = NameEnv TyThing
156
157 data TyThing = AnId   Id
158              | ATyCon TyCon
159              | AClass Class
160
161 instance NamedThing TyThing where
162   getName (AnId id)   = getName id
163   getName (ATyCon tc) = getName tc
164   getName (AClass cl) = getName cl
165 \end{code}
166
167
168 \begin{code}
169 lookupTypeEnv :: SymbolTable -> Name -> Maybe TyThing
170 lookupTypeEnv tbl name
171   = case lookupModuleEnv tbl (nameModule name) of
172         Just details -> lookupNameEnv (md_types details) name
173         Nothing      -> Nothing
174
175
176 groupTyThings :: [TyThing] -> FiniteMap Module TypeEnv
177   -- Finite map because we want the range too
178 groupTyThings things
179   = foldl add emptyFM things
180   where
181     add :: FiniteMap Module TypeEnv -> TyThing -> FiniteMap Module TypeEnv
182     add tbl thing = addToFM tbl mod new_env
183                   where
184                     name    = getName thing
185                     mod     = nameModule name
186                     new_env = case lookupFM tbl mod of
187                                 Nothing  -> unitNameEnv name thing
188                                 Just env -> extendNameEnv env name thing
189                 
190 extendTypeEnv :: SymbolTable -> FiniteMap Module TypeEnv -> SymbolTable
191 extendTypeEnv tbl things
192   = foldFM add tbl things
193   where
194     add mod type_env tbl
195         = panic "extendTypeEnv" --extendModuleEnv mod new_details
196         where
197           new_details 
198              = case lookupModuleEnv tbl mod of
199                   Nothing      -> (emptyModDetails mod) {md_types = type_env}
200                   Just details -> details {md_types = md_types details 
201                                                      `plusNameEnv` type_env}
202 \end{code}
203
204
205 %************************************************************************
206 %*                                                                      *
207 \subsection{Auxiliary types}
208 %*                                                                      *
209 %************************************************************************
210
211 These types are defined here because they are mentioned in ModDetails,
212 but they are mostly elaborated elsewhere
213
214 \begin{code}
215 data VersionInfo 
216   = VersionInfo {
217         modVers  :: Version,
218         fixVers  :: Version,
219         ruleVers :: Version,
220         declVers :: NameEnv Version
221     }
222
223 type DeprecationEnv = NameEnv DeprecTxt         -- Give reason for deprecation
224
225 type InstEnv    = UniqFM ClsInstEnv             -- Maps Class to instances for that class
226 type ClsInstEnv = [(TyVarSet, [Type], DFunId)]  -- The instances for a particular class
227 type DFunId     = Id
228
229 type RuleEnv    = IdEnv [CoreRule]
230
231 emptyRuleEnv    = emptyVarEnv
232 \end{code}
233
234
235 \begin{code}
236 type Avails       = [AvailInfo]
237 type AvailInfo    = GenAvailInfo Name
238 type RdrAvailInfo = GenAvailInfo OccName
239
240 data GenAvailInfo name  = Avail name     -- An ordinary identifier
241                         | AvailTC name   -- The name of the type or class
242                                   [name] -- The available pieces of type/class.
243                                          -- NB: If the type or class is itself
244                                          -- to be in scope, it must be in this list.
245                                          -- Thus, typically: AvailTC Eq [Eq, ==, /=]
246                         deriving( Eq )
247                         -- Equality used when deciding if the interface has changed
248
249 type AvailEnv     = NameEnv AvailInfo   -- Maps a Name to the AvailInfo that contains it
250 \end{code}
251
252
253 %************************************************************************
254 %*                                                                      *
255 \subsection{ModIface}
256 %*                                                                      *
257 %************************************************************************
258
259 \begin{code}
260 type ExportItem          = (ModuleName, [RdrAvailInfo])
261
262 type ImportVersion name  = (ModuleName, WhetherHasOrphans, IsBootInterface, WhatsImported name)
263
264 type ModVersionInfo     = (Version,             -- Version of the whole module
265                            Version,             -- Version number for all fixity decls together
266                            Version)             -- ...ditto all rules together
267
268 type WhetherHasOrphans   = Bool
269         -- An "orphan" is 
270         --      * an instance decl in a module other than the defn module for 
271         --              one of the tycons or classes in the instance head
272         --      * a transformation rule in a module other than the one defining
273         --              the function in the head of the rule.
274
275 type IsBootInterface     = Bool
276
277 data WhatsImported name  = NothingAtAll                         -- The module is below us in the
278                                                                 -- hierarchy, but we import nothing
279
280                          | Everything Version                   -- The module version
281
282                          | Specifically Version                 -- Module version
283                                         Version                 -- Fixity version
284                                         Version                 -- Rules version
285                                         [(name,Version)]        -- List guaranteed non-empty
286                          deriving( Eq )
287         -- 'Specifically' doesn't let you say "I imported f but none of the fixities in
288         -- the module". If you use anything in the module you get its fixity and rule version
289         -- So if the fixities or rules change, you'll recompile, even if you don't use either.
290         -- This is easy to implement, and it's safer: you might not have used the rules last
291         -- time round, but if someone has added a new rule you might need it this time
292
293         -- 'Everything' means there was a "module M" in 
294         -- this module's export list, so we just have to go by M's version,
295         -- not the list of (name,version) pairs
296 \end{code}
297
298
299 %************************************************************************
300 %*                                                                      *
301 \subsection{The persistent compiler state}
302 %*                                                                      *
303 %************************************************************************
304
305 \begin{code}
306 data PersistentCompilerState 
307    = PCS {
308         pcs_PST :: PackageSymbolTable,  -- Domain = non-home-package modules
309                                         --   except that the InstEnv components is empty
310         pcs_insts :: InstEnv,           -- The total InstEnv accumulated from all
311                                         --   the non-home-package modules
312         pcs_rules :: RuleEnv,           -- Ditto RuleEnv
313
314         pcs_PRS :: PersistentRenamerState
315      }
316 \end{code}
317
318 The @PersistentRenamerState@ persists across successive calls to the
319 compiler.
320
321 It contains:
322   * A name supply, which deals with allocating unique names to
323     (Module,OccName) original names, 
324  
325   * An accumulated InstEnv from all the modules in pcs_PST
326     The point is that we don't want to keep recreating it whenever
327     we compile a new module.  The InstEnv component of pcPST is empty.
328     (This means we might "see" instances that we shouldn't "really" see;
329     but the Haskell Report is vague on what is meant to be visible, 
330     so we just take the easy road here.)
331
332   * Ditto for rules
333
334   * A "holding pen" for declarations that have been read out of
335     interface files but not yet sucked in, renamed, and typechecked
336
337 \begin{code}
338 data PersistentRenamerState
339   = PRS { prsOrig  :: OrigNameEnv,
340           prsDecls :: DeclsMap,
341           prsInsts :: IfaceInsts,
342           prsRules :: IfaceRules
343     }
344 \end{code}
345
346 The OrigNameEnv makes sure that there is just one Unique assigned for
347 each original name; i.e. (module-name, occ-name) pair.  The Name is
348 always stored as a Global, and has the SrcLoc of its binding location.
349 Actually that's not quite right.  When we first encounter the original
350 name, we might not be at its binding site (e.g. we are reading an
351 interface file); so we give it 'noSrcLoc' then.  Later, when we find
352 its binding site, we fix it up.
353
354 Exactly the same is true of the Module stored in the Name.  When we first
355 encounter the occurrence, we may not know the details of the module, so
356 we just store junk.  Then when we find the binding site, we fix it up.
357
358 \begin{code}
359 data OrigNameEnv
360  = Orig { origNames  :: FiniteMap (ModuleName,OccName) Name,    -- Ensures that one original name gets one unique
361           origIParam :: FiniteMap OccName Name                  -- Ensures that one implicit parameter name gets one unique
362    }
363 \end{code}
364
365
366 A DeclsMap contains a binding for each Name in the declaration
367 including the constructors of a type decl etc.  The Bool is True just
368 for the 'main' Name.
369
370 \begin{code}
371 type DeclsMap = NameEnv (AvailInfo, Bool, (Module, RdrNameHsDecl))
372
373 type IfaceInsts = Bag GatedDecl
374 type IfaceRules = Bag GatedDecl
375
376 type GatedDecl = (NameSet, (Module, RdrNameHsDecl))
377 \end{code}
378
379
380 %************************************************************************
381 %*                                                                      *
382 \subsection{The result of compiling one module}
383 %*                                                                      *
384 %************************************************************************
385
386 \begin{code}
387 data CompResult
388    = CompOK   ModDetails  -- new details (HST additions)
389               (Maybe (ModIFace, Linkable))
390                        -- summary and code; Nothing => compilation not reqd
391                        -- (old summary and code are still valid)
392               PersistentCompilerState   -- updated PCS
393               (Bag WarnMsg)             -- warnings
394
395    | CompErrs PersistentCompilerState   -- updated PCS
396               (Bag ErrMsg)              -- errors
397               (Bag WarnMsg)             -- warnings
398
399
400 -- The driver sits between 'compile' and 'hscMain', translating calls
401 -- to the former into calls to the latter, and results from the latter
402 -- into results from the former.  It does things like preprocessing
403 -- the .hs file if necessary, and compiling up the .stub_c files to
404 -- generate Linkables.
405
406 data HscResult
407    = HscOK   ModDetails              -- new details (HomeSymbolTable additions)
408              (Maybe ModIFace)        -- new iface (if any compilation was done)
409              (Maybe String)          -- generated stub_h filename (in /tmp)
410              (Maybe String)          -- generated stub_c filename (in /tmp)
411              PersistentCompilerState -- updated PCS
412              [SDoc]                  -- warnings
413
414    | HscErrs PersistentCompilerState -- updated PCS
415              [SDoc]                  -- errors
416              [SDoc]                  -- warnings
417
418         
419 -- These two are only here to avoid recursion between CmCompile and
420 -- CompManager.  They really ought to be in the latter.
421 type ModuleEnv a = UniqFM a   -- Domain is Module
422
423 type HomeModMap         = FiniteMap ModuleName Module -- domain: home mods only
424 type HomeInterfaceTable = ModuleEnv ModIFace
425 \end{code}
426
427
428 %************************************************************************
429 %*                                                                      *
430 \subsection{Provenance and export info}
431 %*                                                                      *
432 %************************************************************************
433
434 The GlobalRdrEnv gives maps RdrNames to Names.  There is a separate
435 one for each module, corresponding to that module's top-level scope.
436
437 \begin{code}
438 type GlobalRdrEnv = RdrNameEnv [(Name,Provenance)]      -- The list is because there may be name clashes
439                                                         -- These only get reported on lookup,
440                                                         -- not on construction
441 \end{code}
442
443 The "provenance" of something says how it came to be in scope.
444
445 \begin{code}
446 data Provenance
447   = LocalDef                    -- Defined locally
448
449   | NonLocalDef                 -- Defined non-locally
450         ImportReason
451         PrintUnqualified
452
453 {-
454 Moved here from Name.
455 pp_prov (LocalDef _ Exported)          = char 'x'
456 pp_prov (LocalDef _ NotExported)       = char 'l'
457 pp_prov (NonLocalDef ImplicitImport _) = char 'j'
458 pp_prov (NonLocalDef (UserImport _ _ True ) _) = char 'I'       -- Imported by name
459 pp_prov (NonLocalDef (UserImport _ _ False) _) = char 'i'       -- Imported by ..
460 pp_prov SystemProv                     = char 's'
461 -}
462
463 data ImportReason
464   = UserImport Module SrcLoc Bool       -- Imported from module M on line L
465                                         -- Note the M may well not be the defining module
466                                         -- for this thing!
467         -- The Bool is true iff the thing was named *explicitly* in the import spec,
468         -- rather than being imported as part of a group; e.g.
469         --      import B
470         --      import C( T(..) )
471         -- Here, everything imported by B, and the constructors of T
472         -- are not named explicitly; only T is named explicitly.
473         -- This info is used when warning of unused names.
474
475   | ImplicitImport                      -- Imported implicitly for some other reason
476                         
477
478 type PrintUnqualified = Bool    -- True <=> the unqualified name of this thing is
479                                 -- in scope in this module, so print it 
480                                 -- unqualified in error messages
481 \end{code}
482
483 \begin{code}
484 hasBetterProv :: Provenance -> Provenance -> Bool
485 -- Choose 
486 --      a local thing                 over an   imported thing
487 --      a user-imported thing         over a    non-user-imported thing
488 --      an explicitly-imported thing  over an   implicitly imported thing
489 hasBetterProv LocalDef                              _                              = True
490 hasBetterProv (NonLocalDef (UserImport _ _ True) _) _                              = True
491 hasBetterProv (NonLocalDef (UserImport _ _ _   ) _) (NonLocalDef ImplicitImport _) = True
492 hasBetterProv _                                     _                              = False
493
494 pprNameProvenance :: Name -> Provenance -> SDoc
495 pprNameProvenance name LocalDef                = ptext SLIT("defined at") <+> ppr (nameSrcLoc name)
496 pprNameProvenance name (NonLocalDef why _) = sep [ppr_reason why, 
497                                               nest 2 (parens (ppr_defn (nameSrcLoc name)))]
498
499 ppr_reason ImplicitImport         = ptext SLIT("implicitly imported")
500 ppr_reason (UserImport mod loc _) = ptext SLIT("imported from") <+> ppr mod <+> ptext SLIT("at") <+> ppr loc
501
502 ppr_defn loc | isGoodSrcLoc loc = ptext SLIT("at") <+> ppr loc
503              | otherwise        = empty
504 \end{code}