No instance arising [GHC-39999]

This error happens when an expression in the code has a type constraint (e.g. Eq a => a -> a) requiring an instance of a type class but GHC can‘t find it. This most commonly happens for two reasons: Either the type is too polymorphic (i.e. general) e.g. forall a. a and there is no type signature declaring that the type should have the instance. Or the type is specific e.g. Bool, but there is no instance for the desired type class defined for this type.

Examples

A usage of (==) on a data type which doesn‘t have an instance for Eq.

Error message

Main.hs:4:15: error: [GHC-39999]
    • No instance for (Eq Foo) arising from a use of ‘==’
    • In the expression: foo == A
      In an equation for ‘isA’: isA foo = foo == A
  |
4 | isA foo = foo == A
  |               ^^

Explanation

The operator == is only defined on types which have an instance for the Eq type class. The data type Foo does not have an instance. So GHC doesn‘t know how to compare values of Foo. To make this example compile we can create an Eq instance by using a derive statement.

Main.hs
Before
data Foo = A | B

isA :: Foo -> Bool
isA foo = foo == A
After
data Foo = A | B deriving Eq

isA :: Foo -> Bool
isA foo = foo == A
A usage of `+` on a too polymorphic variable.

Error message

Main.hs:2:11: error: [GHC-39999]
    • No instance for (Num a) arising from a use of ‘+’
      Possible fix:
        add (Num a) to the context of
          the type signature for:
            add :: forall a. a -> a -> a
    • In the expression: x + y
      In an equation for ‘add’: add x y = x + y
  |
2 | add x y = x + y
  |           ^

Explanation

The operator + is only defined on types which have an instance of the Num type class. If the function has the signature a -> a -> a someone could e.g. pass in a String for a and GHC wouldn‘t know how to add two Strings. Too fix it, like the compiler suggests, we add the Num a => constraint to the type signature to make sure that all users of add provide a suitable Num instance.

Main.hs
Before
add :: a -> a -> a
add x y = x + y
After
add :: Num a => a -> a -> a
add x y = x + y
A usage of `x.foo` with the field `foo` not being in scope

Error message

src/Main.hs:6:12: error: [GHC-39999]
    • No instance for ‘GHC.Records.HasField "foo" MyData Int’
        arising from selecting the field ‘foo’
      Perhaps you want to add ‘foo’ to the import list in the import of
      ‘DataType’ (src/Main.hs:3:1-24).
    • In the expression: x.foo
      In an equation for ‘getFoo’: getFoo x = x.foo
  |
6 | getFoo x = x.foo
  |

Explanation

This error arises when using the OverloadedRecordDot extension. Given a module exporting a record:

module DataType where

data MyData = MyData { foo :: Int, bar :: String }

When MyData is imported into a module without also importing the fields, attempting to access fields using OverloadedRecordDot will result in an error.

Adding the field to the import list will resolve the issue.

Main.hs
Before
module Main where

import DataType (MyData)

getFoo :: MyData -> Int
getFoo x = x.foo
After
module Main where

import DataType (MyData(foo))

getFoo :: MyData -> Int
getFoo x = x.foo
Missing superclass declaration

Error message on GHC 9.6.2

Main.hs:5:10: error: [GHC-39999]
    • Could not deduce ‘Show (Foo a)’
        arising from the head of a quantified constraint
        arising from the superclasses of an instance declaration
      from the context: Show a
        bound by a quantified context at Main.hs:5:10-18
    • In the instance declaration for ‘Show1 Foo’
  |
5 | instance Show1 Foo where
  |          ^^^^^^^^^

Explanation

The Show1 class has changed in GHC 9.6 to require a quantified superclass constraint Show. To fix this error, for every instance Show1 declaration add a corresponding instance Show declaration for the same data type.

Main.hs
Before
import Data.Functor.Classes (Show1(..))

newtype Foo a = Foo a

instance Show1 Foo where
  liftShowsPrec showsPrec _showList prec (Foo a) rest = "Foo " ++ showsPrec prec a rest
After
import Data.Functor.Classes (Show1(..))

newtype Foo a = Foo a

instance Show a => Show (Foo a) where
   show (Foo a) = "Foo " ++ show a

instance Show1 Foo where
  liftShowsPrec showsPrec _showList prec (Foo a) rest = "Foo " ++ showsPrec prec a rest
Adding numbers to strings

Error message

Main.hs:1:16: error: [GHC-39999]
    • No instance for ‘Num String’ arising from the literal ‘5’
    • In the first argument of ‘(+)’, namely ‘5’
      In the second argument of ‘($)’, namely ‘5 + "4"’
      In the expression: print $ 5 + "4"
  |
1 | main = print $ 5 + "4"
  |                ^

Explanation

Given that Haskell is a strong statically typed language, it is not a surprise that adding numbers to strings gives a compile-time error. However, one could expect GHC to be unhappy about "4", not about 5 as above! Let’s take a deeper look on how the type checker works.

The compiler first encounters the operator (+) which has type Num a => a -> a -> a. Thus it infers that both arguments of (+) should be of the same type a. Looking at the first argument 5 does not reveal us what a is: it could be Int, could be Double, etc. But the second argument "4" is certainly String, so the compiler concludes that a should be String.

Now the compiler looks again at the first argument 5. Since the second argument of (+) is String, it infers that 5 must be String as well. In Haskell a numeric literal could be anything which has instance Num, so GHC searches for instance Num String but could not find one and bails out with an error.

Main.hs
Before
main = print $ 5 + "4"
After
main = print $ 5 + 4