confusing type error

migmit migmit at gmail.com
Thu Dec 4 20:59:39 UTC 2014


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 <qdunkan at gmail.com> написал(а):
> 
> 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 at haskell.org
> http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


More information about the Glasgow-haskell-users mailing list