d66596bc3fd3847865c0d0066b704711d2379119
[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, getDecl, getImportVersions, getSpecialInstModules,
25                           mkSearchPath, getWiredInDecl
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         -- Notice that the rnEnv starts empty
85     closeDecls rn_local_decls (availsToNameSet local_avails) []
86                                                 `thenRn` \ (rn_all_decls1, all_names1, imp_avails1) ->
87
88         -- SLURP IN ALL NEEDED INSTANCE DECLARATIONS
89         -- We extract instance decls that only mention things (type constructors, classes) that are
90         -- already imported.  Those that don't can't possibly be useful to us.
91         --
92         -- We do another closeDecls, so that we can slurp info for the dictionary functions
93         -- for the instance declaration.  These are *not* optional because the version number on
94         -- the dfun acts as the version number for the instance declaration itself; if the
95         -- instance decl changes, so will its dfun version number.
96     getImportedInstDecls                                `thenRn` \ imported_insts ->
97     let
98         all_big_names = mkNameSet [name | Avail name _ <- local_avails]    `unionNameSets` 
99                         mkNameSet [name | Avail name _ <- imp_avails1]
100
101         rn_needed_insts = [ initRnMS emptyRnEnv mod_name InterfaceMode (rnDecl (InstD inst_decl))
102                           | (inst_names, mod_name, inst_decl) <- imported_insts,
103                             all (`elemNameSet` all_big_names) inst_names
104                           ]
105     in
106     sequenceRn rn_needed_insts                          `thenRn` \ inst_decls ->
107     closeDecls rn_all_decls1 all_names1 imp_avails1     `thenRn` \ (rn_all_decls2, all_names2, imp_avails2) ->
108
109
110         -- GENERATE THE VERSION/USAGE INFO
111     getImportVersions imp_avails2                       `thenRn` \ import_versions ->
112     getNameSupplyRn                                     `thenRn` \ name_supply ->
113
114
115         -- GENERATE THE SPECIAL-INSTANCE MODULE LIST
116         -- The "special instance" modules are those modules that contain instance
117         -- declarations that contain no type constructor or class that was declared
118         -- in that module.
119     getSpecialInstModules                               `thenRn` \ imported_special_inst_mods ->
120     let
121         special_inst_decls = [d | InstD d@(InstDecl inst_ty _ _ _ _) <- rn_local_decls,
122                                   all (not.isLocallyDefined) (nameSetToList (extractHsTyNames inst_ty))
123                              ]
124         special_inst_mods | null special_inst_decls = imported_special_inst_mods
125                           | otherwise               = mod_name : imported_special_inst_mods
126     in
127                   
128     
129
130         -- RETURN THE RENAMED MODULE
131     let
132         import_mods = [mod | ImportDecl mod _ _ _ _ <- imports]
133
134         renamed_module = HsModule mod_name vers 
135                                   trashed_exports trashed_imports trashed_fixities
136                                   (inst_decls ++ rn_all_decls2)
137                                   loc
138     in
139     returnRn (Just (renamed_module, 
140                     (import_versions, export_env, special_inst_mods),
141                      name_supply,
142                      import_mods))
143     }
144   where
145     trashed_exports  = {-trace "rnSource:trashed_exports"-} Nothing
146     trashed_imports  = {-trace "rnSource:trashed_imports"-} []
147     trashed_fixities = []
148 \end{code}
149
150 @addImplicits@ forces the renamer to slurp in some things which aren't
151 mentioned explicitly, but which might be needed by the type checker.
152
153 \begin{code}
154 addImplicits mod_name
155   = addImplicitOccsRn (implicit_main ++ default_tys)
156   where
157         -- Add occurrences for Int, Double, and (), because they
158         -- are the types to which ambigious type variables may be defaulted by
159         -- the type checker; so they won't every appear explicitly.
160         -- [The () one is a GHC extension for defaulting CCall results.]
161     default_tys = [getName intTyCon, getName doubleTyCon, getName unitTyCon]
162
163         -- Add occurrences for IO or PrimIO
164     implicit_main | mod_name == mAIN     = [ioTyCon_NAME]
165                   | mod_name == gHC_MAIN = [primIoTyCon_NAME]
166                   | otherwise            = []
167 \end{code}
168
169
170 \begin{code}
171 closeDecls :: [RenamedHsDecl]                   -- Declarations got so far
172            -> NameSet                           -- Names bound by those declarations
173            -> [AvailInfo]                       -- Available stuff generated by closeDecls so far
174            -> RnMG ([RenamedHsDecl],            -- input + extra decls slurped
175                     NameSet,                    -- input + names bound by extra decls
176                     [AvailInfo])                -- input + extra avails from extra decls
177         -- The monad includes a list of possibly-unresolved Names
178         -- This list is empty when closeDecls returns
179
180 closeDecls decls decl_names import_avails
181   = popOccurrenceName           `thenRn` \ maybe_unresolved ->
182
183     case maybe_unresolved of
184
185         -- No more unresolved names; we're done
186         Nothing ->      returnRn (decls, decl_names, import_avails)
187
188         -- An "unresolved" name that we've already dealt with
189         Just (name,_) | name `elemNameSet` decl_names 
190           -> closeDecls decls decl_names import_avails
191         
192         -- An unresolved name that's wired in.  In this case there's no 
193         -- declaration to get, but we still want to record it as now available,
194         -- so that we remember to look for instance declarations involving it.
195         Just (name,_) | isWiredInName name
196           -> getWiredInDecl name        `thenRn` \ decl_avail ->
197                      closeDecls decls 
198                                 (addAvailToNameSet decl_names decl_avail)
199                                 (decl_avail : import_avails)
200
201         -- Genuinely unresolved name
202         Just (name,necessity) | otherwise
203           -> getDecl name               `thenRn` \ (decl_avail,new_decl) ->
204              case decl_avail of
205
206                 -- Can't find the declaration; check that it was optional
207                 NotAvailable -> case necessity of { 
208                                         Optional -> addWarnRn (getDeclWarn name);
209                                         other    -> addErrRn  (getDeclErr  name)
210                                 }                                               `thenRn_` 
211                                 closeDecls decls decl_names import_avails
212
213                 -- Found it
214                 other -> initRnMS emptyRnEnv mod_name InterfaceMode (
215                                      rnDecl new_decl
216                          )                              `thenRn` \ rn_decl ->
217                          closeDecls (rn_decl : decls)
218                                     (addAvailToNameSet decl_names decl_avail)
219                                     (decl_avail : import_avails)
220                      where
221                          (mod_name,_) = modAndOcc name
222
223 getDeclErr name sty
224   = ppSep [ppStr "Failed to find interface decl for", ppr sty name]
225
226 getDeclWarn name sty
227   = ppSep [ppStr "Warning: failed to find (optional) interface decl for", ppr sty name]
228 \end{code}
229
230