Type Mismatch [GHC-83865]
GHC expected one type, but was given another. Unlike dynamically-typed programming languages,
type signatures in Haskell are like a contract between the programmer and the compiler.
In its simplest form, when you call a function f
with type a -> b
, with some argument x
,
the compiler will check whether x
has type a
and if that is not the case, it will trigger
the type mismatch error. This case is illustrated by the terms
example, below.
Type mismatch errors are quite general, however, so you will still encounter them in many other situations.
Examples
Values of Different Types
Function inc
has type Int -> Int
, hence it expects an argument
of type Int
; yet, on the definition of two
it was called with
an argument of type String
.
If you ever need to know the type of something, you can ask for it in ghci
with the command :type
(or its shorthand :t
):
ghci> :t "x"
"x" :: String
Error Message
Terms.hs:6:11: error: [GHC-83865]
• Couldn't match type ‘[Char]’ with ‘Int’
Expected: Int
Actual: String
• In the first argument of ‘inc’, namely ‘"x"’
In the expression: inc "x"
In an equation for ‘two’: two = inc "x"
|
4 | two = inc "x"
|
Terms.hs
inc :: Int -> Int
inc i = i + 1
two = inc "x"
inc :: Int -> Int
inc i = i + 1
two = inc 1
Type expected, but kind received.
Forgetting the type parameter to Maybe
is the culprit, but it is only caught in the
context of the the arrow in the declaration of isNothing
, which can be confusing.
The arrow (->
) in Haskell is a type constructor. It takes two types
of kind Type
, and returns a fresh type, also of kind Type
. That is, for x -> y
to make any sense, GHC needs x
and y
to be types of kind Type
, which is not
the case in this example: Maybe
by itself has kind Type -> Type
.
If you ever need to know the kind of something, you can ask ghci
with the :kind
(or its shorthand :k
), keeping in mind
that *
(pronounced “star”) is a synonym for Type
:
ghci> :k (->)
(->) :: * -> * -> *
ghci> :k Maybe
Maybe :: * -> *
Error Message
Type.hs:1:14: error: [GHC-83865]
• Expecting one more argument to ‘Maybe’
Expected a type, but ‘Maybe’ has kind ‘* -> *’
• In the type signature: isNothing :: Maybe -> Bool
|
1 | isNothing :: Maybe -> Bool
|
Type.hs
isNothing :: Maybe -> Bool
isNothing Nothing = True
isNothing _ = False
isNothing :: Maybe a -> Bool
isNothing Nothing = True
isNothing _ = False
Forall-quantification not matched
Function f
takes an argument of type forall r. r -> r
, so you might think
the function g :: String -> String
would be suitable, because the type variable
r
can be instantiated to the concrete type String
.
However, GHC 9.0 and later do not instantiate of forall-quantified variables in function arguments like that.
You can almost always fix this issue by explicitly applying arguments as shown in the “after” column below. In fact, that is what GHC used to do automatically. Note that this can prevent sharing in some situation, which is why it was deemed better to make this explicit.
Since GHC 9.2.4, you can also enable the DeepSubsumption
language extension to fix this error which reverts GHC back to its old implicit behavior.
For more detailed information see:
- Youtube: @rae: What Haskell’s deep subsumption is, why we killed it, and then why we resurrected it.
- GHC Proposal: Simplify subsumption
Error Message
Subsumption.hs:2:5: error: [GHC-83865]
• Couldn't match type: String -> String
with: forall r. r -> r
Expected: (forall r. r -> r) -> Int
Actual: (String -> String) -> Int
• In the expression: g
In an equation for ‘f’: f = g
|
2 | f = g
| ^
Subsumption.hs
f :: (forall r. r -> r) -> Int
f = g
g :: (String -> String) -> Int
g _ = 1337
f :: (forall r. r -> r) -> Int
f x = g x
g :: (String -> String) -> Int
g _ = 1337