
I recently got a confusing error msg, and reduced it to a small case: f1 :: Monad m => m Bool f1 = f2 0 0 'a' f2 :: Monad m => Int -> Float -> m Bool f2 = undefined
From this, it's clear that f2 is being given an extra Char argument it didn't ask for. However, the error msg (ghc 7.8.3) is:
Couldn't match type ‘m Bool’ with ‘Bool’ Expected type: Char -> m Bool Actual type: Char -> Bool Relevant bindings include f1 :: m Bool (bound at Bug.hs:4:1) The function ‘f2’ is applied to three arguments, but its type ‘Int -> Float -> Char -> Bool’ has only three In the expression: f2 0 0 'a' In an equation for ‘f1’: f1 = f2 0 0 'a' The confusing part is that 'f2' was applied to three arguments, but it's type has only three. It includes the Char in expected and actual types, and implies that the type of 'f2' includes the Char. So I took quite a while to realize that the type of 'f2' in fact *didn't* expect a Char (and had an 'm'), so that the "but its type" is *not* in fact its declared type. I suppose it infers a type for 'f2' based on its use, and that then becomes the "actual" type, but it seems less confusing if it picked the declared type of 'f2' as its actual type. Perhaps this is working as intended, but it it is confusing! Especially the part about "expected three but got three". Ideally I'd like to see "too many arguments" or at least "expected (Char -> m Bool) but actually 'm Bool'". Actually I'd expect the other way: "expected 'm Bool' but got (Char -> m Bool)' but I think ghc has always done it backwards from how I expect. It looks like it's substituting (->) for 'm', so maybe it's one of those things where ((->) a) is also a monad.

This seems straightforwardly to be a bug, to me. HEAD gives the same behavior you report below. Please post on the bug tracker at https://ghc.haskell.org/trac/ghc/newticket
Thanks!
Richard
On Dec 4, 2014, at 1:50 PM, Evan Laforge
I recently got a confusing error msg, and reduced it to a small case:
f1 :: Monad m => m Bool f1 = f2 0 0 'a'
f2 :: Monad m => Int -> Float -> m Bool f2 = undefined
From this, it's clear that f2 is being given an extra Char argument it didn't ask for. However, the error msg (ghc 7.8.3) is:
Couldn't match type ‘m Bool’ with ‘Bool’ Expected type: Char -> m Bool Actual type: Char -> Bool Relevant bindings include f1 :: m Bool (bound at Bug.hs:4:1) The function ‘f2’ is applied to three arguments, but its type ‘Int -> Float -> Char -> Bool’ has only three In the expression: f2 0 0 'a' In an equation for ‘f1’: f1 = f2 0 0 'a'
The confusing part is that 'f2' was applied to three arguments, but it's type has only three. It includes the Char in expected and actual types, and implies that the type of 'f2' includes the Char. So I took quite a while to realize that the type of 'f2' in fact *didn't* expect a Char (and had an 'm'), so that the "but its type" is *not* in fact its declared type.
I suppose it infers a type for 'f2' based on its use, and that then becomes the "actual" type, but it seems less confusing if it picked the declared type of 'f2' as its actual type. Perhaps this is working as intended, but it it is confusing! Especially the part about "expected three but got three".
Ideally I'd like to see "too many arguments" or at least "expected (Char -> m Bool) but actually 'm Bool'". Actually I'd expect the other way: "expected 'm Bool' but got (Char -> m Bool)' but I think ghc has always done it backwards from how I expect. It looks like it's substituting (->) for 'm', so maybe it's one of those things where ((->) a) is also a monad. _______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

It seems to be an instance of https://ghc.haskell.org/trac/ghc/ticket/7869 But it is fixed (both in HEAD and 7.8). Probably the fix is partial? On Thu, 2014-12-04 at 14:53 -0500, Richard Eisenberg wrote:
This seems straightforwardly to be a bug, to me. HEAD gives the same behavior you report below. Please post on the bug tracker at https://ghc.haskell.org/trac/ghc/newticket
Thanks! Richard
On Dec 4, 2014, at 1:50 PM, Evan Laforge
wrote: I recently got a confusing error msg, and reduced it to a small case:
f1 :: Monad m => m Bool f1 = f2 0 0 'a'
f2 :: Monad m => Int -> Float -> m Bool f2 = undefined
From this, it's clear that f2 is being given an extra Char argument it didn't ask for. However, the error msg (ghc 7.8.3) is:
Couldn't match type ‘m Bool’ with ‘Bool’ Expected type: Char -> m Bool Actual type: Char -> Bool Relevant bindings include f1 :: m Bool (bound at Bug.hs:4:1) The function ‘f2’ is applied to three arguments, but its type ‘Int -> Float -> Char -> Bool’ has only three In the expression: f2 0 0 'a' In an equation for ‘f1’: f1 = f2 0 0 'a'
The confusing part is that 'f2' was applied to three arguments, but it's type has only three. It includes the Char in expected and actual types, and implies that the type of 'f2' includes the Char. So I took quite a while to realize that the type of 'f2' in fact *didn't* expect a Char (and had an 'm'), so that the "but its type" is *not* in fact its declared type.
I suppose it infers a type for 'f2' based on its use, and that then becomes the "actual" type, but it seems less confusing if it picked the declared type of 'f2' as its actual type. Perhaps this is working as intended, but it it is confusing! Especially the part about "expected three but got three".
Ideally I'd like to see "too many arguments" or at least "expected (Char -> m Bool) but actually 'm Bool'". Actually I'd expect the other way: "expected 'm Bool' but got (Char -> m Bool)' but I think ghc has always done it backwards from how I expect. It looks like it's substituting (->) for 'm', so maybe it's one of those things where ((->) a) is also a monad. _______________________________________________ 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

Int -> Float -> Char -> Bool *is* in fact a valid type for f2, since ((->)
Char) is a Monad. However, I agree the error message is confusing,
especially the "expected n, but got n" part.
-Brent
On Thu, Dec 4, 2014 at 1:50 PM, Evan Laforge
I recently got a confusing error msg, and reduced it to a small case:
f1 :: Monad m => m Bool f1 = f2 0 0 'a'
f2 :: Monad m => Int -> Float -> m Bool f2 = undefined
From this, it's clear that f2 is being given an extra Char argument it didn't ask for. However, the error msg (ghc 7.8.3) is:
Couldn't match type ‘m Bool’ with ‘Bool’ Expected type: Char -> m Bool Actual type: Char -> Bool Relevant bindings include f1 :: m Bool (bound at Bug.hs:4:1) The function ‘f2’ is applied to three arguments, but its type ‘Int -> Float -> Char -> Bool’ has only three In the expression: f2 0 0 'a' In an equation for ‘f1’: f1 = f2 0 0 'a'
The confusing part is that 'f2' was applied to three arguments, but it's type has only three. It includes the Char in expected and actual types, and implies that the type of 'f2' includes the Char. So I took quite a while to realize that the type of 'f2' in fact *didn't* expect a Char (and had an 'm'), so that the "but its type" is *not* in fact its declared type.
I suppose it infers a type for 'f2' based on its use, and that then becomes the "actual" type, but it seems less confusing if it picked the declared type of 'f2' as its actual type. Perhaps this is working as intended, but it it is confusing! Especially the part about "expected three but got three".
Ideally I'd like to see "too many arguments" or at least "expected (Char -> m Bool) but actually 'm Bool'". Actually I'd expect the other way: "expected 'm Bool' but got (Char -> m Bool)' but I think ghc has always done it backwards from how I expect. It looks like it's substituting (->) for 'm', so maybe it's one of those things where ((->) a) is also a monad. _______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

I don't see a bug here. f2 is perfectly OK, so, let's examine f1 more closely. It tries to get `m Bool` by applying f1 to three arguments: 0, 0, and 'a'. Now, since `f2` has the type `Int -> Float -> n Bool`, where `n` is of kind `* -> *` (and an instance of `Monad` class, but it's not yet the time to look for instances), we have `f2 0 :: Float -> n Bool` and `f2 0 0 :: n Bool`. Since that is applied to 'a', Haskell deduces that the last type should be something like `Char -> Something` — or, equivalently, `(->) Char Something`. Therefore, it can see that `n` is in fact `(->) Char` and `Something` is `Bool`. Therefore, `f2 0 0 'a' :: Bool`. But it is expecting `m Bool`, not `Bool` — which is exactly what an error message says. Отправлено с iPad
4 дек. 2014 г., в 21:50, Evan Laforge
написал(а): I recently got a confusing error msg, and reduced it to a small case:
f1 :: Monad m => m Bool f1 = f2 0 0 'a'
f2 :: Monad m => Int -> Float -> m Bool f2 = undefined
From this, it's clear that f2 is being given an extra Char argument it didn't ask for. However, the error msg (ghc 7.8.3) is:
Couldn't match type ‘m Bool’ with ‘Bool’ Expected type: Char -> m Bool Actual type: Char -> Bool Relevant bindings include f1 :: m Bool (bound at Bug.hs:4:1) The function ‘f2’ is applied to three arguments, but its type ‘Int -> Float -> Char -> Bool’ has only three In the expression: f2 0 0 'a' In an equation for ‘f1’: f1 = f2 0 0 'a'
The confusing part is that 'f2' was applied to three arguments, but it's type has only three. It includes the Char in expected and actual types, and implies that the type of 'f2' includes the Char. So I took quite a while to realize that the type of 'f2' in fact *didn't* expect a Char (and had an 'm'), so that the "but its type" is *not* in fact its declared type.
I suppose it infers a type for 'f2' based on its use, and that then becomes the "actual" type, but it seems less confusing if it picked the declared type of 'f2' as its actual type. Perhaps this is working as intended, but it it is confusing! Especially the part about "expected three but got three".
Ideally I'd like to see "too many arguments" or at least "expected (Char -> m Bool) but actually 'm Bool'". Actually I'd expect the other way: "expected 'm Bool' but got (Char -> m Bool)' but I think ghc has always done it backwards from how I expect. It looks like it's substituting (->) for 'm', so maybe it's one of those things where ((->) a) is also a monad. _______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

On Thu, Dec 4, 2014 at 12:59 PM, migmit
It tries to get `m Bool` by applying f1 to three arguments: 0, 0, and 'a'. Now, since `f2` has the type `Int -> Float -> n Bool`, where `n` is of kind `* -> *` (and an instance of `Monad` class, but it's not yet the time to look for instances), we have `f2 0 :: Float -> n Bool` and `f2 0 0 :: n Bool`. Since that is applied to 'a', Haskell deduces that the last type should be something like `Char -> Something` — or, equivalently, `(->) Char Something`. Therefore, it can see that `n` is in fact `(->) Char` and `Something` is `Bool`. Therefore, `f2 0 0 'a' :: Bool`. But it is expecting `m Bool`, not `Bool` — which is exactly what an error message says.
Right, that's what I suspected was happening. The confusion arrises because it guesses that 'm' should be (->), and that deduction then leads to a dead-end. But when it reports the problem, it uses its guessed 'm', rather that backing up to the declared value. But surely always backing up to the declared unspecialized value is no good either, because then you get vague errors. All the compiler knows is that when it simplifies as far as it can, it winds up with a /= b, it doesn't know that I would have been surprised by its path a few steps back. But arity errors are common, and intentionally instantiating a prefix type constructor like 'm a' as (->) is probably much less common. So perhaps there could be a heuristic that treats (->) specially and includes an extra clause in the error if it unified a type variable to (->)? I suspect the "expected n but got n" error is also due to the same thing, it counts arrows on one side but inferred arrows on the other? Or something? In any case, it seems like the two sides are counting inconsistently.

The reason I said "That's a bug!" so confidently is because of the "expected n but got n" part. Even if everything else is OK, we need to fix that one bit.
And I tend to agree about using heuristics to report better error messages in the presence of instantiating a type variable with (->). I've been caught and confused by that, too.
Richard
On Dec 4, 2014, at 4:23 PM, Evan Laforge
On Thu, Dec 4, 2014 at 12:59 PM, migmit
wrote: It tries to get `m Bool` by applying f1 to three arguments: 0, 0, and 'a'. Now, since `f2` has the type `Int -> Float -> n Bool`, where `n` is of kind `* -> *` (and an instance of `Monad` class, but it's not yet the time to look for instances), we have `f2 0 :: Float -> n Bool` and `f2 0 0 :: n Bool`. Since that is applied to 'a', Haskell deduces that the last type should be something like `Char -> Something` — or, equivalently, `(->) Char Something`. Therefore, it can see that `n` is in fact `(->) Char` and `Something` is `Bool`. Therefore, `f2 0 0 'a' :: Bool`. But it is expecting `m Bool`, not `Bool` — which is exactly what an error message says.
Right, that's what I suspected was happening. The confusion arrises because it guesses that 'm' should be (->), and that deduction then leads to a dead-end. But when it reports the problem, it uses its guessed 'm', rather that backing up to the declared value.
But surely always backing up to the declared unspecialized value is no good either, because then you get vague errors. All the compiler knows is that when it simplifies as far as it can, it winds up with a /= b, it doesn't know that I would have been surprised by its path a few steps back.
But arity errors are common, and intentionally instantiating a prefix type constructor like 'm a' as (->) is probably much less common. So perhaps there could be a heuristic that treats (->) specially and includes an extra clause in the error if it unified a type variable to (->)?
I suspect the "expected n but got n" error is also due to the same thing, it counts arrows on one side but inferred arrows on the other? Or something? In any case, it seems like the two sides are counting inconsistently. _______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

But it says `expected Char -> Bool, got Char -> m Bool', note the `m' type
constructor in the second one. So it's not `n' vs. `n'.
On Dec 5, 2014 10:50 PM, "Richard Eisenberg"
The reason I said "That's a bug!" so confidently is because of the "expected n but got n" part. Even if everything else is OK, we need to fix that one bit.
And I tend to agree about using heuristics to report better error messages in the presence of instantiating a type variable with (->). I've been caught and confused by that, too.
Richard
On Dec 4, 2014, at 4:23 PM, Evan Laforge
wrote: On Thu, Dec 4, 2014 at 12:59 PM, migmit
wrote: It tries to get `m Bool` by applying f1 to three arguments: 0, 0, and 'a'. Now, since `f2` has the type `Int -> Float -> n Bool`, where `n` is of kind `* -> *` (and an instance of `Monad` class, but it's not yet the time to look for instances), we have `f2 0 :: Float -> n Bool` and `f2 0 0 :: n Bool`. Since that is applied to 'a', Haskell deduces that the last type should be something like `Char -> Something` — or, equivalently, `(->) Char Something`. Therefore, it can see that `n` is in fact `(->) Char` and `Something` is `Bool`. Therefore, `f2 0 0 'a' :: Bool`. But it is expecting `m Bool`, not `Bool` — which is exactly what an error message says.
Right, that's what I suspected was happening. The confusion arrises because it guesses that 'm' should be (->), and that deduction then leads to a dead-end. But when it reports the problem, it uses its guessed 'm', rather that backing up to the declared value.
But surely always backing up to the declared unspecialized value is no good either, because then you get vague errors. All the compiler knows is that when it simplifies as far as it can, it winds up with a /= b, it doesn't know that I would have been surprised by its path a few steps back.
But arity errors are common, and intentionally instantiating a prefix type constructor like 'm a' as (->) is probably much less common. So perhaps there could be a heuristic that treats (->) specially and includes an extra clause in the error if it unified a type variable to (->)?
I suspect the "expected n but got n" error is also due to the same thing, it counts arrows on one side but inferred arrows on the other? Or something? In any case, it seems like the two sides are counting inconsistently. _______________________________________________ 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

I think Richard is referring to "The function ‘f2’ is applied to three
arguments,
but its type ‘Int -> Float -> Char -> Bool’ has only three". Note
"applied to three ... but ... only three". Here n = three.
-Brent
On Fri, Dec 5, 2014 at 9:55 AM, Dr. ÉRDI Gergő
But it says `expected Char -> Bool, got Char -> m Bool', note the `m' type constructor in the second one. So it's not `n' vs. `n'. On Dec 5, 2014 10:50 PM, "Richard Eisenberg"
wrote: The reason I said "That's a bug!" so confidently is because of the "expected n but got n" part. Even if everything else is OK, we need to fix that one bit.
And I tend to agree about using heuristics to report better error messages in the presence of instantiating a type variable with (->). I've been caught and confused by that, too.
Richard
On Dec 4, 2014, at 4:23 PM, Evan Laforge
wrote: On Thu, Dec 4, 2014 at 12:59 PM, migmit
wrote: It tries to get `m Bool` by applying f1 to three arguments: 0, 0, and 'a'. Now, since `f2` has the type `Int -> Float -> n Bool`, where `n` is of kind `* -> *` (and an instance of `Monad` class, but it's not yet the time to look for instances), we have `f2 0 :: Float -> n Bool` and `f2 0 0 :: n Bool`. Since that is applied to 'a', Haskell deduces that the last type should be something like `Char -> Something` — or, equivalently, `(->) Char Something`. Therefore, it can see that `n` is in fact `(->) Char` and `Something` is `Bool`. Therefore, `f2 0 0 'a' :: Bool`. But it is expecting `m Bool`, not `Bool` — which is exactly what an error message says.
Right, that's what I suspected was happening. The confusion arrises because it guesses that 'm' should be (->), and that deduction then leads to a dead-end. But when it reports the problem, it uses its guessed 'm', rather that backing up to the declared value.
But surely always backing up to the declared unspecialized value is no good either, because then you get vague errors. All the compiler knows is that when it simplifies as far as it can, it winds up with a /= b, it doesn't know that I would have been surprised by its path a few steps back.
But arity errors are common, and intentionally instantiating a prefix type constructor like 'm a' as (->) is probably much less common. So perhaps there could be a heuristic that treats (->) specially and includes an extra clause in the error if it unified a type variable to (->)?
I suspect the "expected n but got n" error is also due to the same thing, it counts arrows on one side but inferred arrows on the other? Or something? In any case, it seems like the two sides are counting inconsistently. _______________________________________________ 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
_______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

I was going to ask if I should go ahead and file a bug anyway, but I
just noticed commit 09b7943321f89b945d10f8a914f4c2cbf73dff91 seems to
fix it.
Many thanks to Yuras!
On Fri, Dec 5, 2014 at 7:50 AM, Brent Yorgey
I think Richard is referring to "The function ‘f2’ is applied to three arguments, but its type ‘Int -> Float -> Char -> Bool’ has only three". Note "applied to three ... but ... only three". Here n = three.
-Brent
On Fri, Dec 5, 2014 at 9:55 AM, Dr. ÉRDI Gergő
wrote: But it says `expected Char -> Bool, got Char -> m Bool', note the `m' type constructor in the second one. So it's not `n' vs. `n'.
On Dec 5, 2014 10:50 PM, "Richard Eisenberg"
wrote: The reason I said "That's a bug!" so confidently is because of the "expected n but got n" part. Even if everything else is OK, we need to fix that one bit.
And I tend to agree about using heuristics to report better error messages in the presence of instantiating a type variable with (->). I've been caught and confused by that, too.
Richard
On Dec 4, 2014, at 4:23 PM, Evan Laforge
wrote: On Thu, Dec 4, 2014 at 12:59 PM, migmit
wrote: It tries to get `m Bool` by applying f1 to three arguments: 0, 0, and 'a'. Now, since `f2` has the type `Int -> Float -> n Bool`, where `n` is of kind `* -> *` (and an instance of `Monad` class, but it's not yet the time to look for instances), we have `f2 0 :: Float -> n Bool` and `f2 0 0 :: n Bool`. Since that is applied to 'a', Haskell deduces that the last type should be something like `Char -> Something` — or, equivalently, `(->) Char Something`. Therefore, it can see that `n` is in fact `(->) Char` and `Something` is `Bool`. Therefore, `f2 0 0 'a' :: Bool`. But it is expecting `m Bool`, not `Bool` — which is exactly what an error message says.
Right, that's what I suspected was happening. The confusion arrises because it guesses that 'm' should be (->), and that deduction then leads to a dead-end. But when it reports the problem, it uses its guessed 'm', rather that backing up to the declared value.
But surely always backing up to the declared unspecialized value is no good either, because then you get vague errors. All the compiler knows is that when it simplifies as far as it can, it winds up with a /= b, it doesn't know that I would have been surprised by its path a few steps back.
But arity errors are common, and intentionally instantiating a prefix type constructor like 'm a' as (->) is probably much less common. So perhaps there could be a heuristic that treats (->) specially and includes an extra clause in the error if it unified a type variable to (->)?
I suspect the "expected n but got n" error is also due to the same thing, it counts arrows on one side but inferred arrows on the other? Or something? In any case, it seems like the two sides are counting inconsistently. _______________________________________________ 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
_______________________________________________ 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
participants (6)
-
Brent Yorgey
-
Dr. ÉRDI Gergő
-
Evan Laforge
-
migmit
-
Richard Eisenberg
-
Yuras Shumovich