Type checker's expected and inferred types (reformatted)

David Menendez dave at zednenem.com
Sun Oct 25 16:02:51 EDT 2009


On Sun, Oct 25, 2009 at 1:37 PM, Isaac Dupree
<ml at isaac.cedarswampstudios.org> wrote:
> David Menendez wrote:
>>
>> The expected type is what the context wants (it's *ex*ternal). The
>> inferred type is what the expression itself has (it's *in*ternal).
>>
>> So inferring the type Maybe () for bar seems wrong.
>
> well, maybe GHC just gets it wrong enough of the time, that I got confused.
>
> Or maybe ... When there are bound variables interacting, on the inside and
> outside, it gets confusing.
>
>
> ghci:
> Prelude> \x -> (3+x) + (length x)
>
> <interactive>:1:15:
>    Couldn't match expected type `[a]' against inferred type `Int'
>    In the second argument of `(+)', namely `(length x)'
>    In the expression: (3 + x) + (length x)
>    In the expression: \ x -> (3 + x) + (length x)
>
> Your explanation of "expected" and "inferred" could make sense to me if the
> error message followed the "Couldn't match" line with, instead,
>    "In the first argument of `length', namely `x'"
> because 'length' gives the context of expected list-type, but we've found
> out from elsewhere (a vague word) that 'x' needs to have type Int.

This had me confused for a while, but I think I've worked out what's
happening. (+) is polymorphic, and GHC is giving it the type [a] ->
[a] -> [a]. So the context is expecting [a], but we infer length x ::
Int from the definition of length.

In the alternate case, \x -> length x + (3+x), GHC gives the outer (+)
the type Int -> Int -> Int, and the inner (+) the type [a] -> [a] ->
[a], which is why we get the type mismatch complaint for 3+x instead
of x.

Note what happens if we use a monomorphic operator:

Prelude> let (<>) = undefined :: Int -> Int -> Int
Prelude> \x -> (3+x) <> length x

<interactive>:1:22:
    Couldn't match expected type `[a]' against inferred type `Int'
    In the first argument of `length', namely `x'
    In the second argument of `(<>)', namely `length x'
    In the expression: (3 + x) <> length x
Prelude> \x -> (3+x) + length x

Here, GHC has concluded that x must be an Int, and thus can't be
passed to length.

Prelude> \x -> length x <> (3+x)

<interactive>:1:19:
    Couldn't match expected type `Int' against inferred type `[a]'
    In the second argument of `(<>)', namely `(3 + x)'
    In the expression: length x <> (3 + x)
    In the expression: \ x -> length x <> (3 + x)

Here, GHC has concluded that x must be [a], and thus 3+x must be [a],
which can't be used with <>.

-- 
Dave Menendez <dave at zednenem.com>
<http://www.eyrie.org/~zednenem/>


More information about the Glasgow-haskell-users mailing list