Skip to content
GitLab
Projects
Groups
Snippets
/
Help
Help
Support
Community forum
Keyboard shortcuts
?
Submit feedback
Sign in / Register
Toggle navigation
Menu
Open sidebar
jberryman
GHC
Commits
4417e97d
Commit
4417e97d
authored
Jan 30, 2006
by
simonpj@microsoft.com
Browse files
Improve error messsage when argument count varies
parent
a0f8de19
Changes
1
Hide whitespace changes
Inline
Side-by-side
ghc/compiler/typecheck/TcMatches.lhs
View file @
4417e97d
...
...
@@ -44,7 +44,7 @@ import Id ( idType, mkLocalId )
import TyCon ( TyCon )
import Util ( isSingleton )
import Outputable
import SrcLoc ( Located(..) )
import SrcLoc ( Located(..)
, getLoc
)
import ErrUtils ( Message )
import List ( nub )
...
...
@@ -74,7 +74,7 @@ tcMatchesFun fun_name matches exp_ty
-- sensible location. Note: we have to do this odd
-- ann-grabbing, because we don't always have annotations in
-- hand when we call tcMatchesFun...
check
Tc (sameNoOfArgs matches) (varyingArgsErr
fun_name matches
)
check
Args
fun_name matches
-- ToDo: Don't use "expected" stuff if there ain't a type signature
-- because inconsistency between branches
...
...
@@ -489,18 +489,23 @@ tcMDoStmt tc_rhs ctxt stmt res_ty thing_inside
number of args are used in each equation.
\begin{code}
sameNoOfArgs :: MatchGroup Name -> Bool
sameNoOfArgs (MatchGroup matches _)
= isSingleton (nub (map args_in_match matches))
checkArgs :: Name -> MatchGroup Name -> TcM ()
checkArgs fun (MatchGroup (match1:matches) _)
| null bad_matches = return ()
| otherwise
= failWithTc (vcat [ptext SLIT("Equations for") <+> quotes (ppr fun) <+>
ptext SLIT("have different numbers of arguments"),
nest 2 (ppr (getLoc match1)),
nest 2 (ppr (getLoc (head bad_matches)))])
where
n_args1 = args_in_match match1
bad_matches = [m | m <- matches, args_in_match m /= n_args1]
args_in_match :: LMatch Name -> Int
args_in_match (L _ (Match pats _ _)) = length pats
\end{code}
\begin{code}
varyingArgsErr name matches
= sep [ptext SLIT("Varying number of arguments for function"), quotes (ppr name)]
matchCtxt ctxt match = hang (ptext SLIT("In") <+> pprMatchContext ctxt <> colon)
4 (pprMatch ctxt match)
...
...
Write
Preview
Supports
Markdown
0%
Try again
or
attach a new 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