Multiple default declarations [GHC-99565]

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. However, every Haskell module may contain at most one such default declaration. If a module contains more that one default declaration, then this error is thrown by GHC.

Examples

Multiple default declarations in single module

In this example the programmer tries to customize the defaulting behaviour for numeric types to allow defaulting to both Double and Int. In order to do this both defaults have to be specified in a comma-separated list instead of two separate default declarations.

Error Message

messages/GHC-99565/multiple-defaults/before/MultipleDefaults.hs:4:1: error:
    Multiple default declarations
      here was another default declaration messages/GHC-99565/multiple-defaults/before/MultipleDefaults.hs:3:1-16
  |
4 | default (Double)
  | ^^^^^^^^^^^^^^^^
MultipleDefaults.hs
Before
module MultipleDefaults where

default (Double)
default (Int)

main :: IO ()
main = print 5
After
module MultipleDefaults where

default (Double, Int)


main :: IO ()
main = print 5