Skip to content
Snippets Groups Projects
Commit ac398378 authored by sof's avatar sof
Browse files

[project @ 1999-09-15 13:48:25 by sof]

When constructing vanilla modules from ModuleNames, consult the HiMaps
to make sure we're using the 'right' kind of Module (i.e., it has got
the DLL flag correctly set.)
parent 51c592c2
No related branches found
No related tags found
No related merge requests found
......@@ -63,7 +63,7 @@ newImportedGlobalName mod_name occ mod
in
case lookupFM cache key of
Just name -> returnRn name
Nothing -> setNameSupplyRn (us', inst_ns, new_cache) `thenRn_`
Nothing -> setNameSupplyRn (us', inst_ns, new_cache) `thenRn_`
returnRn name
where
(us', us1) = splitUniqSupply us
......@@ -90,7 +90,8 @@ newImportedBinder mod rdr_name
-- Make an imported global name, checking first to see if it's in the cache
mkImportedGlobalName :: ModuleName -> OccName -> RnM d Name
mkImportedGlobalName mod_name occ
= newImportedGlobalName mod_name occ (mkVanillaModule mod_name)
= lookupModuleRn mod_name `thenRn` \ mod ->
newImportedGlobalName mod_name occ mod --(mkVanillaModule mod_name)
mkImportedGlobalFromRdrName rdr_name
| isQual rdr_name
......
......@@ -40,11 +40,11 @@ import Name ( Name, OccName, NamedThing(..),
decode, mkLocalName
)
import Module ( Module, ModuleName, ModuleHiMap, SearchPath, WhereFrom,
mkModuleHiMaps, moduleName
mkModuleHiMaps, moduleName, mkVanillaModule, mkSearchPath
)
import NameSet
import RdrName ( RdrName, dummyRdrVarName, rdrNameOcc )
import CmdLineOpts ( opt_D_dump_rn_trace, opt_IgnoreIfacePragmas )
import CmdLineOpts ( opt_D_dump_rn_trace, opt_IgnoreIfacePragmas, opt_HiMap )
import PrelInfo ( builtinNames )
import TysWiredIn ( boolTyCon )
import SrcLoc ( SrcLoc, mkGeneratedSrcLoc )
......@@ -445,11 +445,12 @@ renameSourceCode mod_name name_supply m
-- only do any I/O if we need to read in a fixity declaration;
-- and that doesn't happen in pragmas etc
mkModuleHiMaps (mkSearchPath opt_HiMap) >>= \ himaps ->
newIORef name_supply >>= \ names_var ->
newIORef (emptyBag,emptyBag) >>= \ errs_var ->
let
rn_down = RnDown { rn_loc = mkGeneratedSrcLoc, rn_ns = names_var,
rn_errs = errs_var,
rn_errs = errs_var, rn_hi_maps = himaps,
rn_mod = mod_name }
s_down = SDown { rn_mode = InterfaceMode,
-- So that we can refer to PrelBase.True etc
......@@ -726,3 +727,13 @@ getHiMaps :: RnM d (ModuleHiMap, ModuleHiMap)
getHiMaps (RnDown {rn_hi_maps = himaps}) _
= return himaps
\end{code}
\begin{code}
lookupModuleRn :: ModuleName -> RnM d Module
lookupModuleRn x =
getHiMaps `thenRn` \ (himap, _) ->
case lookupFM himap x of
Nothing -> returnRn (mkVanillaModule x)
Just (_,x) -> returnRn x
\end{code}
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment