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