Skip to content

Commit

Permalink
Re-jig the reporting of names bound multiple times
Browse files Browse the repository at this point in the history
Fixes Trac #7164

MERGED from commit 2c6d11f
  • Loading branch information
Simon Peyton Jones authored and pcapriotti committed Aug 31, 2012
1 parent 66cb7e7 commit 87511d1
Show file tree
Hide file tree
Showing 4 changed files with 20 additions and 16 deletions.
21 changes: 10 additions & 11 deletions compiler/basicTypes/RdrName.lhs
Original file line number Diff line number Diff line change
Expand Up @@ -585,26 +585,25 @@ mkGlobalRdrEnv gres
(nameOccName (gre_name gre))
gre
findLocalDupsRdrEnv :: GlobalRdrEnv -> [OccName] -> (GlobalRdrEnv, [[Name]])
findLocalDupsRdrEnv :: GlobalRdrEnv -> [OccName] -> [[Name]]
-- ^ For each 'OccName', see if there are multiple local definitions
-- for it. If so, remove all but one (to suppress subsequent error messages)
-- for it; return a list of all such
-- and return a list of the duplicate bindings
findLocalDupsRdrEnv rdr_env occs
= go rdr_env [] occs
where
go rdr_env dups [] = (rdr_env, dups)
go _ dups [] = dups
go rdr_env dups (occ:occs)
= case filter isLocalGRE gres of
[] -> WARN( True, ppr occ <+> ppr rdr_env )
go rdr_env dups occs -- Weird! No binding for occ
[_] -> go rdr_env dups occs -- The common case
dup_gres -> go (extendOccEnv rdr_env occ (head dup_gres : nonlocal_gres))
(map gre_name dup_gres : dups)
occs
[] -> go rdr_env dups occs
[_] -> go rdr_env dups occs -- The common case
dup_gres -> go rdr_env' (map gre_name dup_gres : dups) occs
where
gres = lookupOccEnv rdr_env occ `orElse` []
nonlocal_gres = filterOut isLocalGRE gres
rdr_env' = delFromOccEnv rdr_env occ
-- The delFromOccEnv avoids repeating the same
-- complaint twice, when occs itself has a duplicate
-- which is a common case
insertGRE :: GlobalRdrElt -> [GlobalRdrElt] -> [GlobalRdrElt]
insertGRE new_g [] = [new_g]
Expand Down
3 changes: 2 additions & 1 deletion compiler/main/HscTypes.lhs
Original file line number Diff line number Diff line change
Expand Up @@ -1116,7 +1116,8 @@ mkPrintUnqualified dflags env = (qual_name, qual_mod)
then NameNotInScope1
else NameNotInScope2

| otherwise = panic "mkPrintUnqualified"
| otherwise = NameNotInScope1 -- Can happen if 'f' is bound twice in the module
-- Eg f = True; g = 0; f = False
where
mod = nameModule name
occ = nameOccName name
Expand Down
7 changes: 5 additions & 2 deletions compiler/rename/RnEnv.lhs
Original file line number Diff line number Diff line change
Expand Up @@ -1608,11 +1608,14 @@ addUnusedWarning name span msg
\begin{code}
addNameClashErrRn :: RdrName -> [GlobalRdrElt] -> RnM ()
addNameClashErrRn rdr_name names
addNameClashErrRn rdr_name gres
| all isLocalGRE gres -- If there are two or more *local* defns, we'll have reported
= return () -- that already, and we don't want an error cascade
| otherwise
= addErr (vcat [ptext (sLit "Ambiguous occurrence") <+> quotes (ppr rdr_name),
ptext (sLit "It could refer to") <+> vcat (msg1 : msgs)])
where
(np1:nps) = names
(np1:nps) = gres
msg1 = ptext (sLit "either") <+> mk_ref np1
msgs = [ptext (sLit " or") <+> mk_ref np | np <- nps]
mk_ref gre = sep [quotes (ppr (gre_name gre)) <> comma, pprNameProvenance gre]
Expand Down
5 changes: 3 additions & 2 deletions compiler/rename/RnNames.lhs
Original file line number Diff line number Diff line change
Expand Up @@ -414,10 +414,11 @@ extendGlobalRdrEnvRn avails new_fixities
rdr_env3 = foldl extendGlobalRdrEnv rdr_env2 gres
fix_env' = foldl extend_fix_env fix_env gres
(rdr_env', dups) = findLocalDupsRdrEnv rdr_env3 new_occs
dups = findLocalDupsRdrEnv rdr_env3 new_occs
gbl_env' = gbl_env { tcg_rdr_env = rdr_env', tcg_fix_env = fix_env' }
gbl_env' = gbl_env { tcg_rdr_env = rdr_env3, tcg_fix_env = fix_env' }
; traceRn (text "extendGlobalRdrEnvRn dups" <+> (ppr dups))
; mapM_ addDupDeclErr dups
; traceRn (text "extendGlobalRdrEnvRn" <+> (ppr new_fixities $$ ppr fix_env $$ ppr fix_env'))
Expand Down

0 comments on commit 87511d1

Please sign in to comment.