Generating better type-error messages is a hoary chestnut, but Herbert brought my attention to this thread on reddit, which has the following idea.
At the moment, from
module Foo where addThree = \x -> x + 3 :: Int y = addThree $ Just 5
we get this error:
Foo.hs:2:20 Couldn't match expected type `Int' with actual type `Maybe a0' In the return type of a call of `Just' In the second argument of `($)', namely `Just 5' In the expression: addThree $ Just 5
Maybe we could generate this instead
Foo.hs:2:20 inferred: "Just 5" has type "Maybe a0" expected: second argument of "($)" must have type "Int" in the expression: addThree $ Just 5
Trac metadata
Trac field
Value
Version
7.8.2
Type
Bug
TypeOfFailure
OtherFailure
Priority
normal
Resolution
Unresolved
Component
Compiler
Test case
Differential revisions
BlockedBy
Related
Blocking
CC
Operating system
Architecture
Edited
To upload designs, you'll need to enable LFS and have an admin enable hashed storage. More information
Child items
...
Show closed items
Linked items
0
Link issues together to show that they're related or that one is blocking others.
Learn more.
I like this, and think the second set of output reads much, much better. Bonus points: use ANSI terminal colors to highlight some key words in the output, such as "Warning" or "Error" should they exist.
Here's an error that a noob making a subtle typo might get from GHC:
Prelude> map 1 [1..5]<interactive>:2:1: Could not deduce (Num (a0 -> b)) arising from the ambiguity check for ‛it’ from the context (Num (a -> b), Num a, Enum a) bound by the inferred type for ‛it’: (Num (a -> b), Num a, Enum a) => [b] at <interactive>:2:1-12 The type variable ‛a0’ is ambiguous When checking that ‛it’ has the inferred type ‛forall a b. (Num (a -> b), Num a, Enum a) => [b]’ Probable cause: the inferred type is ambiguous
I wholeheartedly agree that the information needs to be presented in a way that's easier to digest.
For what should be a really simple error, I really have to stare that down to understand what it's actually trying to say ...
Despite the very general ticket title, let’s not confalte multiple errors. The original ticket was a about a type mismatch (inferred vs. expected). The example by schlyer is about an ambiguous type in the GHCi prompt. Note that with some more instances added, map 1 [1..5] would type check!
This seems like a nice and easy ticket to handle by a newcomer.
The function to change is misMatchMsg in compiler/typecheck/TcErrors.hs.
Don't forget to update the expected test output. Use 'make accept', see Building/RunningTests/Updating. Please make sure you get all of them (grep for the old error message).
While I love the the proposal in the ticket, I feel that a purely textual change to the error message could be a great boon without changing a single line of code.
"Expected" versus "actual" don't really the nature of the problem. For example, what is the type of foo in the following
foo :: Intfoo = "Howdy!"
Is foo actually an Int, since that was declared? Did the compiler expect foo to be a String, since that's what we passed it? Or is foo actually a "String", since that's what it contained, but the compiler expected a Int, since that's what we told it would be contained?
Perhaps just changing
Couldn't match expected type 'Foo' with actual type 'Bar'
to
Couldn't match declared type 'Foo' against a value of type `Bar'
The error there would not be about the type of foo, though. It would be about the type of "Howdy!".
Foo.hs:4:7: Couldn't match expected type ‘Int’ with actual type ‘[Char]’ In the expression: "Howdy!" In an equation for ‘foo’: foo = "Howdy!"
The "actual type" is ... the actual type of the expression "Howdy!" that the compiler points out. The "expected type" is the type expected from the context, that is, the type the expression would have to have for the whole thing to type check. I know lots of people find this confusing but I have never been able to understand why...
I wonder if it would help at all to just reverse the order of the two, that is,
Couldn't match actual type ‘[Char]’ with expected type ‘Int’ In the expression: "Howdy!"
Presumably the programmer has a strong association between the expression and its (actual) type, and then can work out what "expected type" refers to by elimination.
I'm also not that attached to the phrase "expected type". We could be more explicit and say something like "type ‘Int’ expected from context". I think the phrase "actual type" is quite good, though.
The trouble with "declared type" is that it often isn't declared. Consider
not 'c'
The actual type of 'c' is Char, but the type expected by the context (the call of not) is Bool. But it'd be confusing to say that Bool was the "declared" type!
Switching the order as Reid suggests in ticket:9173#comment:107699 would be easy, and I can see that it might help. Do others like that?
I'd also be ok with saying "type expected by the context" instead of just "expected". That longer phrase would also suggest putting it second.
Foo.hs:4:7: Couldn't match expected type ‘Int’ with actual type ‘[Char]’ In the expression: "Howdy!" In an equation for ‘foo’: foo = "Howdy!"
This example reminded me that sometimes the phrase "In the expression" is confusing to me. It seems that the phrase *should* be "Of the expression". Using 'in' makes me expect that the error message is referring to some particular component of the expression, rather than the whole thing.
It's a small incongruence, but it's big enough to force me to stop thinking about code and start thinking about the possible meanings of the error message.
Switching the order as Reid suggests in ticket:9173#comment:107699 would be easy, and I can see that it might help. Do others like that?
I'd also be ok with saying "type expected by the context" instead of just "expected". That longer phrase would also suggest putting it second.
+1. E.g.:
foo.hs:1:11: Couldn't match actual type ‘Char’ with type expected by context, ‘Bool’ In the first argument of ‘not’, namely ‘'c'’ In the expression: not 'c' In an equation for ‘foo’: foo = not 'c'
(I recall now that "In the expression" is used because the message often *does* refer to a component of the whole expression. Still, I think it would be nice if it switched to "In the expression" when referring to the whole thing.)
Once D808 gets merged (could be today! but more likely in 2-3), printing out the expression that has the bad type will be much easier, as I've restructured how that information sloshes around internally. So that will be a viable improvement very soon.