[project @ 2000-10-12 16:41:48 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 where
9
10 #include "HsVersions.h"
11
12 import Name             ( Name, NameEnv )
13 import Module           ( Module, ModuleName )
14 import Class            ( Class )
15 import OccName          ( OccName )
16 import RdrName          ( RdrNameEnv )
17 import Outputable       ( SDoc )
18 import UniqFM           ( UniqFM )
19 import FiniteMap        ( FiniteMap )
20 import Bag              ( Bag )
21 import Id               ( Id )
22 import VarEnv           ( IdEnv )
23 import BasicTypes       ( Version, Fixity )
24 import TyCon            ( TyCon )
25 import ErrUtils         ( ErrMsg, WarnMsg )
26 import CmLink           ( Linkable )
27 import RdrHsSyn         ( RdrNameInstDecl, RdrNameRuleDecl, RdrNameHsDecl,
28                           RdrNameDeprecation, RdrNameFixitySig )
29 import UniqSupply       ( UniqSupply )
30 import HsDecls          ( DeprecTxt )
31 import CoreSyn          ( CoreRule )
32 import RnMonad          ( ImportVersion, ExportItem, WhetherHasOrphans )
33 import NameSet          ( NameSet )
34
35 \end{code}
36
37 %************************************************************************
38 %*                                                                      *
39 \subsection{Symbol tables and Module details}
40 %*                                                                      *
41 %************************************************************************
42
43 A @ModDetails@ summarises everything we know about a compiled module.
44
45 \begin{code}
46 data ModDetails
47    = ModDetails {
48         moduleId      :: Module,
49         moduleExports :: Avails,                -- What it exports
50         moduleEnv     :: GlobalRdrEnv,          -- Its top level environment
51
52         fixityEnv     :: NameEnv Fixity,
53         deprecEnv     :: NameEnv DeprecTxt,
54         typeEnv       :: TypeEnv,
55
56         instEnv       :: InstEnv,
57         ruleEnv       :: RuleEnv                -- Domain may include Id from other modules
58      }
59
60 emptyModDetails :: Module -> ModuleDetails
61 emptyModDetails mod
62   = ModDetails { moduleId      = mod,
63                  moduleExports = [],
64                  moduleEnv     = emptyRdrEnv,
65                  fixityEnv     = emptyNameEnv,
66                  deprecEnv     = emptyNameEnv,
67                  typeEnv       = emptyNameEnv,
68                  instEnv       = emptyInstEnv,
69                  ruleEnv       = emptyRuleEnv
70     }           
71 \end{code}
72
73 Symbol tables map modules to ModDetails:
74
75 \begin{code}
76 type SymbolTable        = ModuleEnv ModDetails
77 type HomeSymbolTable    = SymbolTable   -- Domain = modules in the home package
78 type PackageSymbolTable = SymbolTable   -- Domain = modules in the some other package
79 type GlobalSymbolTable  = SymbolTable   -- Domain = all modules
80 \end{code}
81
82 Simple lookups in the symbol table.
83
84 \begin{code}
85 lookupFixityEnv :: SymbolTable -> Name -> Fixity
86         -- Returns defaultFixity if there isn't an explicit fixity
87 lookupFixityEnv tbl name
88   = case lookupModuleEnv tbl (nameModule name) of
89         Nothing      -> defaultFixity
90         Just details -> case lookupNameEnv (fixityEnv details) name of
91                                 Just fixity -> fixity
92                                 Nothing     -> defaultFixity
93 \end{code}
94
95
96 %************************************************************************
97 %*                                                                      *
98 \subsection{Type environment stuff}
99 %*                                                                      *
100 %************************************************************************
101
102 \begin{code}
103 type TypeEnv = NameEnv TyThing
104
105 data TyThing = AnId   Id
106              | ATyCon TyCon
107              | AClass Class
108
109 instance NamedThing TyThing where
110   getName (AnId id)   = getName id
111   getName (ATyCon tc) = getName tc
112   getName (AClass cl) = getName cl
113 \end{code}
114
115
116 \begin{code}
117 lookupTypeEnv :: SymbolTable -> Name -> Maybe TyThing
118 lookupTypeEnv tbl name
119   = case lookupModuleEnv tbl (nameModule name) of
120         Just details -> lookupNameEnv (typeEnv details) name
121         Nothing      -> Nothing
122
123
124 groupTyThings :: [TyThing] -> FiniteMap Module TypeEnv
125   -- Finite map because we want the range too
126 groupTyThings things
127   = foldl add emptyFM things
128   where
129     add :: FiniteMap Module TypeEnv -> TyThing -> FiniteMap Module TypeEnv
130     add tbl thing = addToFM tbl mod new_env
131                   where
132                     name    = getName thing
133                     mod     = nameModule name
134                     new_env = case lookupFM tbl mod of
135                                 Nothing  -> unitNameEnv name thing
136                                 Just env -> extendNameEnv env name thing
137                 
138 extendTypeEnv :: SymbolTable -> FiniteMap Module TypeEnv -> SymbolTable
139 extendTypeEnv tbl things
140   = foldFM add tbl things
141   where
142     add mod type_env tbl
143         = extendModuleEnv mod new_details
144         where
145           new_details = case lookupModuleEnv tbl mod of
146                             Nothing      -> emptyModDetails mod {typeEnv = type_env}
147                             Just details -> details {typeEnv = typeEnv details `plusNameEnv` type_env})
148 \end{code}
149
150
151 %************************************************************************
152 %*                                                                      *
153 \subsection{Auxiliary types}
154 %*                                                                      *
155 %************************************************************************
156
157 These types are defined here because they are mentioned in ModDetails,
158 but they are mostly elaborated elsewhere
159
160 \begin{code}
161 type DeprecationEnv = NameEnv DeprecTxt         -- Give reason for deprecation
162
163 type GlobalRdrEnv = RdrNameEnv [Name]   -- The list is because there may be name clashes
164                                         -- These only get reported on lookup,
165                                         -- not on construction
166
167 type InstEnv    = UniqFM ClsInstEnv             -- Maps Class to instances for that class
168 type ClsInstEnv = [(TyVarSet, [Type], Id)]      -- The instances for a particular class
169
170 type RuleEnv    = IdEnv [CoreRule]
171 \end{code}
172
173
174 \begin{code}
175 type Avails       = [AvailInfo]
176 type AvailInfo    = GenAvailInfo Name
177 type RdrAvailInfo = GenAvailInfo OccName
178
179 data GenAvailInfo name  = Avail name     -- An ordinary identifier
180                         | AvailTC name   -- The name of the type or class
181                                   [name] -- The available pieces of type/class.
182                                          -- NB: If the type or class is itself
183                                          -- to be in scope, it must be in this list.
184                                          -- Thus, typically: AvailTC Eq [Eq, ==, /=]
185                         deriving( Eq )
186                         -- Equality used when deciding if the interface has changed
187
188 type AvailEnv     = NameEnv AvailInfo   -- Maps a Name to the AvailInfo that contains it
189 \end{code}
190
191
192 %************************************************************************
193 %*                                                                      *
194 \subsection{ModIface}
195 %*                                                                      *
196 %************************************************************************
197
198 \begin{code}
199 -- ModIFace is nearly the same as RnMonad.ParsedIface.
200 -- Right now it's identical :)
201 data ModIFace 
202    = ModIFace {
203         mi_mod       :: Module,                   -- Complete with package info
204         mi_vers      :: Version,                  -- Module version number
205         mi_orphan    :: WhetherHasOrphans,        -- Whether this module has orphans
206         mi_usages    :: [ImportVersion OccName],  -- Usages
207         mi_exports   :: [ExportItem],             -- Exports
208         mi_insts     :: [RdrNameInstDecl],        -- Local instance declarations
209         mi_decls     :: [(Version, RdrNameHsDecl)],    -- Local definitions
210         mi_fixity    :: (Version, [RdrNameFixitySig]), -- Local fixity declarations, 
211                                                        -- with their version
212         mi_rules     :: (Version, [RdrNameRuleDecl]),  -- Rules, with their version
213         mi_deprecs   :: [RdrNameDeprecation]           -- Deprecations
214      }
215 \end{code}
216
217
218 %************************************************************************
219 %*                                                                      *
220 \subsection{The persistent compiler state}
221 %*                                                                      *
222 %************************************************************************
223
224 \begin{code}
225 data PersistentCompilerState 
226    = PCS {
227         pcsPST :: PackageSymbolTable,           -- Domain = non-home-package modules
228                                                 --   except that the InstEnv components is empty
229         pcsInsts :: InstEnv                     -- The total InstEnv accumulated from all
230                                                 --   the non-home-package modules
231         pcsRules :: RuleEnv                     -- Ditto RuleEnv
232
233         pcsPRS :: PersistentRenamerState
234      }
235 \end{code}
236
237 The @PersistentRenamerState@ persists across successive calls to the
238 compiler.
239
240 It contains:
241   * A name supply, which deals with allocating unique names to
242     (Module,OccName) original names, 
243  
244   * An accumulated InstEnv from all the modules in pcsPST
245     The point is that we don't want to keep recreating it whenever
246     we compile a new module.  The InstEnv component of pcPST is empty.
247     (This means we might "see" instances that we shouldn't "really" see;
248     but the Haskell Report is vague on what is meant to be visible, 
249     so we just take the easy road here.)
250
251   * Ditto for rules
252
253   * A "holding pen" for declarations that have been read out of
254     interface files but not yet sucked in, renamed, and typechecked
255
256 \begin{code}
257 data PersistentRenamerState
258   = PRS { prsOrig  :: OrigNameEnv,
259           prsDecls :: DeclsMap,
260           prsInsts :: IfaceInsts,
261           prsRules :: IfaceRules
262     }
263
264 <<<<<<< HscTypes.lhs
265 data NameSupply
266  = NS { nsUniqs  :: UniqSupply,
267         nsNames  :: FiniteMap (Module,OccName) Name,    -- Ensures that one original name gets one unique
268         nsIParam :: FiniteMap OccName Name              -- Ensures that one implicit parameter name gets one unique
269 =======
270 data OrigNameEnv
271  = Orig { origNames  :: FiniteMap (Module,OccName) Name -- Ensures that one original name gets one unique
272           origIParam :: FiniteMap OccName Name          -- Ensures that one implicit parameter name gets one unique
273 >>>>>>> 1.6
274    }
275
276 type DeclsMap = NameEnv (Version, AvailInfo, Bool, (Module, RdrNameHsDecl))
277                 -- A DeclsMap contains a binding for each Name in the declaration
278                 -- including the constructors of a type decl etc.
279                 -- The Bool is True just for the 'main' Name.
280
281 type IfaceInsts = Bag GatedDecl
282 type IfaceRules = Bag GatedDecl
283
284 type GatedDecl = (NameSet, (Module, RdrNameHsDecl))
285 \end{code}
286
287
288 %************************************************************************
289 %*                                                                      *
290 \subsection{The result of compiling one module}
291 %*                                                                      *
292 %************************************************************************
293
294 \begin{code}
295 data CompResult
296    = CompOK   ModDetails  -- new details (HST additions)
297               (Maybe (ModIFace, Linkable))
298                        -- summary and code; Nothing => compilation not reqd
299                        -- (old summary and code are still valid)
300               PersistentCompilerState   -- updated PCS
301               (Bag WarnMsg)             -- warnings
302
303    | CompErrs PersistentCompilerState   -- updated PCS
304               (Bag ErrMsg)              -- errors
305               (Bag WarnMsg)             -- warnings
306
307
308 -- The driver sits between 'compile' and 'hscMain', translating calls
309 -- to the former into calls to the latter, and results from the latter
310 -- into results from the former.  It does things like preprocessing
311 -- the .hs file if necessary, and compiling up the .stub_c files to
312 -- generate Linkables.
313
314 data HscResult
315    = HscOK   ModDetails                 -- new details (HomeSymbolTable additions)
316              Maybe ModIFace             -- new iface (if any compilation was done)
317              Maybe String               -- generated stub_h
318              Maybe String               -- generated stub_c
319              PersistentCompilerState    -- updated PCS
320              [SDoc]                     -- warnings
321
322    | HscErrs PersistentCompilerState    -- updated PCS
323              [SDoc]                     -- errors
324              [SDoc]                     -- warnings
325
326         
327 -- These two are only here to avoid recursion between CmCompile and
328 -- CompManager.  They really ought to be in the latter.
329 type ModuleEnv a = UniqFM a   -- Domain is Module
330
331 type HomeModMap         = FiniteMap ModuleName Module -- domain: home mods only
332 type HomeInterfaceTable = ModuleEnv ModIFace
333 \end{code}
334
335