Non-numeric type in default declaration [GHC-88933]

A numeric literal such as 5 is overloaded in Haskell and has the type forall a. Num a => a. This allows the programmer to use numeric literals in many contexts without having a separate literal syntax for different numeric types. By extension, many numeric functions have a polymorphic type involving the Num type class.

A downside of using overloaded arithmetic expressions is that GHC is not always able to non-ambiguously infer a concrete type, such as Int or Double. This is the case, for example, in the expression show 5. The compiler cannot infer if the programmer means show (5 :: Int), show (5 :: Double) or any other numeric type.

Since this case is very common, the Haskell report specifies a default behaviour for overloaded numeric expressions which involve the Num typeclass. Numeric types are defaulted to Integer, and if that is not possible to Double.

This defaulting behaviour can be customized with “default declarations”. A default declaration uses the syntax default (...) with a list of comma-separated types. These types are tried in the order in which they occur in the default declaration.

Every type which appears in a default declaration must implement the Num type class. If a type which occurs in a default declaration does not have such an instance, then this error is thrown by GHC.

Examples

A default declaration was provided for Bool

In this example a default declaration was provided for the type Bool. Since Bool does not implement the Num type class, we have to remove the default declaration if we want to compile the program.

Error message

BoolDefaultDeclaration.hs:3:1: error: [GHC-88933]
    • The default type ‘Bool’ is not an instance of ‘Num’
    • When checking the types in a default declaration
  |
3 | default (Bool)
  | ^^^^^^^^^^^^^^
BoolDefaultDeclaration.hs
Before
module BoolDefaultDeclaration where

default (Bool)
After
module BoolDefaultDeclaration where


A default declaration was provided for String

In this example, the programmer wrote a default declaration for the type String, which does not implement the type class Num. If we enable the OverloadedStrings extension, then the rules about which types are allowed in default declarations are relaxed. Every type which implements either the Num or the IsString type class is now allowed in default declarations.

Error message

StringDefaultDeclaration.hs:4:1: error: [GHC-88933]
    • The default type ‘String’ is not an instance of ‘Num’
    • When checking the types in a default declaration
  |
4 | default (String)
StringDefaultDeclaration.hs
Before

module StringDefaultDeclaration where

default (String)

main :: IO ()
main = print "Hello, World!"
After
{-# LANGUAGE OverloadedStrings #-}
module StringDefaultDeclaration where

default (String)

main :: IO ()
main = print "Hello, World!"