Feedback on Error messages in ghc.

Peter A Jonsson pj at ludd.ltu.se
Tue Jun 28 15:43:51 EDT 2005


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




More information about the Glasgow-haskell-users mailing list