[project @ 1999-01-28 14:22:15 by simonpj]
[ghc-hetmet.git] / ghc / compiler / rename / RnIfaces.lhs
1 %
2 % (c) The GRASP/AQUA Project, Glasgow University, 1992-1998
3 %
4 \section[RnIfaces]{Cacheing and Renaming of Interfaces}
5
6 \begin{code}
7 module RnIfaces (
8         getInterfaceExports,
9         getImportedInstDecls,
10         getSpecialInstModules, getDeferredDataDecls,
11         importDecl, recordSlurp,
12         getImportVersions, getSlurpedNames, getRnStats, getImportedFixities,
13
14         checkUpToDate, loadHomeInterface,
15
16         getDeclBinders,
17         mkSearchPath
18     ) where
19
20 #include "HsVersions.h"
21
22 import CmdLineOpts      ( opt_PruneTyDecls,  opt_PruneInstDecls, 
23                           opt_D_show_rn_imports, opt_IgnoreIfacePragmas
24                         )
25 import HsSyn            ( HsDecl(..), TyClDecl(..), InstDecl(..), IfaceSig(..), 
26                           HsType(..), ConDecl(..), IE(..), ConDetails(..), Sig(..),
27                           FixitySig(..),
28                           hsDeclName, countTyClDecls, isDataDecl, nonFixitySigs
29                         )
30 import BasicTypes       ( Version, NewOrData(..) )
31 import RdrHsSyn         ( RdrNameHsDecl, RdrNameInstDecl, RdrNameTyClDecl,
32                         )
33 import RnEnv            ( newImportedGlobalName, newImportedGlobalFromRdrName, 
34                           addImplicitOccsRn, pprAvail,
35                           availName, availNames, addAvailToNameSet
36                         )
37 import RnSource         ( rnHsSigType )
38 import RnMonad
39 import RnHsSyn          ( RenamedHsDecl )
40 import ParseIface       ( parseIface, IfaceStuff(..) )
41
42 import FiniteMap        ( FiniteMap, sizeFM, emptyFM, delFromFM,
43                           lookupFM, addToFM, addToFM_C, addListToFM, 
44                           fmToList
45                         )
46 import Name             ( Name {-instance NamedThing-},
47                           nameModule, moduleString, pprModule, isLocallyDefined,
48                           isWiredInName, maybeWiredInTyConName,  pprModule,
49                           maybeWiredInIdName, nameUnique, NamedThing(..)
50                          )
51 import OccName          ( Module, mkBootModule, 
52                           moduleIfaceFlavour, bootFlavour, hiFile
53                         )
54 import RdrName          ( RdrName, rdrNameOcc )
55 import NameSet
56 import Id               ( idType, isDataConId_maybe )
57 import DataCon          ( dataConTyCon, dataConType )
58 import TyCon            ( TyCon, tyConDataCons, isSynTyCon, getSynTyConDefn )
59 import Type             ( namesOfType )
60 import Var              ( Id )
61 import SrcLoc           ( mkSrcLoc, SrcLoc )
62 import PrelMods         ( pREL_GHC )
63 import PrelInfo         ( cCallishTyKeys, thinAirModules )
64 import Bag
65 import Maybes           ( MaybeErr(..), maybeToBool )
66 import ListSetOps       ( unionLists )
67 import Outputable
68 import Unique           ( Unique )
69 import StringBuffer     ( StringBuffer, hGetStringBuffer )
70 import FastString       ( mkFastString )
71 import Outputable
72
73 import IO       ( isDoesNotExistError )
74 import List     ( nub )
75
76 \end{code}
77
78
79
80 %*********************************************************
81 %*                                                      *
82 \subsection{Statistics}
83 %*                                                      *
84 %*********************************************************
85
86 \begin{code}
87 getRnStats :: [RenamedHsDecl] -> RnMG SDoc
88 getRnStats all_decls
89   = getIfacesRn                 `thenRn` \ ifaces ->
90     let
91         n_mods      = sizeFM (iModMap ifaces)
92
93         decls_imported = filter is_imported_decl all_decls
94
95         decls_read     = [decl | (_, avail, decl, True) <- nameEnvElts (iDecls ifaces),
96                                         -- Data, newtype, and class decls are in the decls_fm
97                                         -- under multiple names; the tycon/class, and each
98                                         -- constructor/class op too.
99                                         -- The 'True' selects just the 'main' decl
100                                  not (isLocallyDefined (availName avail))
101                              ]
102
103         (cd_rd, dd_rd, add_rd, nd_rd, and_rd, sd_rd, vd_rd,     _) = count_decls decls_read
104         (cd_sp, dd_sp, add_sp, nd_sp, and_sp, sd_sp, vd_sp, id_sp) = count_decls decls_imported
105
106         (unslurped_insts, _)  = iDefInsts ifaces
107         inst_decls_unslurped  = length (bagToList unslurped_insts)
108         inst_decls_read       = id_sp + inst_decls_unslurped
109
110         stats = vcat 
111                 [int n_mods <> text " interfaces read",
112                  hsep [ int cd_sp, text "class decls imported, out of", 
113                         int cd_rd, text "read"],
114                  hsep [ int dd_sp, text "data decls imported (of which", int add_sp, 
115                         text "abstractly), out of",  
116                         int dd_rd, text "read"],
117                  hsep [ int nd_sp, text "newtype decls imported (of which", int and_sp, 
118                         text "abstractly), out of",  
119                         int nd_rd, text "read"],
120                  hsep [int sd_sp, text "type synonym decls imported, out of",  
121                         int sd_rd, text "read"],
122                  hsep [int vd_sp, text "value signatures imported, out of",  
123                         int vd_rd, text "read"],
124                  hsep [int id_sp, text "instance decls imported, out of",  
125                         int inst_decls_read, text "read"]
126                 ]
127     in
128     returnRn (hcat [text "Renamer stats: ", stats])
129
130 is_imported_decl (DefD _) = False
131 is_imported_decl (ValD _) = False
132 is_imported_decl decl     = not (isLocallyDefined (hsDeclName decl))
133
134 count_decls decls
135   = -- pprTrace "count_decls" (ppr  decls
136     --
137     --                      $$
138     --                      text "========="
139     --                      $$
140     --                      ppr imported_decls
141     --  ) $
142     (class_decls, 
143      data_decls,    abstract_data_decls,
144      newtype_decls, abstract_newtype_decls,
145      syn_decls, 
146      val_decls, 
147      inst_decls)
148   where
149     tycl_decls = [d | TyClD d <- decls]
150     (class_decls, data_decls, newtype_decls, syn_decls) = countTyClDecls tycl_decls
151     abstract_data_decls    = length [() | TyData DataType _ _ _ [] _ _ _ <- tycl_decls]
152     abstract_newtype_decls = length [() | TyData NewType  _ _ _ [] _ _ _ <- tycl_decls]
153
154     val_decls     = length [() | SigD _   <- decls]
155     inst_decls    = length [() | InstD _  <- decls]
156
157 \end{code}    
158
159 %*********************************************************
160 %*                                                      *
161 \subsection{Loading a new interface file}
162 %*                                                      *
163 %*********************************************************
164
165 \begin{code}
166 loadHomeInterface :: SDoc -> Name -> RnMG Ifaces
167 loadHomeInterface doc_str name
168   = loadInterface doc_str (nameModule name)
169
170 loadInterface :: SDoc -> Module -> RnMG Ifaces
171 loadInterface doc_str load_mod
172  = getIfacesRn          `thenRn` \ ifaces ->
173    let
174         new_hif              = moduleIfaceFlavour load_mod
175         this_mod             = iMod ifaces
176         mod_map              = iModMap ifaces
177         (insts, tycls_names) = iDefInsts ifaces
178    in
179         -- CHECK WHETHER WE HAVE IT ALREADY
180    case lookupFM mod_map load_mod of {
181         Just (existing_hif, _, _) 
182                 | bootFlavour new_hif || not (bootFlavour existing_hif)
183                 ->      -- Already in the cache, and new version is no better than old,
184                         -- so don't re-read it
185                     returnRn ifaces ;
186         other ->
187
188         -- READ THE MODULE IN
189    findAndReadIface doc_str load_mod            `thenRn` \ read_result ->
190    case read_result of {
191         -- Check for not found
192         Nothing ->      -- Not found, so add an empty export env to the Ifaces map
193                         -- so that we don't look again
194                    let
195                         new_mod_map = addToFM mod_map load_mod (hiFile, 0, [])
196                         new_ifaces = ifaces { iModMap = new_mod_map }
197                    in
198                    setIfacesRn new_ifaces               `thenRn_`
199                    failWithRn new_ifaces (noIfaceErr load_mod) ;
200
201         -- Found and parsed!
202         Just (ParsedIface _ mod_vers usages exports rd_inst_mods rd_decls rd_insts) ->
203
204         -- LOAD IT INTO Ifaces
205         -- First set the module
206
207         -- NB: *first* we do loadDecl, so that the provenance of all the locally-defined
208         ---    names is done correctly (notably, whether this is an .hi file or .hi-boot file).
209         --     If we do loadExport first the wrong info gets into the cache (unless we
210         --      explicitly tag each export which seems a bit of a bore)
211
212     getModuleRn                 `thenRn` \ this_mod ->
213     setModuleRn load_mod  $     -- First set the module name of the module being loaded,
214                                 -- so that unqualified occurrences in the interface file
215                                 -- get the right qualifer
216     foldlRn loadDecl (iDecls ifaces) rd_decls           `thenRn` \ new_decls ->
217     foldlRn loadFixDecl (iFixes ifaces) rd_decls        `thenRn` \ new_fixities ->
218     foldlRn loadInstDecl insts rd_insts                 `thenRn` \ new_insts ->
219
220     mapRn (loadExport this_mod) exports                 `thenRn` \ avails_s ->
221     let
222          mod_details = (new_hif, mod_vers, concat avails_s)
223
224                         -- Exclude this module from the "special-inst" modules
225          new_inst_mods = iInstMods ifaces `unionLists` (filter (/= this_mod) rd_inst_mods)
226
227          new_ifaces = ifaces { iModMap   = addToFM mod_map load_mod mod_details,
228                                iDecls    = new_decls,
229                                iFixes    = new_fixities,
230                                iDefInsts = (new_insts, tycls_names),
231                                iInstMods = new_inst_mods  }
232     in
233     setIfacesRn new_ifaces              `thenRn_`
234     returnRn new_ifaces
235     }}
236
237 loadExport :: Module -> ExportItem -> RnMG [AvailInfo]
238 loadExport this_mod (mod, entities)
239   | mod == this_mod = returnRn []
240         -- If the module exports anything defined in this module, just ignore it.
241         -- Reason: otherwise it looks as if there are two local definition sites
242         -- for the thing, and an error gets reported.  Easiest thing is just to
243         -- filter them out up front. This situation only arises if a module
244         -- imports itself, or another module that imported it.  (Necessarily,
245         -- this invoves a loop.)  Consequence: if you say
246         --      module A where
247         --         import B( AType )
248         --         type AType = ...
249         --
250         --      module B( AType ) where
251         --         import {-# SOURCE #-} A( AType )
252         --
253         -- then you'll get a 'B does not export AType' message.  A bit bogus
254         -- but it's a bogus thing to do!
255
256   | otherwise
257   = mapRn load_entity entities
258   where
259     new_name occ = newImportedGlobalName mod occ
260
261     load_entity (Avail occ)
262       = new_name occ            `thenRn` \ name ->
263         returnRn (Avail name)
264     load_entity (AvailTC occ occs)
265       = new_name occ            `thenRn` \ name ->
266         mapRn new_name occs     `thenRn` \ names ->
267         returnRn (AvailTC name names)
268
269
270 loadFixDecl :: FixityEnv 
271             -> (Version, RdrNameHsDecl)
272             -> RnMG FixityEnv
273 loadFixDecl fixity_env (version, FixD (FixitySig rdr_name fixity loc))
274   =     -- Ignore the version; when the fixity changes the version of
275         -- its 'host' entity changes, so we don't need a separate version
276         -- number for fixities
277     newImportedGlobalFromRdrName rdr_name       `thenRn` \ name ->
278     let
279         new_fixity_env = addToNameEnv fixity_env name (FixitySig name fixity loc)
280     in
281     returnRn new_fixity_env
282
283         -- Ignore the other sorts of decl
284 loadFixDecl fixity_env other_decl = returnRn fixity_env
285
286 loadDecl :: DeclsMap
287          -> (Version, RdrNameHsDecl)
288          -> RnMG DeclsMap
289
290 loadDecl decls_map (version, decl)
291   = getDeclBinders new_name decl        `thenRn` \ maybe_avail ->
292     case maybe_avail of {
293         Nothing -> returnRn decls_map;  -- No bindings
294         Just avail ->
295
296     getDeclSysBinders new_name decl     `thenRn` \ sys_bndrs ->
297     let
298         main_name     = availName avail
299         new_decls_map = foldl add_decl decls_map
300                                        [ (name, (version,avail,decl',name==main_name)) 
301                                        | name <- sys_bndrs ++ availNames avail]
302         add_decl decls_map (name, stuff)
303           = WARN( name `elemNameEnv` decls_map, ppr name )
304             addToNameEnv decls_map name stuff
305     in
306     returnRn new_decls_map
307     }
308   where
309     new_name rdr_name loc = newImportedGlobalFromRdrName rdr_name
310     {-
311       If a signature decl is being loaded, and optIgnoreIfacePragmas is on,
312       we toss away unfolding information.
313
314       Also, if the signature is loaded from a module we're importing from source,
315       we do the same. This is to avoid situations when compiling a pair of mutually
316       recursive modules, peering at unfolding info in the interface file of the other, 
317       e.g., you compile A, it looks at B's interface file and may as a result change
318       its interface file. Hence, B is recompiled, maybe changing its interface file,
319       which will the unfolding info used in A to become invalid. Simple way out is to
320       just ignore unfolding info.
321
322       [Jan 99: I junked the second test above.  If we're importing from an hi-boot
323        file there isn't going to *be* any pragma info.  Maybe the above comment
324        dates from a time where we picked up a .hi file first if it existed?]
325     -}
326     decl' = 
327      case decl of
328        SigD (IfaceSig name tp ls loc) | opt_IgnoreIfacePragmas -> 
329             SigD (IfaceSig name tp [] loc)
330        _ -> decl
331
332 loadInstDecl :: Bag IfaceInst
333              -> RdrNameInstDecl
334              -> RnMG (Bag IfaceInst)
335 loadInstDecl insts decl@(InstDecl inst_ty binds uprags dfun_name src_loc)
336   = 
337         -- Find out what type constructors and classes are "gates" for the
338         -- instance declaration.  If all these "gates" are slurped in then
339         -- we should slurp the instance decl too.
340         -- 
341         -- We *don't* want to count names in the context part as gates, though.
342         -- For example:
343         --              instance Foo a => Baz (T a) where ...
344         --
345         -- Here the gates are Baz and T, but *not* Foo.
346     let 
347         munged_inst_ty = case inst_ty of
348                                 HsForAllTy tvs cxt ty -> HsForAllTy tvs [] ty
349                                 other                 -> inst_ty
350     in
351         -- We find the gates by renaming the instance type with in a 
352         -- and returning the free variables of the type
353     initRnMS emptyRnEnv vanillaInterfaceMode (
354         discardOccurrencesRn (rnHsSigType (text "an instance decl") munged_inst_ty)
355     )                                           `thenRn` \ (_, gate_names) ->
356     getModuleRn                                 `thenRn` \ mod_name -> 
357     returnRn (((mod_name, decl), gate_names) `consBag` insts)
358
359 vanillaInterfaceMode = InterfaceMode Compulsory
360 \end{code}
361
362
363 %********************************************************
364 %*                                                      *
365 \subsection{Loading usage information}
366 %*                                                      *
367 %********************************************************
368
369 \begin{code}
370 checkUpToDate :: Module -> RnMG Bool            -- True <=> no need to recompile
371 checkUpToDate mod_name
372   = findAndReadIface doc_str mod_name           `thenRn` \ read_result ->
373
374         -- CHECK WHETHER WE HAVE IT ALREADY
375     case read_result of
376         Nothing ->      -- Old interface file not found, so we'd better bail out
377                     traceRn (sep [ptext SLIT("Didnt find old iface"), 
378                                     pprModule mod_name])        `thenRn_`
379                     returnRn False
380
381         Just (ParsedIface _ _ usages _ _ _ _) 
382                 ->      -- Found it, so now check it
383                     checkModUsage usages
384   where
385         -- Only look in current directory, with suffix .hi
386     doc_str = sep [ptext SLIT("need usage info from"), pprModule mod_name]
387
388 checkModUsage [] = returnRn True                -- Yes!  Everything is up to date!
389
390 checkModUsage ((mod, old_mod_vers, whats_imported) : rest)
391   = loadInterface doc_str mod           `thenRn` \ ifaces ->
392     let
393         maybe_new_mod_vers        = lookupFM (iModMap ifaces) mod
394         Just (_, new_mod_vers, _) = maybe_new_mod_vers
395     in
396         -- If we can't find a version number for the old module then
397         -- bail out saying things aren't up to date
398     if not (maybeToBool maybe_new_mod_vers) then
399         traceRn (sep [ptext SLIT("Can't find version number for module"), pprModule mod]) `thenRn_`
400         returnRn False
401     else
402
403         -- If the module version hasn't changed, just move on
404     if new_mod_vers == old_mod_vers then
405         traceRn (sep [ptext SLIT("Module version unchanged:"), pprModule mod])  `thenRn_`
406         checkModUsage rest
407     else
408     traceRn (sep [ptext SLIT("Module version has changed:"), pprModule mod])    `thenRn_`
409
410         -- Module version changed, so check entities inside
411
412         -- If the usage info wants to say "I imported everything from this module"
413         --     it does so by making whats_imported equal to Everything
414         -- In that case, we must recompile
415     case whats_imported of {
416       Everything -> traceRn (ptext SLIT("...and I needed the whole module"))    `thenRn_`
417                     returnRn False;                -- Bale out
418
419       Specifically old_local_vers ->
420
421         -- Non-empty usage list, so check item by item
422     checkEntityUsage mod (iDecls ifaces) old_local_vers `thenRn` \ up_to_date ->
423     if up_to_date then
424         traceRn (ptext SLIT("...but the bits I use haven't."))  `thenRn_`
425         checkModUsage rest      -- This one's ok, so check the rest
426     else
427         returnRn False          -- This one failed, so just bail out now
428     }
429   where
430     doc_str = sep [ptext SLIT("need version info for"), pprModule mod]
431
432
433 checkEntityUsage mod decls [] 
434   = returnRn True       -- Yes!  All up to date!
435
436 checkEntityUsage mod decls ((occ_name,old_vers) : rest)
437   = newImportedGlobalName mod occ_name          `thenRn` \ name ->
438     case lookupNameEnv decls name of
439
440         Nothing       ->        -- We used it before, but it ain't there now
441                           putDocRn (sep [ptext SLIT("No longer exported:"), ppr name])  `thenRn_`
442                           returnRn False
443
444         Just (new_vers,_,_,_)   -- It's there, but is it up to date?
445                 | new_vers == old_vers
446                         -- Up to date, so check the rest
447                 -> checkEntityUsage mod decls rest
448
449                 | otherwise
450                         -- Out of date, so bale out
451                 -> putDocRn (sep [ptext SLIT("Out of date:"), ppr name])  `thenRn_`
452                    returnRn False
453 \end{code}
454
455
456 %*********************************************************
457 %*                                                      *
458 \subsection{Getting in a declaration}
459 %*                                                      *
460 %*********************************************************
461
462 \begin{code}
463 importDecl :: Occurrence -> RnMode -> RnMG (Maybe RdrNameHsDecl)
464         -- Returns Nothing for a wired-in or already-slurped decl
465
466 importDecl (name, loc) mode
467   = checkSlurped name                   `thenRn` \ already_slurped ->
468     if already_slurped then
469 --      traceRn (sep [text "Already slurped:", ppr name])       `thenRn_`
470         returnRn Nothing        -- Already dealt with
471     else
472     if isWiredInName name then
473         getWiredInDecl name mode
474     else 
475        getIfacesRn              `thenRn` \ ifaces ->
476        let
477          mod = nameModule name
478        in
479        if mod == iMod ifaces then    -- Don't bring in decls from
480           addWarnRn (importDeclWarn mod name loc) `thenRn_`
481 --        pprTrace "importDecl wierdness:" (ppr name) $
482           returnRn Nothing         -- the renamed module's own interface file
483                                    -- 
484        else
485        getNonWiredInDecl name loc mode
486 \end{code}
487
488 \begin{code}
489 getNonWiredInDecl :: Name -> SrcLoc -> RnMode -> RnMG (Maybe RdrNameHsDecl)
490 getNonWiredInDecl needed_name loc mode
491   = traceRn doc_str                             `thenRn_`
492     loadHomeInterface doc_str needed_name       `thenRn` \ ifaces ->
493     case lookupNameEnv (iDecls ifaces) needed_name of
494
495         -- Special case for data/newtype type declarations
496       Just (version, avail, TyClD tycl_decl, _) | isDataDecl tycl_decl
497         -> getNonWiredDataDecl needed_name version avail tycl_decl      `thenRn` \ (avail', maybe_decl) ->
498            recordSlurp (Just version) necessity avail'                  `thenRn_`
499            returnRn maybe_decl
500
501       Just (version,avail,decl,_)
502         -> recordSlurp (Just version) necessity avail   `thenRn_`
503            returnRn (Just decl)
504
505       Nothing ->        -- Can happen legitimately for "Optional" occurrences
506                    case necessity of { 
507                         Optional -> addWarnRn (getDeclWarn needed_name loc);
508                         other    -> addErrRn  (getDeclErr  needed_name loc)
509                    }                                            `thenRn_` 
510                    returnRn Nothing
511   where
512      necessity = modeToNecessity mode
513      doc_str = sep [ptext SLIT("need decl for"), ppr needed_name, ptext SLIT("needed at"), ppr loc]
514 \end{code}
515
516 @getWiredInDecl@ maps a wired-in @Name@ to what it makes available.
517 It behaves exactly as if the wired in decl were actually in an interface file.
518 Specifically,
519
520   *     if the wired-in name is a data type constructor or a data constructor, 
521         it brings in the type constructor and all the data constructors; and
522         marks as "occurrences" any free vars of the data con.
523
524   *     similarly for synonum type constructor
525
526   *     if the wired-in name is another wired-in Id, it marks as "occurrences"
527         the free vars of the Id's type.
528
529   *     it loads the interface file for the wired-in thing for the
530         sole purpose of making sure that its instance declarations are available
531
532 All this is necessary so that we know all types that are "in play", so
533 that we know just what instances to bring into scope.
534         
535 \begin{code}
536 getWiredInDecl name mode
537   = setModuleRn mod_name (
538         initRnMS emptyRnEnv new_mode get_wired
539     )                                           `thenRn` \ avail ->
540     recordSlurp Nothing necessity avail         `thenRn_`
541
542         -- Force in the home module in case it has instance decls for
543         -- the thing we are interested in.
544         --
545         -- Mini hack 1: no point for non-tycons/class; and if we
546         -- do this we find PrelNum trying to import PackedString,
547         -- because PrelBase's .hi file mentions PackedString.unpackString
548         -- But PackedString.hi isn't built by that point!
549         --
550         -- Mini hack 2; GHC is guaranteed not to have
551         -- instance decls, so it's a waste of time to read it
552         --
553         -- NB: We *must* look at the availName of the slurped avail, 
554         -- not the name passed to getWiredInDecl!  Why?  Because if a data constructor 
555         -- or class op is passed to getWiredInDecl we'll pull in the whole data/class
556         -- decl, and recordSlurp will record that fact.  But since the data constructor
557         -- isn't a tycon/class we won't force in the home module.  And even if the
558         -- type constructor/class comes along later, loadDecl will say that it's already
559         -- been slurped, so getWiredInDecl won't even be called.  Pretty obscure bug, this was.
560     let
561         main_name  = availName avail
562         main_is_tc = case avail of { AvailTC _ _ -> True; Avail _ -> False }
563         mod        = nameModule main_name
564         doc_str    = sep [ptext SLIT("need home module for wired in thing"), ppr name]
565     in
566     (if not main_is_tc || mod == pREL_GHC then
567         returnRn ()             
568     else
569         loadHomeInterface doc_str main_name     `thenRn_`
570         returnRn ()
571     )                                           `thenRn_`
572
573     returnRn Nothing            -- No declaration to process further
574   where
575     necessity = modeToNecessity mode
576     new_mode = case mode of 
577                         InterfaceMode _ -> mode
578                         SourceMode      -> vanillaInterfaceMode
579
580     get_wired | is_tycon                        -- ... a type constructor
581               = get_wired_tycon the_tycon
582
583               | maybeToBool maybe_data_con              -- ... a wired-in data constructor
584               = get_wired_tycon (dataConTyCon data_con)
585
586               | otherwise                       -- ... a wired-in non data-constructor
587               = get_wired_id the_id
588
589     mod_name             = nameModule name
590     maybe_wired_in_tycon = maybeWiredInTyConName name
591     is_tycon             = maybeToBool maybe_wired_in_tycon
592     maybe_wired_in_id    = maybeWiredInIdName    name
593     Just the_tycon       = maybe_wired_in_tycon
594     Just the_id          = maybe_wired_in_id
595     maybe_data_con       = isDataConId_maybe the_id
596     Just data_con        = maybe_data_con
597
598
599 get_wired_id id
600   = addImplicitOccsRn id_mentions       `thenRn_`
601     returnRn (Avail (getName id))
602   where
603     id_mentions = nameSetToList (namesOfType ty)
604     ty = idType id
605
606 get_wired_tycon tycon 
607   | isSynTyCon tycon
608   = addImplicitOccsRn (nameSetToList mentioned)         `thenRn_`
609     returnRn (AvailTC tc_name [tc_name])
610   where
611     tc_name     = getName tycon
612     (tyvars,ty) = getSynTyConDefn tycon
613     mentioned   = namesOfType ty `minusNameSet` mkNameSet (map getName tyvars)
614
615 get_wired_tycon tycon 
616   | otherwise           -- data or newtype
617   = addImplicitOccsRn (nameSetToList mentioned)         `thenRn_`
618     returnRn (AvailTC tycon_name (tycon_name : map getName data_cons))
619   where
620     tycon_name = getName tycon
621     data_cons  = tyConDataCons tycon
622     mentioned  = foldr (unionNameSets . namesOfType . dataConType) emptyNameSet data_cons
623 \end{code}
624
625
626     
627 %*********************************************************
628 %*                                                      *
629 \subsection{Getting what a module exports}
630 %*                                                      *
631 %*********************************************************
632
633 \begin{code}
634 getInterfaceExports :: Module -> RnMG Avails
635 getInterfaceExports mod
636   = loadInterface doc_str mod   `thenRn` \ ifaces ->
637     case lookupFM (iModMap ifaces) mod of
638         Nothing ->      -- Not there; it must be that the interface file wasn't found;
639                         -- the error will have been reported already.
640                         -- (Actually loadInterface should put the empty export env in there
641                         --  anyway, but this does no harm.)
642                       returnRn []
643
644         Just (_, _, avails) -> returnRn avails
645   where
646     doc_str = sep [pprModule mod, ptext SLIT("is directly imported")]
647 \end{code}
648
649
650 %*********************************************************
651 %*                                                      *
652 \subsection{Data type declarations are handled specially}
653 %*                                                      *
654 %*********************************************************
655
656 Data type declarations get special treatment.  If we import a data type decl
657 with all its constructors, we end up importing all the types mentioned in 
658 the constructors' signatures, and hence {\em their} data type decls, and so on.
659 In effect, we get the transitive closure of data type decls.  Worse, this drags
660 in tons on instance decls, and their unfoldings, and so on.
661
662 If only the type constructor is mentioned, then all this is a waste of time.
663 If any of the data constructors are mentioned then we really have to 
664 drag in the whole declaration.
665
666 So when we import the type constructor for a @data@ or @newtype@ decl, we
667 put it in the "deferred data/newtype decl" pile in Ifaces.  Right at the end
668 we slurp these decls, if they havn't already been dragged in by an occurrence
669 of a constructor.
670
671 \begin{code}
672 getNonWiredDataDecl needed_name 
673                     version
674                     avail@(AvailTC tycon_name _) 
675                     ty_decl@(TyData new_or_data context tycon tyvars condecls derivings pragmas src_loc)
676   |  needed_name == tycon_name
677   && opt_PruneTyDecls
678         -- don't prune newtypes, as the code generator may
679         -- want to peer inside a newtype type constructor
680         -- (ClosureInfo.fun_result_ty is the culprit.)
681   && not (new_or_data == NewType)
682   && not (nameUnique needed_name `elem` cCallishTyKeys)         
683         -- Hack!  Don't prune these tycons whose constructors
684         -- the desugarer must be able to see when desugaring
685         -- a CCall.  Ugh!
686
687   =     -- Need the type constructor; so put it in the deferred set for now
688     getIfacesRn                 `thenRn` \ ifaces ->
689     let
690         deferred_data_decls = iDefData ifaces
691         new_ifaces          = ifaces {iDefData = new_deferred_data_decls}
692
693         no_constr_ty_decl       = TyData new_or_data [] tycon tyvars [] derivings pragmas src_loc
694         new_deferred_data_decls = addToNameEnv deferred_data_decls tycon_name 
695                                                (nameModule tycon_name, no_constr_ty_decl)
696                 -- Nota bene: we nuke both the constructors and the context in the deferred decl.
697                 -- If we don't nuke the context then renaming the deferred data decls can give
698                 -- new unresolved names (for the classes).  This could be handled, but there's
699                 -- no point.  If the data type is completely abstract then we aren't interested
700                 -- its context.
701     in
702     setIfacesRn new_ifaces      `thenRn_`
703     returnRn (AvailTC tycon_name [tycon_name], Nothing)
704
705   | otherwise
706   =     -- Need a data constructor, so delete the data decl from the deferred set if it's there
707     getIfacesRn                 `thenRn` \ ifaces ->
708     let
709         deferred_data_decls = iDefData ifaces
710         new_ifaces          = ifaces {iDefData = new_deferred_data_decls}
711
712         new_deferred_data_decls = delFromNameEnv deferred_data_decls tycon_name
713     in
714     setIfacesRn new_ifaces      `thenRn_`
715     returnRn (avail, Just (TyClD ty_decl))
716 \end{code}
717
718 \begin{code}
719 getDeferredDataDecls :: RnMG [(Module, RdrNameTyClDecl)]
720 getDeferredDataDecls 
721   = getIfacesRn                 `thenRn` \ ifaces ->
722     let
723         deferred_list = nameEnvElts (iDefData ifaces)
724         trace_msg = hang (text "Slurping abstract data/newtype decls for: ")
725                         4 (ppr (map fst deferred_list))
726     in
727     traceRn trace_msg                   `thenRn_`
728     returnRn deferred_list
729 \end{code}
730
731
732 %*********************************************************
733 %*                                                      *
734 \subsection{Instance declarations are handled specially}
735 %*                                                      *
736 %*********************************************************
737
738 \begin{code}
739 getImportedInstDecls :: RnMG [(Module,RdrNameInstDecl)]
740 getImportedInstDecls
741   =     -- First load any special-instance modules that aren't aready loaded
742     getSpecialInstModules                       `thenRn` \ inst_mods ->
743     mapRn load_it inst_mods                     `thenRn_`
744
745         -- Now we're ready to grab the instance declarations
746         -- Find the un-gated ones and return them, 
747         -- removing them from the bag kept in Ifaces
748     getIfacesRn         `thenRn` \ ifaces ->
749     let
750         (insts, tycls_names) = iDefInsts ifaces
751
752                 -- An instance decl is ungated if all its gates have been slurped
753         select_ungated :: IfaceInst                                     -- A gated inst decl
754
755                        -> ([(Module, RdrNameInstDecl)], [IfaceInst])    -- Accumulator
756
757                        -> ([(Module, RdrNameInstDecl)],                 -- The ungated ones
758                            [IfaceInst])                                 -- Still gated, but with
759                                                                         -- depeleted gates
760         select_ungated (decl,gates) (ungated_decls, gated_decls)
761           | isEmptyNameSet remaining_gates
762           = (decl : ungated_decls, gated_decls)
763           | otherwise
764           = (ungated_decls, (decl, remaining_gates) : gated_decls)
765           where
766             remaining_gates = gates `minusNameSet` tycls_names
767
768         (un_gated_insts, still_gated_insts) = foldrBag select_ungated ([], []) insts
769         
770         new_ifaces = ifaces {iDefInsts = (listToBag still_gated_insts, tycls_names)}
771                                 -- NB: don't throw away tycls_names;
772                                 -- we may comre across more instance decls
773     in
774     traceRn (sep [text "getInstDecls:", fsep (map ppr (nameSetToList tycls_names))])    `thenRn_`
775     setIfacesRn new_ifaces      `thenRn_`
776     returnRn un_gated_insts
777   where
778     load_it mod = loadInterface (doc_str mod) mod
779     doc_str mod = sep [pprModule mod, ptext SLIT("is a special-instance module")]
780
781
782 getSpecialInstModules :: RnMG [Module]
783 getSpecialInstModules 
784   = getIfacesRn                                         `thenRn` \ ifaces ->
785     returnRn (iInstMods ifaces)
786
787 getImportedFixities :: RnMG FixityEnv
788 getImportedFixities
789   = getIfacesRn                                         `thenRn` \ ifaces ->
790     returnRn (iFixes ifaces)
791 \end{code}
792
793
794 %*********************************************************
795 %*                                                      *
796 \subsection{Keeping track of what we've slurped, and version numbers}
797 %*                                                      *
798 %*********************************************************
799
800 getImportVersions figures out what the "usage information" for this moudule is;
801 that is, what it must record in its interface file as the things it uses.
802 It records:
803         - anything reachable from its body code
804         - any module exported with a "module Foo".
805
806 Why the latter?  Because if Foo changes then this module's export list
807 will change, so we must recompile this module at least as far as
808 making a new interface file --- but in practice that means complete
809 recompilation.
810
811 What about this? 
812         module A( f, g ) where          module B( f ) where
813           import B( f )                   f = h 3
814           g = ...                         h = ...
815
816 Should we record B.f in A's usages?  In fact we don't.  Certainly, if
817 anything about B.f changes than anyone who imports A should be recompiled;
818 they'll get an early exit if they don't use B.f.  However, even if B.f
819 doesn't change at all, B.h may do so, and this change may not be reflected
820 in f's version number.  So there are two things going on when compiling module A:
821
822 1.  Are A.o and A.hi correct?  Then we can bale out early.
823 2.  Should modules that import A be recompiled?
824
825 For (1) it is slightly harmful to record B.f in A's usages, because a change in
826 B.f's version will provoke full recompilation of A, producing an identical A.o,
827 and A.hi differing only in its usage-version of B.f (which isn't used by any importer).
828
829 For (2), because of the tricky B.h question above, we ensure that A.hi is touched
830 (even if identical to its previous version) if A's recompilation was triggered by
831 an imported .hi file date change.  Given that, there's no need to record B.f in
832 A's usages.
833
834 On the other hand, if A exports "module B" then we *do* count module B among
835 A's usages, because we must recompile A to ensure that A.hi changes appropriately.
836
837 \begin{code}
838 getImportVersions :: Module                     -- Name of this module
839                   -> Maybe [IE any]             -- Export list for this module
840                   -> RnMG (VersionInfo Name)    -- Version info for these names
841
842 getImportVersions this_mod exports
843   = getIfacesRn                                 `thenRn` \ ifaces ->
844     let
845         mod_map   = iModMap ifaces
846         imp_names = iVSlurp ifaces
847
848         -- mv_map groups together all the things imported from a particular module.
849         mv_map, mv_map_mod :: FiniteMap Module (WhatsImported Name)
850
851         mv_map_mod = foldl add_mod emptyFM export_mods
852                 -- mv_map_mod records all the modules that have a "module M"
853                 -- in this module's export list with an "Everything" 
854
855         mv_map = foldl add_mv mv_map_mod imp_names
856                 -- mv_map adds the version numbers of things exported individually
857
858         mk_version_info (mod, local_versions)
859            = case lookupFM mod_map mod of
860                 Just (hif, version, _) -> (mod, version, local_versions)
861     in
862     returnRn (map mk_version_info (fmToList mv_map))
863   where
864      export_mods = case exports of
865                         Nothing -> []
866                         Just es -> [mod | IEModuleContents mod <- es, mod /= this_mod]
867
868      add_mv mv_map v@(name, version) 
869       = addToFM_C add_item mv_map mod (Specifically [v]) 
870         where
871          mod = nameModule name
872
873          add_item Everything        _ = Everything
874          add_item (Specifically xs) _ = Specifically (v:xs)
875
876      add_mod mv_map mod = addToFM mv_map mod Everything
877 \end{code}
878
879 \begin{code}
880 checkSlurped name
881   = getIfacesRn         `thenRn` \ ifaces ->
882     returnRn (name `elemNameSet` iSlurp ifaces)
883
884 getSlurpedNames :: RnMG NameSet
885 getSlurpedNames
886   = getIfacesRn         `thenRn` \ ifaces ->
887     returnRn (iSlurp ifaces)
888
889 recordSlurp maybe_version necessity avail
890   = {- traceRn (hsep [text "Record slurp:", pprAvail avail, 
891                                         -- NB PprForDebug prints export flag, which is too
892                                         -- strict; it's a knot-tied thing in RnNames
893                   case necessity of {Compulsory -> text "comp"; Optional -> text "opt" } ])     `thenRn_` 
894     -}
895     getIfacesRn         `thenRn` \ ifaces ->
896     let
897         Ifaces { iSlurp    = slurped_names,
898                  iVSlurp   = imp_names,
899                  iDefInsts = (insts, tycls_names) } = ifaces
900
901         new_slurped_names = addAvailToNameSet slurped_names avail
902
903         new_imp_names = case maybe_version of
904                            Just version -> (availName avail, version) : imp_names
905                            Nothing      -> imp_names
906
907                 -- Add to the names that will let in instance declarations;
908                 -- but only (a) if it's a type/class
909                 --          (b) if it's compulsory (unless the test flag opt_PruneInstDecls is off)
910         new_tycls_names = case avail of
911                                 AvailTC tc _  | not opt_PruneInstDecls || 
912                                                 case necessity of {Optional -> False; Compulsory -> True }
913                                               -> tycls_names `addOneToNameSet` tc
914                                 otherwise     -> tycls_names
915
916         new_ifaces = ifaces { iSlurp    = new_slurped_names,
917                               iVSlurp   = new_imp_names,
918                               iDefInsts = (insts, new_tycls_names) }
919     in
920     setIfacesRn new_ifaces
921 \end{code}
922
923
924 %*********************************************************
925 %*                                                      *
926 \subsection{Getting binders out of a declaration}
927 %*                                                      *
928 %*********************************************************
929
930 @getDeclBinders@ returns the names for a @RdrNameHsDecl@.
931 It's used for both source code (from @availsFromDecl@) and interface files
932 (from @loadDecl@).
933
934 It doesn't deal with source-code specific things: ValD, DefD.  They
935 are handled by the sourc-code specific stuff in RnNames.
936
937 \begin{code}
938 getDeclBinders :: (RdrName -> SrcLoc -> RnMG Name)      -- New-name function
939                 -> RdrNameHsDecl
940                 -> RnMG (Maybe AvailInfo)
941
942 getDeclBinders new_name (TyClD (TyData _ _ tycon _ condecls _ _ src_loc))
943   = new_name tycon src_loc                      `thenRn` \ tycon_name ->
944     getConFieldNames new_name condecls          `thenRn` \ sub_names ->
945     returnRn (Just (AvailTC tycon_name (tycon_name : nub sub_names)))
946         -- The "nub" is because getConFieldNames can legitimately return duplicates,
947         -- when a record declaration has the same field in multiple constructors
948
949 getDeclBinders new_name (TyClD (TySynonym tycon _ _ src_loc))
950   = new_name tycon src_loc              `thenRn` \ tycon_name ->
951     returnRn (Just (AvailTC tycon_name [tycon_name]))
952
953 getDeclBinders new_name (TyClD (ClassDecl _ cname _ sigs _ _ tname dname src_loc))
954   = new_name cname src_loc                      `thenRn` \ class_name ->
955
956         -- Record the names for the class ops
957     let
958         -- ignoring fixity declarations
959         nonfix_sigs = nonFixitySigs sigs
960     in
961     mapRn (getClassOpNames new_name) nonfix_sigs        `thenRn` \ sub_names ->
962
963     returnRn (Just (AvailTC class_name (class_name : sub_names)))
964
965 getDeclBinders new_name (SigD (IfaceSig var ty prags src_loc))
966   = new_name var src_loc                        `thenRn` \ var_name ->
967     returnRn (Just (Avail var_name))
968
969 getDeclBinders new_name (FixD _)  = returnRn Nothing
970 getDeclBinders new_name (ForD _)  = returnRn Nothing
971 getDeclBinders new_name (DefD _)  = returnRn Nothing
972 getDeclBinders new_name (InstD _) = returnRn Nothing
973
974 ----------------
975 getConFieldNames new_name (ConDecl con _ _ (RecCon fielddecls) src_loc : rest)
976   = mapRn (\n -> new_name n src_loc) (con:fields)       `thenRn` \ cfs ->
977     getConFieldNames new_name rest                      `thenRn` \ ns  -> 
978     returnRn (cfs ++ ns)
979   where
980     fields = concat (map fst fielddecls)
981
982 getConFieldNames new_name (ConDecl con _ _ condecl src_loc : rest)
983   = new_name con src_loc                `thenRn` \ n ->
984     (case condecl of
985       NewCon _ (Just f) -> 
986         new_name f src_loc `thenRn` \ new_f ->
987         returnRn [n,new_f]
988       _ -> returnRn [n])                `thenRn` \ nn ->
989     getConFieldNames new_name rest      `thenRn` \ ns -> 
990     returnRn (nn ++ ns)
991
992 getConFieldNames new_name [] = returnRn []
993
994 getClassOpNames new_name (ClassOpSig op _ _ src_loc) = new_name op src_loc
995 \end{code}
996
997 @getDeclSysBinders@ gets the implicit binders introduced by a decl.
998 A the moment that's just the tycon and datacon that come with a class decl.
999 They aren'te returned by getDeclBinders because they aren't in scope;
1000 but they *should* be put into the DeclsMap of this module.
1001
1002 \begin{code}
1003 getDeclSysBinders new_name (TyClD (ClassDecl _ cname _ sigs _ _ tname dname src_loc))
1004   = new_name dname src_loc                      `thenRn` \ datacon_name ->
1005     new_name tname src_loc                      `thenRn` \ tycon_name ->
1006     returnRn [tycon_name, datacon_name]
1007
1008 getDeclSysBinders new_name other_decl
1009   = returnRn []
1010 \end{code}
1011
1012 %*********************************************************
1013 %*                                                      *
1014 \subsection{Reading an interface file}
1015 %*                                                      *
1016 %*********************************************************
1017
1018 \begin{code}
1019 findAndReadIface :: SDoc -> Module -> RnMG (Maybe ParsedIface)
1020         -- Nothing <=> file not found, or unreadable, or illegible
1021         -- Just x  <=> successfully found and parsed 
1022
1023 findAndReadIface doc_str mod_name
1024   = traceRn trace_msg                   `thenRn_`
1025       -- we keep two maps for interface files,
1026       -- one for 'normal' ones, the other for .hi-boot files,
1027       -- hence the need to signal which kind we're interested.
1028     getModuleHiMap from_hi_boot         `thenRn` \ himap ->
1029     case (lookupFM himap (moduleString mod_name)) of
1030          -- Found the file
1031        Just fpath -> readIface fpath
1032          -- Hack alert!  When compiling PrelBase we have to load the
1033          -- decls for packCString# and friends; they are 'thin-air' Ids
1034          -- (see PrelInfo.lhs).  So if we don't find the HiFile we quietly
1035          -- look for a .hi-boot file instead, and use that
1036        Nothing |  not from_hi_boot && mod_name `elem` thinAirModules
1037                -> findAndReadIface doc_str (mkBootModule mod_name)
1038                | otherwise               
1039                -> traceRn (ptext SLIT("...failed"))     `thenRn_`
1040                   returnRn Nothing
1041   where
1042     hif          = moduleIfaceFlavour mod_name
1043     from_hi_boot = bootFlavour hif
1044
1045     trace_msg = sep [hsep [ptext SLIT("Reading"), 
1046                            if from_hi_boot then ptext SLIT("[boot]") else empty,
1047                            ptext SLIT("interface for"), 
1048                            pprModule mod_name <> semi],
1049                      nest 4 (ptext SLIT("reason:") <+> doc_str)]
1050 \end{code}
1051
1052 @readIface@ tries just the one file.
1053
1054 \begin{code}
1055 readIface :: String -> RnMG (Maybe ParsedIface) 
1056         -- Nothing <=> file not found, or unreadable, or illegible
1057         -- Just x  <=> successfully found and parsed 
1058 readIface file_path
1059   = ioToRnMG (hGetStringBuffer file_path)       `thenRn` \ read_result ->
1060     case read_result of
1061         Right contents    -> 
1062              case parseIface contents (mkSrcLoc (mkFastString file_path) 1) of
1063                   Failed err      -> failWithRn Nothing err 
1064                   Succeeded (PIface iface) -> 
1065                         if opt_D_show_rn_imports then
1066                            putDocRn (hcat[ptext SLIT("Read "), text file_path]) `thenRn_`
1067                            returnRn (Just iface)
1068                         else
1069                            returnRn (Just iface)
1070
1071         Left err ->
1072           if isDoesNotExistError err then
1073              returnRn Nothing
1074           else
1075              failWithRn Nothing (cannaeReadFile file_path err)
1076 \end{code}
1077
1078 %*********************************************************
1079 %*                                                       *
1080 \subsection{Utils}
1081 %*                                                       *
1082 %*********************************************************
1083
1084 @mkSearchPath@ takes a string consisting of a colon-separated list
1085 of directories and corresponding suffixes, and turns it into a list
1086 of (directory, suffix) pairs.  For example:
1087
1088 \begin{verbatim}
1089  mkSearchPath "foo%.hi:.%.p_hi:baz%.mc_hi"
1090    = [("foo",".hi"),( ".", ".p_hi"), ("baz",".mc_hi")]
1091 \begin{verbatim}
1092
1093 \begin{code}
1094 mkSearchPath :: Maybe String -> SearchPath
1095 mkSearchPath Nothing = [(".",".hi")]
1096 mkSearchPath (Just s)
1097   = go s
1098   where
1099     go "" = []
1100     go s  = 
1101       case span (/= '%') s of
1102        (dir,'%':rs) ->
1103          case span (/= ':') rs of
1104           (hisuf,_:rest) -> (dir,hisuf):go rest
1105           (hisuf,[])     -> [(dir,hisuf)]
1106 \end{code}
1107
1108 %*********************************************************
1109 %*                                                       *
1110 \subsection{Errors}
1111 %*                                                       *
1112 %*********************************************************
1113
1114 \begin{code}
1115 noIfaceErr filename
1116   = hcat [ptext SLIT("Could not find valid interface file "), 
1117           quotes (pprModule filename)]
1118
1119 cannaeReadFile file err
1120   = hcat [ptext SLIT("Failed in reading file: "), 
1121           text file, 
1122           ptext SLIT("; error="), 
1123           text (show err)]
1124
1125 getDeclErr name loc
1126   = sep [ptext SLIT("Failed to find interface decl for") <+> quotes (ppr name), 
1127          ptext SLIT("needed at") <+> ppr loc]
1128
1129 getDeclWarn name loc
1130   = sep [ptext SLIT("Failed to find (optional) interface decl for") <+> quotes (ppr name),
1131          ptext SLIT("desired at") <+> ppr loc]
1132
1133 importDeclWarn mod name loc
1134   = sep [ptext SLIT("Compiler tried to import decl from interface file with same name as module."), 
1135          ptext SLIT("(possible cause: module name clashes with interface file already in scope.)")
1136         ] $$
1137     hsep [ptext SLIT("Interface:"), quotes (pprModule mod), comma, ptext SLIT("name:"), quotes (ppr name), 
1138           comma, ptext SLIT("desired at:"), ppr loc
1139          ]
1140
1141 \end{code}