Skip to content
GitLab
Projects
Groups
Snippets
Help
Loading...
Help
What's new
10
Help
Support
Community forum
Keyboard shortcuts
?
Submit feedback
Sign in / Register
Toggle navigation
Open sidebar
Tobias Decking
GHC
Commits
ae0b2a9e
Commit
ae0b2a9e
authored
Oct 04, 2004
by
simonpj
Browse files
Options
Browse Files
Download
Email Patches
Plain Diff
[project @ 2004-10-04 09:28:00 by simonpj]
Better reporting of duplicate top-level defns
parent
864388a3
Changes
3
Hide whitespace changes
Inline
Side-by-side
Showing
3 changed files
with
13 additions
and
12 deletions
+13
-12
ghc/compiler/rename/RnEnv.lhs
ghc/compiler/rename/RnEnv.lhs
+3
-1
ghc/compiler/rename/RnExpr.lhs
ghc/compiler/rename/RnExpr.lhs
+1
-0
ghc/compiler/rename/RnNames.lhs
ghc/compiler/rename/RnNames.lhs
+9
-11
No files found.
ghc/compiler/rename/RnEnv.lhs
View file @
ae0b2a9e
...
...
@@ -56,6 +56,7 @@ import BasicTypes ( IPName, mapIPName )
import SrcLoc ( SrcSpan, srcSpanStart, Located(..), eqLocated, unLoc,
srcLocSpan, getLoc, combineSrcSpans, srcSpanStartLine, srcSpanEndLine )
import Outputable
import Util ( sortLe )
import ListSetOps ( removeDups )
import List ( nubBy )
import CmdLineOpts
...
...
@@ -759,5 +760,6 @@ dupNamesErr descriptor located_names
big_loc = foldr1 combineSrcSpans locs
one_line = srcSpanStartLine big_loc == srcSpanEndLine big_loc
locations | one_line = empty
| otherwise = ptext SLIT("Bound at:") <+> vcat (map ppr locs)
| otherwise = ptext SLIT("Bound at:") <+>
vcat (map ppr (sortLe (<=) locs))
\end{code}
ghc/compiler/rename/RnExpr.lhs
View file @
ae0b2a9e
...
...
@@ -831,6 +831,7 @@ rnMDoStmts stmts
in
returnM stmts_w_fvs
where
doc = text "In a recursive mdo-expression"
...
...
ghc/compiler/rename/RnNames.lhs
View file @
ae0b2a9e
...
...
@@ -50,7 +50,7 @@ import RdrName ( RdrName, rdrNameOcc, setRdrNameSpace,
import Outputable
import Maybes ( isNothing, catMaybes, mapCatMaybes, seqMaybe )
import SrcLoc ( noSrcLoc, Located(..), mkGeneralSrcSpan,
unLoc, noLoc, srcLocSpan, SrcSpan )
unLoc, noLoc, srcLocSpan,
combineSrcSpans,
SrcSpan )
import BasicTypes ( DeprecTxt )
import ListSetOps ( removeDups )
import Util ( sortLe, notNull, isSingleton )
...
...
@@ -1002,17 +1002,15 @@ exportClashErr global_env name1 name2 ie1 ie2
[] -> pprPanic "exportClashErr" (ppr name)
addDupDeclErr :: [Name] -> TcRn ()
addDupDeclErr (n:ns)
= addErrAt (srcLocSpan (nameSrcLoc n)) $
vcat [ptext SLIT("Multiple declarations of") <+> quotes (ppr n),
nest 2 (ptext SLIT("other declarations at:")),
nest 4 (vcat (map ppr sorted_locs))]
addDupDeclErr names
= addErrAt big_loc $
vcat [ptext SLIT("Multiple declarations of") <+> quotes (ppr name1),
ptext SLIT("Declared at:") <+> vcat (map ppr sorted_locs)]
where
sorted_locs = sortLe occ'ed_before (map nameSrcLoc ns)
occ'ed_before a b = case compare a b of
LT -> True
EQ -> True
GT -> False
locs = map nameSrcLoc names
big_loc = foldr1 combineSrcSpans (map srcLocSpan locs)
name1 = head names
sorted_locs = sortLe (<=) (sortLe (<=) locs)
dupExportWarn occ_name ie1 ie2
= hsep [quotes (ppr occ_name),
...
...
Write
Preview
Markdown
is supported
0%
Try again
or
attach a new file
.
Attach a file
Cancel
You are about to add
0
people
to the discussion. Proceed with caution.
Finish editing this message first!
Cancel
Please
register
or
sign in
to comment