Skip to content
Snippets Groups Projects
Commit 6cea635a authored by Simon Peyton Jones's avatar Simon Peyton Jones
Browse files

[project @ 1998-01-29 12:46:11 by simonpj]

Fix interaction of "hiding" on import with "module M" on export
parent 9e999371
No related branches found
No related tags found
No related merge requests found
......@@ -484,16 +484,29 @@ pprFixityProvenance (fixity, how_in_scope) = ppr how_in_scope
=============== Avails ================
=============== ExportAvails ================
\begin{code}
mkExportAvails :: Bool -> Module -> [AvailInfo] -> ExportAvails
mkExportAvails unqualified_import mod_name avails
mkExportAvails :: Module -> Bool -> GlobalNameEnv -> [AvailInfo] -> ExportAvails
mkExportAvails mod_name unqual_imp name_env avails
= (mod_avail_env, entity_avail_env)
where
-- The "module M" syntax only applies to *unqualified* imports (1.4 Report, Section 5.1.1)
mod_avail_env | unqualified_import = unitFM mod_name avails
| otherwise = emptyFM
mod_avail_env = unitFM mod_name unqual_avails
-- unqual_avails is the Avails that are visible in *unqualfied* form
-- (1.4 Report, Section 5.1.1)
-- For example, in
-- import T hiding( f )
-- we delete f from avails
unqual_avails | not unqual_imp = [] -- Short cut when no unqualified imports
| otherwise = [prune avail | avail <- avails]
prune (Avail n) | unqual_in_scope n = Avail n
prune (Avail n) | otherwise = NotAvailable
prune (AvailTC n ns) = AvailTC n (filter unqual_in_scope ns)
unqual_in_scope n = Unqual (nameOccName n) `elemFM` name_env
entity_avail_env = listToUFM [ (name,avail) | avail <- avails,
name <- availEntityNames avail]
......@@ -556,8 +569,8 @@ filterAvail ie@(IEThingWith want wants) avail@(AvailTC n ns)
avail_occs = map nameOccName ns
wanted_occs = map rdrNameOcc (want:wants)
filterAvail (IEThingAbs _) (AvailTC n ns)
| n `elem` ns = AvailTC n [n]
filterAvail (IEThingAbs _) (AvailTC n ns) = ASSERT( n `elem` ns )
AvailTC n [n]
filterAvail (IEThingAbs _) avail@(Avail n) = avail -- Type synonyms
......
......@@ -313,7 +313,7 @@ qualifyImports this_mod qual_imp unqual_imp as_mod hides
fixity_env = foldl (add_fixity name_env2) emptyFixityEnv fixities
-- Create the export-availability info
export_avails = mkExportAvails unqual_imp qual_mod avails
export_avails = mkExportAvails qual_mod unqual_imp name_env2 avails
in
returnRn (RnEnv name_env2 fixity_env, export_avails)
where
......
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