User-defined type error [GHC-64725]

Errors like this usually come from libraries trying to enforce certain rules about the types they work with, or to improve upon a compiler error that would occur otherwise. It is up to the library authors to provide enough information in the embedded error message to fix the failing program—check the documentation for the function that triggered the error for more information. These errors are constructed using GHC.TypeLits.TypeError applied to a type level error message as the context of a class instance, and the compiler will show them when a program attempts to use such an instance.

Examples

Cannot Display functions

Error Message

Main2.hs:12:23: error: [GHC-64725]
    • Cannot display functions.
      Perhaps there are missing arguments?
    • In the expression: display myFunction
      In an equation for ‘myDisplayedFunction’:
          myDisplayedFunction = display myFunction
   |
12 | myDisplayedFunction = display myFunction
   |                       ^^^^^^^

Explanation

Here, the module SomeDisplayLibrary stands in for a pretty-printing library, used to produce human readable text from Haskell values. The library provides a type class Display with instances for different types with a function display :: Display a => a -> String to perform the conversion. In this case the result is of type String but some libraries use their own data type to structure the output.

A problem common to these libraries is that of function typed values, since there’s no general way to represent them as strings. Perhaps for some functions one could simply write the mapping from inputs to outputs - if the input space is enumerable and small enough - but it becomes impractical for larger types, and unfeasible for non-enumerable types. Usually these libraries don’t provide an instance for functions. In this case, the library authors did provide an instance, but one that gives a compile time error with more information than just “No instance for (Display (Bool -> Int)).”

Depending on context, the solution could be to follow the error message and display the result of applying the function to enough arguments, see myDisplayedAppliedFunction.

If the intention was to actually display the function when the input space is small enough (e.g. just the two Bool constructors), one could define a newtype for functions of type Bool -> a and provide a Display instance for it. Then, the user can call display with the function wrapped in this newtype, see myDisplayedNewtypedFunction.

Main2.hs
Before
module Main2 where

import SomeDisplayLibrary (Display (..))

myFunction :: Bool -> Int
myFunction x =
  if x
    then 42
    else 54

myDisplayedFunction :: String
myDisplayedFunction = display myFunction
After
module Main2 where

import SomeDisplayLibrary (Display (..))

myFunction :: Bool -> Int
myFunction x =
  if x
    then 42
    else 54

myDisplayedAppliedFunction :: String
myDisplayedAppliedFunction = display (myFunction True)

newtype BoolFun a = BoolFun (Bool -> a)

instance Display a => Display (BoolFun a) where
  display (BoolFun f) =
    "(\\x -> if x then " <> display (f True) <>
    " else " <> display (f False) <> ")"

myDisplayedNewtypedFunction :: String
myDisplayedNewtypedFunction = display (BoolFun myFunction)
SomeDisplayLibrary.hs
Before
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE UndecidableInstances #-}

module SomeDisplayLibrary where

import GHC.TypeLits

class Display a where
  display :: a -> String

instance Display () where
  display () = "()"

instance Display Bool where
  display b = if b then "True" else "False"

instance Display Int where
  display = show

instance (Display a, Display b) => Display (a, b) where
  display (a, b) = "(" <> display a <> ", " <> display b <> ")"

instance TypeError (Text "Cannot display functions." :$$:
                    Text "Perhaps there are missing arguments?")
    => Display (a -> b) where
  display = error "unreachable: instance Display (a -> b)"
After
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE UndecidableInstances #-}

module SomeDisplayLibrary where

import GHC.TypeLits

class Display a where
  display :: a -> String

instance Display () where
  display () = "()"

instance Display Bool where
  display b = if b then "True" else "False"

instance Display Int where
  display = show

instance (Display a, Display b) => Display (a, b) where
  display (a, b) = "(" <> display a <> ", " <> display b <> ")"

instance TypeError (Text "Cannot display functions." :$$:
                    Text "Perhaps there are missing arguments?")
    => Display (a -> b) where
  display = error "unreachable: instance Display (a -> b)"
Cannot encode arbitrary precision integers

Error Message

Main1.hs:9:18: error: [GHC-64725]
    • Cannot encode arbitrary precision integers.
      Consider using a fixed size representation.
    • In the expression: encode myValue
      In an equation for ‘myEncodedValue’:
          myEncodedValue = encode myValue
  |
9 | myEncodedValue = encode myValue
  |                  ^^^^^^

Explanation

Here, the module SomeEncodingLibrary stands in for a library used to encode Haskell values into some encoding, represented by the data type Encoded. The library also provides a type class Encode with instances for different types, and the function encode :: Encode a => a -> Encoded to perform the encoding.

There are many such Haskell libraries depending on the target encoding. It’s also common to find data types that don’t work for a particular encoding; in this example, the encoding library only works with types where the size of values is statically-known. Since, in this case, we know myValue fits in an Int, the solution is to use that as the type of myValue instead of Integer. However, for a program that needs to work with Integers, a different solution would be needed, likely using a different encoding (and encoding library) altogether.

Main1.hs
Before
module Main1 where

import SomeEncodingLibrary (Encoded, encode)

myValue :: Integer
myValue = 42

myEncodedValue :: Encoded
myEncodedValue = encode myValue
After
module Main1 where

import SomeEncodingLibrary (Encoded, encode)

myValue :: Int
myValue = 42

myEncodedValue :: Encoded
myEncodedValue = encode myValue
SomeEncodingLibrary.hs
Before
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE TypeFamilies #-}

module SomeEncodingLibrary where

import GHC.TypeLits

class Encode a

data Encoded = Encoded

encode :: Encode a => a -> Encoded
encode _ = Encoded

instance Encode ()

instance Encode Bool

instance Encode Int

instance Encode Word

instance (Encode a, Encode b) => Encode (a, b)

instance TypeError (Text "Cannot encode arbitrary precision integers." :$$:
                    Text "Consider using a fixed size representation.")
    => Encode Integer
After
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE TypeFamilies #-}

module SomeEncodingLibrary where

import GHC.TypeLits

class Encode a

data Encoded = Encoded

encode :: Encode a => a -> Encoded
encode _ = Encoded

instance Encode ()

instance Encode Bool

instance Encode Int

instance Encode Word

instance (Encode a, Encode b) => Encode (a, b)

instance TypeError (Text "Cannot encode arbitrary precision integers." :$$:
                    Text "Consider using a fixed size representation.")
    => Encode Integer