[project @ 1997-03-14 07:52:06 by simonpj]
[ghc-hetmet.git] / ghc / compiler / rename / Rename.lhs
1 %
2 % (c) The GRASP Project, Glasgow University, 1992-1996
3 %
4 \section[Rename]{Renaming and dependency analysis passes}
5
6 \begin{code}
7 #include "HsVersions.h"
8
9 module Rename ( renameModule ) where
10
11 import PreludeGlaST     ( thenPrimIO )
12
13 IMP_Ubiq()
14 IMPORT_1_3(List(partition))
15
16 import HsSyn
17 import RdrHsSyn         ( RdrName, SYN_IE(RdrNameHsModule), SYN_IE(RdrNameImportDecl) )
18 import RnHsSyn          ( SYN_IE(RenamedHsModule), SYN_IE(RenamedHsDecl), extractHsTyNames )
19
20 import CmdLineOpts      ( opt_HiMap )
21 import RnMonad
22 import RnNames          ( getGlobalNames )
23 import RnSource         ( rnDecl )
24 import RnIfaces         ( getImportedInstDecls, importDecl, getImportVersions, getSpecialInstModules,
25                           mkSearchPath
26                         )
27 import RnEnv            ( availsToNameSet, addAvailToNameSet, 
28                           addImplicitOccsRn, lookupImplicitOccRn )
29 import Id               ( GenId {- instance NamedThing -} )
30 import Name             ( Name, Provenance, ExportFlag(..), isLocallyDefined,
31                           NameSet(..), elemNameSet, mkNameSet, unionNameSets, nameSetToList,
32                           isWiredInName, modAndOcc
33                         )
34 import TysWiredIn       ( unitTyCon, intTyCon, doubleTyCon )
35 import PrelInfo         ( ioTyCon_NAME, primIoTyCon_NAME )
36 import TyCon            ( TyCon )
37 import PrelMods         ( mAIN, gHC_MAIN )
38 import ErrUtils         ( SYN_IE(Error), SYN_IE(Warning) )
39 import FiniteMap        ( emptyFM, eltsFM, fmToList, addToFM, FiniteMap )
40 import Pretty
41 import PprStyle         ( PprStyle(..) )
42 import Util             ( panic, assertPanic, pprTrace )
43 \end{code}
44
45
46
47 \begin{code}
48 renameModule :: UniqSupply
49              -> RdrNameHsModule
50              -> IO (Maybe                       -- Nothing <=> everything up to date;
51                                                 -- no ned to recompile any further
52                           (RenamedHsModule,     -- Output, after renaming
53                            InterfaceDetails,    -- Interface; for interface file generatino
54                            RnNameSupply,        -- Final env; for renaming derivings
55                            [Module]),           -- Imported modules; for profiling
56                     Bag Error, 
57                     Bag Warning
58                    )
59 \end{code} 
60
61
62 \begin{code}
63 renameModule us this_mod@(HsModule mod_name vers exports imports fixities local_decls loc)
64   =     -- INITIALISE THE RENAMER MONAD
65     initRn mod_name us (mkSearchPath opt_HiMap) loc $
66
67         -- FIND THE GLOBAL NAME ENVIRONMENT
68     getGlobalNames this_mod                     `thenRn` \ global_name_info ->
69
70     case global_name_info of {
71         Nothing ->      -- Everything is up to date; no need to recompile further
72                         returnRn Nothing ;
73
74                         -- Otherwise, just carry on
75         Just (export_env, rn_env, local_avails) ->
76
77         -- RENAME THE SOURCE
78     initRnMS rn_env mod_name SourceMode (
79         addImplicits mod_name                           `thenRn_`
80         mapRn rnDecl local_decls
81     )                                                   `thenRn` \ rn_local_decls ->
82
83         -- SLURP IN ALL THE NEEDED DECLARATIONS
84     closeDecls rn_local_decls                           `thenRn` \ rn_all_decls ->
85
86
87         -- GENERATE THE VERSION/USAGE INFO
88     getImportVersions mod_name exports                  `thenRn` \ import_versions ->
89     getNameSupplyRn                                     `thenRn` \ name_supply ->
90
91
92         -- GENERATE THE SPECIAL-INSTANCE MODULE LIST
93         -- The "special instance" modules are those modules that contain instance
94         -- declarations that contain no type constructor or class that was declared
95         -- in that module.
96     getSpecialInstModules                               `thenRn` \ imported_special_inst_mods ->
97     let
98         special_inst_decls = [d | InstD d@(InstDecl inst_ty _ _ _ _) <- rn_local_decls,
99                                   all (not.isLocallyDefined) (nameSetToList (extractHsTyNames inst_ty))
100                              ]
101         special_inst_mods | null special_inst_decls = imported_special_inst_mods
102                           | otherwise               = mod_name : imported_special_inst_mods
103     in
104                   
105     
106
107         -- RETURN THE RENAMED MODULE
108     let
109         import_mods = [mod | ImportDecl mod _ _ _ _ <- imports]
110
111         renamed_module = HsModule mod_name vers 
112                                   trashed_exports trashed_imports trashed_fixities
113                                   rn_all_decls
114                                   loc
115     in
116     returnRn (Just (renamed_module, 
117                     (import_versions, export_env, special_inst_mods),
118                      name_supply,
119                      import_mods))
120     }
121   where
122     trashed_exports  = {-trace "rnSource:trashed_exports"-} Nothing
123     trashed_imports  = {-trace "rnSource:trashed_imports"-} []
124     trashed_fixities = []
125 \end{code}
126
127 @addImplicits@ forces the renamer to slurp in some things which aren't
128 mentioned explicitly, but which might be needed by the type checker.
129
130 \begin{code}
131 addImplicits mod_name
132   = addImplicitOccsRn (implicit_main ++ default_tys)
133   where
134         -- Add occurrences for Int, Double, and (), because they
135         -- are the types to which ambigious type variables may be defaulted by
136         -- the type checker; so they won't every appear explicitly.
137         -- [The () one is a GHC extension for defaulting CCall results.]
138     default_tys = [getName intTyCon, getName doubleTyCon, getName unitTyCon]
139
140         -- Add occurrences for IO or PrimIO
141     implicit_main | mod_name == mAIN     = [ioTyCon_NAME]
142                   | mod_name == gHC_MAIN = [primIoTyCon_NAME]
143                   | otherwise            = []
144 \end{code}
145
146
147 \begin{code}
148 closeDecls :: [RenamedHsDecl]                   -- Declarations got so far
149            -> RnMG [RenamedHsDecl]              -- input + extra decls slurped
150         -- The monad includes a list of possibly-unresolved Names
151         -- This list is empty when closeDecls returns
152
153 closeDecls decls 
154   = popOccurrenceName           `thenRn` \ maybe_unresolved ->
155     case maybe_unresolved of
156
157         -- No more unresolved names
158         Nothing ->      -- Slurp instance declarations
159                    getImportedInstDecls                 `thenRn` \ inst_decls ->
160                    traceRn (ppSep [ppPStr SLIT("Slurped"), ppInt (length inst_decls), ppPStr SLIT("instance decls")])
161                                                         `thenRn_`
162
163                         -- None?  then at last we are done
164                    if null inst_decls then
165                         returnRn decls
166                    else 
167                    mapRn rn_inst_decl inst_decls        `thenRn` \ new_inst_decls ->
168
169                         -- We *must* loop again here.  Why?  Two reasons:
170                         -- (a) an instance decl will give rise to an unresolved dfun, whose
171                         --      decl we must slurp to get its version number; that's the version
172                         --      number for the whole instance decl.
173                         -- (b) an instance decl might give rise to a new unresolved class,
174                         --      whose decl we must slurp, which might let in some new instance decls,
175                         --      and so on.  Example:  instance Foo a => Baz [a] where ...
176         
177                    closeDecls (new_inst_decls ++ decls)
178                         
179         -- An unresolved name
180         Just (name,necessity)
181           ->    -- Slurp its declaration, if any
182 --           traceRn (ppSep [ppPStr SLIT("Considering"), ppr PprDebug name])    `thenRn_`
183              importDecl name necessity          `thenRn` \ maybe_decl ->
184              case maybe_decl of
185
186                 -- No declaration... (wired in thing or optional)
187                 Nothing   -> closeDecls decls
188
189                 -- Found a declaration... rename it
190                 Just decl -> rn_iface_decl mod_name decl        `thenRn` \ new_decl ->
191                              closeDecls (new_decl : decls)
192                      where
193                          (mod_name,_) = modAndOcc name
194   where
195                                         -- Notice that the rnEnv starts empty
196     rn_iface_decl mod_name decl  = initRnMS emptyRnEnv mod_name InterfaceMode (rnDecl decl)
197     rn_inst_decl (mod_name,decl) = rn_iface_decl mod_name (InstD decl)
198
199 \end{code}
200
201