Feedback on Error messages in ghc.

Hello, I read the summary of the survey and noticed you wanted feedback on where error messages could be improved. I looked up some (simple) examples of type errors and ran them through ghc. I do not make any claims to be an HCI expert, just a mere mortal with an opinion. Code: 1 module Test2 where 2 3 fib n = if (3 > n) then 1 else (fib (n - 1) + fib (n - 2)) 4 k = fib 's' Error message: Test2.hs:4: No instance for (Num Char) arising from use of `fib' at Test2.hs:4 In the definition of `k': k = fib 's' This isn't a bad error message in my humble opinion, it does pinpoint that I'm doing something wrong in line 4, and that there isn't an instance for Num Char doesn't come as a surprise. However I think it could have been more helpful by telling me that I tried to pass a Char to a function which expected an (Ord a, Num a) => a as its parameter. Code: 1 module Test4 where 2 3 k :: Int -> Int 4 k l = 2.0*l Error message: Test4.hs:4: No instance for (Fractional Int) arising from the literal `2.0' at Test4.hs:4 In the first argument of `(*)', namely `2.0' In the definition of `k': k l = 2.0 * l One reason this kind of error could happen is an inexperienced user declaring the wrong type for his function, or not knowing that 2.0 would be interpreted as a Fractional. Code: 1 module Test7 where 2 3 len' xs = head (xs) + (length xs) 4 o = len' "GH" Error message: Test7.hs:4: Couldn't match `Int' against `Char' Expected type: [Int] Inferred type: [Char] In the first argument of `len'', namely `"GH"' In the definition of `o': o = len' "GH" I ran this through Hugs version November 2002 and got this error message: ERROR "Test7.hs":4 - Type error in application *** Expression : len' "GH" *** Term : "GH" *** Type : String *** Does not match : [Int] I find the Hugs message more clear, but that might be my background. Code: 1 module Test8 where 2 3 f = head 3 Error message: Test8.hs:3: No instance for (Num [a]) arising from the literal `3' at Test8.hs:3 Possible cause: the monomorphism restriction applied to the following: f :: a (bound at Test8.hs:3) Probable fix: give these definition(s) an explicit type signature In the first argument of `head', namely `3' In the definition of `f': f = head 3 This one I find outright scary. For "wrong = div 3 8 + 1/2" it gives an error message that somewhat helps me guess the error, but the above doesn't even come close to helping me. / Peter

greetings. i have to agree with Peter. it's really no fun to read the error messages. i do not have a big problem with those; but i'm not a newbie anymore, and as newbie... i always just understood nothing more than that single given LINENUMBER within all that output-spam. well, most times it was enough. the trick is: to throw the code against the --Wall tests whether it is al dente or crumbly. the solution is to type the types and to look about where the bugs are running. hey, of course, they like crumbs. ;-) especially for newbies it is really confusing, that the compiler output does not always show the real position of the bug (like in imperative languages), but the first found abnormal behaviour that is caused by that bug (like in runtime errors). now that i saw that clean hugs output, i thought about it a little bit more: one does not need pages of error-description written in the style of... juristic blah, but a clear description about what's wrong and maybe some hints to solve it. in that given example
1 module Test7 where 2 3 len' xs = head (xs) + (length xs) 4 o = len' "GH"
i would prefer an output like this: TYPE MISMATCH in "Test7.hs": line 4, col 5 in Expression : len' "GH" between Function : len' and Parameter : "GH" with Types :: [Int] -> [Int] :: [Char] HINT: type of : (len') is caused by missing explicit type declaration len' :: [Int] -> [Int] well, if we replace ("GH") with (f x) and (len') with (g y) then it should look like TYPE MISMATCH in "Test7.hs": line 4, col 5 in Expression : g y (f x) between Function : g y and Parameter : (f x) with Types :: [Int] -> [Int] :: [Char] HINT: type of : (g y) is caused by g :: a -> [a] -> [a] y :: Int HINT: type of : (f x) is caused by f :: X -> String x :: X HINT: expression : f could be mistaken. (Compile with --Wall for more hints.) well, i do not know how hard it is to implement that, but at least without hints it is less irritating than the old style. - Marc Am Dienstag, 28. Juni 2005 21:43 schrieb Peter A Jonsson:
Hello,
I read the summary of the survey and noticed you wanted feedback on where error messages could be improved. I looked up some (simple) examples of type errors and ran them through ghc. I do not make any claims to be an HCI expert, just a mere mortal with an opinion.
Code:
1 module Test2 where 2 3 fib n = if (3 > n) then 1 else (fib (n - 1) + fib (n - 2)) 4 k = fib 's'
Error message:
Test2.hs:4: No instance for (Num Char) arising from use of `fib' at Test2.hs:4 In the definition of `k': k = fib 's'
This isn't a bad error message in my humble opinion, it does pinpoint that I'm doing something wrong in line 4, and that there isn't an instance for Num Char doesn't come as a surprise. However I think it could have been more helpful by telling me that I tried to pass a Char to a function which expected an (Ord a, Num a) => a as its parameter.
Code:
1 module Test4 where 2 3 k :: Int -> Int 4 k l = 2.0*l
Error message:
Test4.hs:4: No instance for (Fractional Int) arising from the literal `2.0' at Test4.hs:4 In the first argument of `(*)', namely `2.0' In the definition of `k': k l = 2.0 * l
One reason this kind of error could happen is an inexperienced user declaring the wrong type for his function, or not knowing that 2.0 would be interpreted as a Fractional.
Code:
1 module Test7 where 2 3 len' xs = head (xs) + (length xs) 4 o = len' "GH"
Error message:
Test7.hs:4: Couldn't match `Int' against `Char' Expected type: [Int] Inferred type: [Char] In the first argument of `len'', namely `"GH"' In the definition of `o': o = len' "GH"
I ran this through Hugs version November 2002 and got this error message:
ERROR "Test7.hs":4 - Type error in application *** Expression : len' "GH" *** Term : "GH" *** Type : String *** Does not match : [Int]
I find the Hugs message more clear, but that might be my background.
Code:
1 module Test8 where 2 3 f = head 3
Error message:
Test8.hs:3: No instance for (Num [a]) arising from the literal `3' at Test8.hs:3 Possible cause: the monomorphism restriction applied to the following: f :: a (bound at Test8.hs:3) Probable fix: give these definition(s) an explicit type signature In the first argument of `head', namely `3' In the definition of `f': f = head 3
This one I find outright scary. For "wrong = div 3 8 + 1/2" it gives an error message that somewhat helps me guess the error, but the above doesn't even come close to helping me.
/ Peter
_______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

I don't disagree with the main thrust, but the idea that imperative language are, in general, better about error messages is not, in my opinion, true. There is a large variation, of course, but for certain types of errors in an imperative language the compiler simply can't get a correct handle on what is wrong (because of ambiguities that cannot be removed). I, and I'm sure everyone else, would always be in support of more detailed error messages, and I agree that the examples cited increase the clarity. In my opinion this increase is significant and worth doing. I just wanted to correct any assumption that imperative language don't suffer from error message problems. Fundamentally, they suffer more, and are in many cases impossible to fix. In my experience GHC error locations always have some relationship to the error in coding, although of course the error message may at times be hard to interpret because the programmer believes he has coded a function with a particular signature but, in fact, has coded the function with a different inferred type. (Of course we all always explicitly specify function signatures and avoid this problem entirely. :-) ) Marc A. Ziegert wrote:
greetings.
i have to agree with Peter. it's really no fun to read the error messages.
i do not have a big problem with those; but i'm not a newbie anymore, and as newbie... i always just understood nothing more than that single given LINENUMBER within all that output-spam. well, most times it was enough.
the trick is: to throw the code against the --Wall tests whether it is al dente or crumbly. the solution is to type the types and to look about where the bugs are running. hey, of course, they like crumbs. ;-)
especially for newbies it is really confusing, that the compiler output does not always show the real position of the bug (like in imperative languages), but the first found abnormal behaviour that is caused by that bug (like in runtime errors).
now that i saw that clean hugs output, i thought about it a little bit more: one does not need pages of error-description written in the style of... juristic blah, but a clear description about what's wrong and maybe some hints to solve it.
in that given example
1 module Test7 where 2 3 len' xs = head (xs) + (length xs) 4 o = len' "GH"
i would prefer an output like this:
TYPE MISMATCH in "Test7.hs": line 4, col 5 in Expression : len' "GH" between Function : len' and Parameter : "GH" with Types :: [Int] -> [Int] :: [Char] HINT: type of : (len') is caused by missing explicit type declaration len' :: [Int] -> [Int]
well, if we replace ("GH") with (f x) and (len') with (g y) then it should look like
TYPE MISMATCH in "Test7.hs": line 4, col 5 in Expression : g y (f x) between Function : g y and Parameter : (f x) with Types :: [Int] -> [Int] :: [Char] HINT: type of : (g y) is caused by g :: a -> [a] -> [a] y :: Int HINT: type of : (f x) is caused by f :: X -> String x :: X HINT: expression : f could be mistaken. (Compile with --Wall for more hints.)
well, i do not know how hard it is to implement that, but at least without hints it is less irritating than the old style.
- Marc
Am Dienstag, 28. Juni 2005 21:43 schrieb Peter A Jonsson:
Hello,
I read the summary of the survey and noticed you wanted feedback on where error messages could be improved. I looked up some (simple) examples of type errors and ran them through ghc. I do not make any claims to be an HCI expert, just a mere mortal with an opinion.
Code:
1 module Test2 where 2 3 fib n = if (3 > n) then 1 else (fib (n - 1) + fib (n - 2)) 4 k = fib 's'
Error message:
Test2.hs:4: No instance for (Num Char) arising from use of `fib' at Test2.hs:4 In the definition of `k': k = fib 's'
This isn't a bad error message in my humble opinion, it does pinpoint that I'm doing something wrong in line 4, and that there isn't an instance for Num Char doesn't come as a surprise. However I think it could have been more helpful by telling me that I tried to pass a Char to a function which expected an (Ord a, Num a) => a as its parameter.
Code:
1 module Test4 where 2 3 k :: Int -> Int 4 k l = 2.0*l
Error message:
Test4.hs:4: No instance for (Fractional Int) arising from the literal `2.0' at Test4.hs:4 In the first argument of `(*)', namely `2.0' In the definition of `k': k l = 2.0 * l
One reason this kind of error could happen is an inexperienced user declaring the wrong type for his function, or not knowing that 2.0 would be interpreted as a Fractional.
Code:
1 module Test7 where 2 3 len' xs = head (xs) + (length xs) 4 o = len' "GH"
Error message:
Test7.hs:4: Couldn't match `Int' against `Char' Expected type: [Int] Inferred type: [Char] In the first argument of `len'', namely `"GH"' In the definition of `o': o = len' "GH"
I ran this through Hugs version November 2002 and got this error message:
ERROR "Test7.hs":4 - Type error in application *** Expression : len' "GH" *** Term : "GH" *** Type : String *** Does not match : [Int]
I find the Hugs message more clear, but that might be my background.
Code:
1 module Test8 where 2 3 f = head 3
Error message:
Test8.hs:3: No instance for (Num [a]) arising from the literal `3' at Test8.hs:3 Possible cause: the monomorphism restriction applied to the following: f :: a (bound at Test8.hs:3) Probable fix: give these definition(s) an explicit type signature In the first argument of `head', namely `3' In the definition of `f': f = head 3
This one I find outright scary. For "wrong = div 3 8 + 1/2" it gives an error message that somewhat helps me guess the error, but the above doesn't even come close to helping me.
/ Peter
_______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
_______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

On 6/29/05, Seth Kurtzberg
I just wanted to correct any assumption that imperative language don't suffer from error message problems. Fundamentally, they suffer more, and are in many cases impossible to fix. In my experience GHC error locations always have some relationship to the error in coding, although of course the error message may at times be hard to interpret because the programmer believes he has coded a function with a particular signature but, in fact, has coded the function with a different inferred type. (Of course we all always explicitly specify function signatures and avoid this problem entirely. :-) )
This makes me think that an interactive "compile-time debugger" could be a good idea to help "newbies". It would present expressions against the inferred type and ask if the inference is correct. The user could either accept the inference, or reject it. After a few itrerations the exact location of the error should be pinpointed exactly. Additionally, confirmed inferences could be added directly in the source code as type annotations. (Iirc, Chameleon does this sort of thing.) Of course, GHC is probably not the place to add such a functionality. It could be a tool of its own right, perhaps part of the Helium project. Cheers, JP.

oh, erm, maybe i was not clear enough. i did not mean that imperative languages are better. far from it. i meant that their compile-time error messages show more lexical miswritings than complex mistakes. their complex mistakes cause runtime-errors. and with logs and debugs of the running program you find mainly "the first abnormal behaviour that is caused by that bug". so, the complex compile-error messages of haskell code are unusual for imperative languages. - marc Am Mittwoch, 29. Juni 2005 05:20 schrieb Seth Kurtzberg:
I don't disagree with the main thrust, but the idea that imperative language are, in general, better about error messages is not, in my opinion, true. There is a large variation, of course, but for certain types of errors in an imperative language the compiler simply can't get a correct handle on what is wrong (because of ambiguities that cannot be removed).
I, and I'm sure everyone else, would always be in support of more detailed error messages, and I agree that the examples cited increase the clarity. In my opinion this increase is significant and worth doing.
I just wanted to correct any assumption that imperative language don't suffer from error message problems. Fundamentally, they suffer more, and are in many cases impossible to fix. In my experience GHC error locations always have some relationship to the error in coding, although of course the error message may at times be hard to interpret because the programmer believes he has coded a function with a particular signature but, in fact, has coded the function with a different inferred type. (Of course we all always explicitly specify function signatures and avoid this problem entirely. :-) )
Marc A. Ziegert wrote:
greetings.
i have to agree with Peter. it's really no fun to read the error messages.
i do not have a big problem with those; but i'm not a newbie anymore, and as newbie... i always just understood nothing more than that single given LINENUMBER within all that output-spam. well, most times it was enough.
the trick is: to throw the code against the --Wall tests whether it is al dente or crumbly. the solution is to type the types and to look about where the bugs are running. hey, of course, they like crumbs. ;-)
especially for newbies it is really confusing, that the compiler output does not always show the real position of the bug (like in imperative languages), but the first found abnormal behaviour that is caused by that bug (like in runtime errors).
now that i saw that clean hugs output, i thought about it a little bit more: one does not need pages of error-description written in the style of... juristic blah, but a clear description about what's wrong and maybe some hints to solve it.
in that given example
1 module Test7 where 2 3 len' xs = head (xs) + (length xs) 4 o = len' "GH"
i would prefer an output like this:
TYPE MISMATCH in "Test7.hs": line 4, col 5 in Expression : len' "GH" between Function : len' and Parameter : "GH" with Types :: [Int] -> [Int] :: [Char] HINT: type of : (len') is caused by missing explicit type declaration len' :: [Int] -> [Int]
well, if we replace ("GH") with (f x) and (len') with (g y) then it should look like
TYPE MISMATCH in "Test7.hs": line 4, col 5 in Expression : g y (f x) between Function : g y and Parameter : (f x) with Types :: [Int] -> [Int] :: [Char] HINT: type of : (g y) is caused by g :: a -> [a] -> [a] y :: Int HINT: type of : (f x) is caused by f :: X -> String x :: X HINT: expression : f could be mistaken. (Compile with --Wall for more hints.)
well, i do not know how hard it is to implement that, but at least without hints it is less irritating than the old style.
- Marc
Am Dienstag, 28. Juni 2005 21:43 schrieb Peter A Jonsson:
Hello,
I read the summary of the survey and noticed you wanted feedback on where error messages could be improved. I looked up some (simple) examples of type errors and ran them through ghc. I do not make any claims to be an HCI expert, just a mere mortal with an opinion.
Code:
1 module Test2 where 2 3 fib n = if (3 > n) then 1 else (fib (n - 1) + fib (n - 2)) 4 k = fib 's'
Error message:
Test2.hs:4: No instance for (Num Char) arising from use of `fib' at Test2.hs:4 In the definition of `k': k = fib 's'
This isn't a bad error message in my humble opinion, it does pinpoint that I'm doing something wrong in line 4, and that there isn't an instance for Num Char doesn't come as a surprise. However I think it could have been more helpful by telling me that I tried to pass a Char to a function which expected an (Ord a, Num a) => a as its parameter.
Code:
1 module Test4 where 2 3 k :: Int -> Int 4 k l = 2.0*l
Error message:
Test4.hs:4: No instance for (Fractional Int) arising from the literal `2.0' at Test4.hs:4 In the first argument of `(*)', namely `2.0' In the definition of `k': k l = 2.0 * l
One reason this kind of error could happen is an inexperienced user declaring the wrong type for his function, or not knowing that 2.0 would be interpreted as a Fractional.
Code:
1 module Test7 where 2 3 len' xs = head (xs) + (length xs) 4 o = len' "GH"
Error message:
Test7.hs:4: Couldn't match `Int' against `Char' Expected type: [Int] Inferred type: [Char] In the first argument of `len'', namely `"GH"' In the definition of `o': o = len' "GH"
I ran this through Hugs version November 2002 and got this error message:
ERROR "Test7.hs":4 - Type error in application *** Expression : len' "GH" *** Term : "GH" *** Type : String *** Does not match : [Int]
I find the Hugs message more clear, but that might be my background.
Code:
1 module Test8 where 2 3 f = head 3
Error message:
Test8.hs:3: No instance for (Num [a]) arising from the literal `3' at Test8.hs:3 Possible cause: the monomorphism restriction applied to the following: f :: a (bound at Test8.hs:3) Probable fix: give these definition(s) an explicit type signature In the first argument of `head', namely `3' In the definition of `f': f = head 3
This one I find outright scary. For "wrong = div 3 8 + 1/2" it gives an error message that somewhat helps me guess the error, but the above doesn't even come close to helping me.
/ Peter
_______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
_______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

Peter A Jonsson
I read the summary of the survey and noticed you wanted feedback on where error messages could be improved.
I have some more comments, but let me say that I'm mostly happy with the error messages as they are. One thing that occasionally happens is that my (explicit) type signature is wrong, and GHC seems to take it as fiat, and give all kinds of rather misleading error messages. (No example, but I can try to create one if it's necessary). Another thing I really would like, is runtime errors with line numbers in them. Sometimes I get an error from "head", "read", "!" or similar during testing, and it would be really nice to know exactly which invocation that failed. In particular since I don't get a stack backtrace. (I can achieve this reasonably well with CPP macros, but it is a chore.) -k -- If I haven't seen further, it is by standing in the footprints of giants
participants (5)
-
Jean-Philippe Bernardy
-
Ketil Malde
-
Marc A. Ziegert
-
Peter A Jonsson
-
Seth Kurtzberg