[project @ 2000-10-12 16:26:41 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 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                  deptecEnv     = 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] -> [(Module, TypeEnv)]
125 groupTyThings things
126   = fmToList (foldl add emptyFM things)
127   where
128     add :: FiniteMap Module TypeEnv -> TyThing -> FiniteMap Module TypeEnv
129     add tbl thing = addToFM tbl mod new_env
130                   where
131                     name    = getName thing
132                     mod     = nameModule name
133                     new_env = case lookupFM tbl mod of
134                                 Nothing  -> unitNameEnv name thing
135                                 Just env -> extendNameEnv env name thing
136                 
137 extendTypeEnv :: SymbolTable -> [TyThing] -> SymbolTable
138 extendTypeEnv tbl things
139   = foldl add tbl (groupTyThings things)
140   where
141     add tbl (mod,type_env)
142         = extendModuleEnv mod new_details
143         where
144           new_details = case lookupModuleEnv tbl mod of
145                             Nothing      -> emptyModDetails mod {typeEnv = type_env}
146                             Just details -> details {typeEnv = typeEnv details `plusNameEnv` type_env})
147 \end{code}
148
149
150 %************************************************************************
151 %*                                                                      *
152 \subsection{Auxiliary types}
153 %*                                                                      *
154 %************************************************************************
155
156 These types are defined here because they are mentioned in ModDetails,
157 but they are mostly elaborated elsewhere
158
159 \begin{code}
160 type DeprecationEnv = NameEnv DeprecTxt         -- Give reason for deprecation
161
162 type GlobalRdrEnv = RdrNameEnv [Name]   -- The list is because there may be name clashes
163                                         -- These only get reported on lookup,
164                                         -- not on construction
165
166 type InstEnv    = UniqFM ClsInstEnv             -- Maps Class to instances for that class
167 type ClsInstEnv = [(TyVarSet, [Type], Id)]      -- The instances for a particular class
168
169 type RuleEnv    = IdEnv [CoreRule]
170 \end{code}
171
172
173 \begin{code}
174 type Avails       = [AvailInfo]
175 type AvailInfo    = GenAvailInfo Name
176 type RdrAvailInfo = GenAvailInfo OccName
177
178 data GenAvailInfo name  = Avail name     -- An ordinary identifier
179                         | AvailTC name   -- The name of the type or class
180                                   [name] -- The available pieces of type/class.
181                                          -- NB: If the type or class is itself
182                                          -- to be in scope, it must be in this list.
183                                          -- Thus, typically: AvailTC Eq [Eq, ==, /=]
184                         deriving( Eq )
185                         -- Equality used when deciding if the interface has changed
186
187 type AvailEnv     = NameEnv AvailInfo   -- Maps a Name to the AvailInfo that contains it
188 \end{code}
189
190
191 %************************************************************************
192 %*                                                                      *
193 \subsection{ModIface}
194 %*                                                                      *
195 %************************************************************************
196
197 \begin{code}
198 -- ModIFace is nearly the same as RnMonad.ParsedIface.
199 -- Right now it's identical :)
200 data ModIFace 
201    = ModIFace {
202         mi_mod       :: Module,                   -- Complete with package info
203         mi_vers      :: Version,                  -- Module version number
204         mi_orphan    :: WhetherHasOrphans,        -- Whether this module has orphans
205         mi_usages    :: [ImportVersion OccName],  -- Usages
206         mi_exports   :: [ExportItem],             -- Exports
207         mi_insts     :: [RdrNameInstDecl],        -- Local instance declarations
208         mi_decls     :: [(Version, RdrNameHsDecl)],    -- Local definitions
209         mi_fixity    :: (Version, [RdrNameFixitySig]), -- Local fixity declarations, 
210                                                        -- with their version
211         mi_rules     :: (Version, [RdrNameRuleDecl]),  -- Rules, with their version
212         mi_deprecs   :: [RdrNameDeprecation]           -- Deprecations
213      }
214 \end{code}
215
216
217 %************************************************************************
218 %*                                                                      *
219 \subsection{The persistent compiler state}
220 %*                                                                      *
221 %************************************************************************
222
223 \begin{code}
224 data PersistentCompilerState 
225    = PCS {
226         pcsPST :: PackageSymbolTable,           -- Domain = non-home-package modules
227                                                 --   except that the InstEnv components is empty
228         pcsInsts :: InstEnv                     -- The total InstEnv accumulated from all
229                                                 --   the non-home-package modules
230         pcsRules :: RuleEnv                     -- Ditto RuleEnv
231
232         pcsPRS :: PersistentRenamerState
233      }
234 \end{code}
235
236 The @PersistentRenamerState@ persists across successive calls to the
237 compiler.
238
239 It contains:
240   * A name supply, which deals with allocating unique names to
241     (Module,OccName) original names, 
242  
243   * An accumulated InstEnv from all the modules in pcsPST
244     The point is that we don't want to keep recreating it whenever
245     we compile a new module.  The InstEnv component of pcPST is empty.
246     (This means we might "see" instances that we shouldn't "really" see;
247     but the Haskell Report is vague on what is meant to be visible, 
248     so we just take the easy road here.)
249
250   * Ditto for rules
251
252   * A "holding pen" for declarations that have been read out of
253     interface files but not yet sucked in, renamed, and typechecked
254
255 \begin{code}
256 data PersistentRenamerState
257   = PRS { prsOrig  :: OrigNameEnv,
258           prsDecls :: DeclsMap,
259           prsInsts :: IfaceInsts,
260           prsRules :: IfaceRules
261     }
262
263 <<<<<<< HscTypes.lhs
264 data NameSupply
265  = NS { nsUniqs  :: UniqSupply,
266         nsNames  :: FiniteMap (Module,OccName) Name,    -- Ensures that one original name gets one unique
267         nsIParam :: FiniteMap OccName Name              -- Ensures that one implicit parameter name gets one unique
268 =======
269 data OrigNameEnv
270  = Orig { origNames  :: FiniteMap (Module,OccName) Name -- Ensures that one original name gets one unique
271           origIParam :: FiniteMap OccName Name          -- Ensures that one implicit parameter name gets one unique
272 >>>>>>> 1.6
273    }
274
275 type DeclsMap = NameEnv (Version, AvailInfo, Bool, (Module, RdrNameHsDecl))
276                 -- A DeclsMap contains a binding for each Name in the declaration
277                 -- including the constructors of a type decl etc.
278                 -- The Bool is True just for the 'main' Name.
279
280 type IfaceInsts = Bag GatedDecl
281 type IfaceRules = Bag GatedDecl
282
283 type GatedDecl = (NameSet, (Module, RdrNameHsDecl))
284 \end{code}
285
286
287 %************************************************************************
288 %*                                                                      *
289 \subsection{The result of compiling one module}
290 %*                                                                      *
291 %************************************************************************
292
293 \begin{code}
294 data CompResult
295    = CompOK   ModDetails  -- new details (HST additions)
296               (Maybe (ModIFace, Linkable))
297                        -- summary and code; Nothing => compilation not reqd
298                        -- (old summary and code are still valid)
299               PersistentCompilerState   -- updated PCS
300               (Bag WarnMsg)             -- warnings
301
302    | CompErrs PersistentCompilerState   -- updated PCS
303               (Bag ErrMsg)              -- errors
304               (Bag WarnMsg)             -- warnings
305
306
307 -- The driver sits between 'compile' and 'hscMain', translating calls
308 -- to the former into calls to the latter, and results from the latter
309 -- into results from the former.  It does things like preprocessing
310 -- the .hs file if necessary, and compiling up the .stub_c files to
311 -- generate Linkables.
312
313 data HscResult
314    = HscOK   ModDetails                 -- new details (HomeSymbolTable additions)
315              Maybe ModIFace             -- new iface (if any compilation was done)
316              Maybe String               -- generated stub_h
317              Maybe String               -- generated stub_c
318              PersistentCompilerState    -- updated PCS
319              [SDoc]                     -- warnings
320
321    | HscErrs PersistentCompilerState    -- updated PCS
322              [SDoc]                     -- errors
323              [SDoc]                     -- warnings
324
325         
326 -- These two are only here to avoid recursion between CmCompile and
327 -- CompManager.  They really ought to be in the latter.
328 type ModuleEnv a = UniqFM a   -- Domain is Module
329
330 type HomeModMap         = FiniteMap ModuleName Module -- domain: home mods only
331 type HomeInterfaceTable = ModuleEnv ModIFace
332 \end{code}
333
334