d9b7e10b02b3a04abe29b3f8a75b05422652b3df
[ghc-hetmet.git] / ghc / compiler / rename / Rename.lhs
1 %
2 % (c) The GRASP Project, Glasgow University, 1992-1998
3 %
4 \section[Rename]{Renaming and dependency analysis passes}
5
6 \begin{code}
7 module Rename ( renameModule ) where
8
9 #include "HsVersions.h"
10
11 import HsSyn
12 import RdrHsSyn         ( RdrNameHsModule )
13 import RnHsSyn          ( RenamedHsModule, RenamedHsDecl, extractHsTyNames )
14
15 import CmdLineOpts      ( opt_HiMap, opt_D_show_rn_trace,
16                           opt_D_dump_rn, opt_D_show_rn_stats,
17                           opt_WarnUnusedBinds, opt_WarnUnusedImports
18                         )
19 import RnMonad
20 import RnNames          ( getGlobalNames )
21 import RnSource         ( rnIfaceDecl, rnSourceDecls )
22 import RnIfaces         ( getImportedInstDecls, importDecl, getImportVersions, getSpecialInstModules,
23                           getDeferredDataDecls,
24                           mkSearchPath, getSlurpedNames, getRnStats
25                         )
26 import RnEnv            ( addImplicitOccsRn, availName, availNames, availsToNameSet, 
27                           warnUnusedTopNames
28                         )
29 import Module           ( pprModule )
30 import Name             ( Name, isLocallyDefined,
31                           NamedThing(..), ImportReason(..), Provenance(..),
32                           nameModule, pprOccName, nameOccName,
33                           getNameProvenance, occNameUserString, 
34                         )
35 import RdrName          ( RdrName )
36 import NameSet
37 import TyCon            ( TyCon )
38 import PrelMods         ( mAIN, pREL_MAIN )
39 import TysWiredIn       ( unitTyCon, intTyCon, doubleTyCon )
40 import PrelInfo         ( ioTyCon_NAME, thinAirIdNames )
41 import Type             ( funTyCon )
42 import ErrUtils         ( pprBagOfErrors, pprBagOfWarnings,
43                           doIfSet, dumpIfSet, ghcExit
44                         )
45 import Bag              ( isEmptyBag )
46 import FiniteMap        ( fmToList, delListFromFM )
47 import UniqSupply       ( UniqSupply )
48 import Util             ( equivClasses )
49 import Maybes           ( maybeToBool )
50 import Outputable
51 \end{code}
52
53
54
55 \begin{code}
56 renameModule :: UniqSupply
57              -> RdrNameHsModule
58              -> IO (Maybe 
59                       ( RenamedHsModule   -- Output, after renaming
60                       , InterfaceDetails  -- Interface; for interface file generatino
61                       , RnNameSupply      -- Final env; for renaming derivings
62                       , [Module]          -- Imported modules; for profiling
63                       ))
64
65 renameModule us this_mod@(HsModule mod_name vers exports imports local_decls loc)
66   =     -- Initialise the renamer monad
67     initRn mod_name us (mkSearchPath opt_HiMap) loc
68            (rename this_mod)                            >>=
69         \ (maybe_rn_stuff, rn_errs_bag, rn_warns_bag) ->
70
71         -- Check for warnings
72     doIfSet (not (isEmptyBag rn_warns_bag))
73             (printErrs (pprBagOfWarnings rn_warns_bag)) >>
74
75         -- Check for errors; exit if so
76     doIfSet (not (isEmptyBag rn_errs_bag))
77             (printErrs (pprBagOfErrors rn_errs_bag)      >>
78              ghcExit 1
79             )                                            >>
80
81         -- Dump output, if any
82     (case maybe_rn_stuff of
83         Nothing  -> return ()
84         Just results@(rn_mod, _, _, _)
85                  -> dumpIfSet opt_D_dump_rn "Renamer:"
86                               (ppr rn_mod)
87     )                                                   >>
88
89         -- Return results
90     return maybe_rn_stuff
91 \end{code}
92
93
94 \begin{code}
95 rename this_mod@(HsModule mod_name vers exports imports local_decls loc)
96   =     -- FIND THE GLOBAL NAME ENVIRONMENT
97     getGlobalNames this_mod                     `thenRn` \ maybe_stuff ->
98
99         -- CHECK FOR EARLY EXIT
100     if not (maybeToBool maybe_stuff) then
101         -- Everything is up to date; no need to recompile further
102         rnStats []              `thenRn_`
103         returnRn Nothing
104     else
105     let
106         Just (export_env, rn_env, global_avail_env) = maybe_stuff
107     in
108
109         -- RENAME THE SOURCE
110     initRnMS rn_env SourceMode (
111         addImplicits mod_name                           `thenRn_`
112         rnSourceDecls local_decls
113     )                                                   `thenRn` \ (rn_local_decls, fvs) ->
114
115         -- SLURP IN ALL THE NEEDED DECLARATIONS
116     slurpDecls rn_local_decls           `thenRn` \ rn_all_decls ->
117
118         -- EXIT IF ERRORS FOUND
119     checkErrsRn                         `thenRn` \ no_errs_so_far ->
120     if not no_errs_so_far then
121         -- Found errors already, so exit now
122         rnStats []              `thenRn_`
123         returnRn Nothing
124     else
125
126         -- GENERATE THE VERSION/USAGE INFO
127     getImportVersions mod_name exports                  `thenRn` \ import_versions ->
128     getNameSupplyRn                                     `thenRn` \ name_supply ->
129
130         -- REPORT UNUSED NAMES
131     reportUnusedNames rn_env global_avail_env
132                       export_env
133                       fvs                               `thenRn_`
134
135         -- GENERATE THE SPECIAL-INSTANCE MODULE LIST
136         -- The "special instance" modules are those modules that contain instance
137         -- declarations that contain no type constructor or class that was declared
138         -- in that module.
139     getSpecialInstModules                               `thenRn` \ imported_special_inst_mods ->
140     let
141         special_inst_decls = [d | InstD d@(InstDecl inst_ty _ _ _ _) <- rn_local_decls,
142                                   all (not.isLocallyDefined) (nameSetToList (extractHsTyNames inst_ty))
143                              ]
144         special_inst_mods | null special_inst_decls = imported_special_inst_mods
145                           | otherwise               = mod_name : imported_special_inst_mods
146     in
147                   
148     
149         -- RETURN THE RENAMED MODULE
150     let
151         import_mods = [mod | ImportDecl mod _ _ _ _ <- imports]
152
153         renamed_module = HsModule mod_name vers 
154                                   trashed_exports trashed_imports
155                                   rn_all_decls
156                                   loc
157     in
158     rnStats rn_all_decls        `thenRn_`
159     returnRn (Just (renamed_module, 
160                     (import_versions, export_env, special_inst_mods),
161                      name_supply,
162                      import_mods))
163   where
164     trashed_exports  = {-trace "rnSource:trashed_exports"-} Nothing
165     trashed_imports  = {-trace "rnSource:trashed_imports"-} []
166 \end{code}
167
168 @addImplicits@ forces the renamer to slurp in some things which aren't
169 mentioned explicitly, but which might be needed by the type checker.
170
171 \begin{code}
172 addImplicits mod_name
173   = addImplicitOccsRn (implicit_main ++ default_tys ++ thinAirIdNames)
174   where
175         -- Add occurrences for Int, Double, and (), because they
176         -- are the types to which ambigious type variables may be defaulted by
177         -- the type checker; so they won't always appear explicitly.
178         -- [The () one is a GHC extension for defaulting CCall results.]
179         -- ALSO: funTyCon, since it occurs implicitly everywhere!
180         --       (we don't want to be bothered with addImplicitOcc at every
181         --        function application)
182     default_tys = [getName intTyCon, getName doubleTyCon,
183                    getName unitTyCon, getName funTyCon]
184
185         -- Add occurrences for IO or PrimIO
186     implicit_main |  mod_name == mAIN
187                   || mod_name == pREL_MAIN = [ioTyCon_NAME]
188                   |  otherwise             = []
189 \end{code}
190
191
192 \begin{code}
193 slurpDecls decls
194   =     -- First of all, get all the compulsory decls
195     slurp_compulsories decls    `thenRn` \ decls1 ->
196
197         -- Next get the optional ones
198     closeDecls optional_mode decls1     `thenRn` \ decls2 ->
199
200         -- Finally get those deferred data type declarations
201     getDeferredDataDecls                                `thenRn` \ data_decls ->
202     mapRn (rn_data_decl compulsory_mode) data_decls     `thenRn` \ rn_data_decls ->
203
204         -- Done
205     returnRn (rn_data_decls ++ decls2)
206
207   where
208     compulsory_mode = InterfaceMode Compulsory
209     optional_mode   = InterfaceMode Optional
210
211         -- The "slurp_compulsories" function is a loop that alternates
212         -- between slurping compulsory decls and slurping the instance
213         -- decls thus made relavant.
214         -- We *must* loop again here.  Why?  Two reasons:
215         -- (a) an instance decl will give rise to an unresolved dfun, whose
216         --      decl we must slurp to get its version number; that's the version
217         --      number for the whole instance decl.  (And its unfolding might mention new
218         --  unresolved names.)
219         -- (b) an instance decl might give rise to a new unresolved class,
220         --      whose decl we must slurp, which might let in some new instance decls,
221         --      and so on.  Example:  instance Foo a => Baz [a] where ...
222     slurp_compulsories decls
223       = closeDecls compulsory_mode decls        `thenRn` \ decls1 ->
224         
225                 -- Instance decls still pending?
226         getImportedInstDecls                    `thenRn` \ inst_decls ->
227         if null inst_decls then 
228                 -- No, none
229             returnRn decls1
230         else
231                 -- Yes, there are some, so rename them and loop
232              traceRn (sep [ptext SLIT("Slurped"), int (length inst_decls), ptext SLIT("instance decls")])
233                                                                 `thenRn_`
234              mapRn (rn_inst_decl compulsory_mode) inst_decls    `thenRn` \ new_inst_decls ->
235              slurp_compulsories (new_inst_decls ++ decls1)
236 \end{code}
237
238 \begin{code}
239 closeDecls :: RnMode
240            -> [RenamedHsDecl]                   -- Declarations got so far
241            -> RnMG [RenamedHsDecl]              -- input + extra decls slurped
242         -- The monad includes a list of possibly-unresolved Names
243         -- This list is empty when closeDecls returns
244
245 closeDecls mode decls 
246   = popOccurrenceName mode              `thenRn` \ maybe_unresolved ->
247     case maybe_unresolved of
248
249         -- No more unresolved names
250         Nothing -> returnRn decls
251                         
252         -- An unresolved name
253         Just name_w_loc
254           ->    -- Slurp its declaration, if any
255 --           traceRn (sep [ptext SLIT("Considering"), ppr name_w_loc])  `thenRn_`
256              importDecl name_w_loc mode         `thenRn` \ maybe_decl ->
257              case maybe_decl of
258
259                 -- No declaration... (wired in thing or optional)
260                 Nothing   -> closeDecls mode decls
261
262                 -- Found a declaration... rename it
263                 Just decl -> rn_iface_decl mod_name mode decl   `thenRn` \ new_decl ->
264                              closeDecls mode (new_decl : decls)
265                          where
266                            mod_name = nameModule (fst name_w_loc)
267
268 rn_iface_decl mod_name mode decl
269   = setModuleRn mod_name $
270     initRnMS emptyRnEnv mode (rnIfaceDecl decl)
271                                         
272 rn_inst_decl mode (mod_name,decl)    = rn_iface_decl mod_name mode (InstD decl)
273 rn_data_decl mode (mod_name,ty_decl) = rn_iface_decl mod_name mode (TyClD ty_decl)
274 \end{code}
275
276 \begin{code}
277 reportUnusedNames (RnEnv gbl_env _) avail_env (ExportEnv export_avails _) mentioned_names
278   | not (opt_WarnUnusedBinds || opt_WarnUnusedImports)
279   = returnRn ()
280
281   | otherwise
282   = let
283         used_names = mentioned_names `unionNameSets` availsToNameSet export_avails
284
285         -- Now, a use of C implies a use of T,
286         -- if C was brought into scope by T(..) or T(C)
287         really_used_names = used_names `unionNameSets`
288                             mkNameSet [ availName avail 
289                                       | sub_name <- nameSetToList used_names,
290                                         let avail = case lookupNameEnv avail_env sub_name of
291                                                         Just avail -> avail
292                                                         Nothing -> pprTrace "r.u.n" (ppr sub_name) $
293                                                                    Avail sub_name
294                                       ]
295
296         defined_names = mkNameSet (concat (rdrEnvElts gbl_env))
297         defined_but_not_used = nameSetToList (defined_names `minusNameSet` really_used_names)
298
299         -- Filter out the ones only defined implicitly
300         bad_guys = filter reportableUnusedName defined_but_not_used
301     in
302     warnUnusedTopNames bad_guys `thenRn_`
303     returnRn ()
304
305 reportableUnusedName :: Name -> Bool
306 reportableUnusedName name
307   = explicitlyImported (getNameProvenance name) &&
308     not (startsWithUnderscore (occNameUserString (nameOccName name)))
309   where
310     explicitlyImported (LocalDef _ _)                        = True     -- Report unused defns of local vars
311     explicitlyImported (NonLocalDef (UserImport _ _ expl) _) = expl     -- Report unused explicit imports
312     explicitlyImported other                                 = False    -- Don't report others
313    
314         -- Haskell 98 encourages compilers to suppress warnings about
315         -- unused names in a pattern if they start with "_".
316     startsWithUnderscore ('_' : _) = True       -- Suppress warnings for names starting
317     startsWithUnderscore other     = False      -- with an underscore
318
319 rnStats :: [RenamedHsDecl] -> RnMG ()
320 rnStats all_decls
321         | opt_D_show_rn_trace || 
322           opt_D_show_rn_stats ||
323           opt_D_dump_rn 
324         = getRnStats all_decls          `thenRn` \ msg ->
325           ioToRnMG (printErrs msg)      `thenRn_`
326           returnRn ()
327
328         | otherwise = returnRn ()
329 \end{code}
330