Overflowed Literals [GHC-97441]

Flag: -Woverflowed-literals
Enabled by default

This warning is emitted if an integer literal (that is, a constant integer value in the source code) will overflow.

Many integer types have fixed precision. This means that only a certain number of bits are available to represent their values. You can check the minimum and maximum values representable by given type by using minBound and maxBound from the Bounded type class defined in the base package. The range of supported values might differ based on what OS / platform you’re using.

>>> minBound :: Int
-9223372036854775808
>>> maxBound :: Int
9223372036854775807

Calculations that exceed this range cause the value to wrap around, which is called “overflow” or “underflow”. Literals outside the range also overflow. This doesn’t cause an error at runtime, but it might cause confusion because the overflowed value is usually not what you want or expect.

To fix the warning you can:

Examples

Overflowed Literals

Error Message

OverflowedLiterals.hs:10:12: warning: [GHC-97441] [-Woverflowed-literals]
    Literal 258 is out of the Word8 range 0..255
   |
10 |     print (258 :: Word8)
   |            ^^^

OverflowedLiterals.hs:15:12: warning: [GHC-97441] [-Woverflowed-literals]
    Literal 9223372036854775817 is out of the Int range -9223372036854775808..9223372036854775807
   |
15 |     print (9223372036854775817 :: Int)
   |            ^^^^^^^^^^^^^^^^^^^
OverflowedLiterals.hs
Before
module Main where

import Data.Word (Word8)

main :: IO ()
main = do
    -- Word8 can represent values in range (0,255)
    -- 258 is 3 larger than maxBound so it will wrap around 0 -> 1 -> 2
    -- prints 2 due to overflow
    print (258 :: Word8)

    -- Int can represent values in range (-9223372036854775808,9223372036854775807)
    -- 9223372036854775817 is 10 larger than maxBound so it will wrap around to negative values
    -- prints -9223372036854775799 due to overflow
    print (9223372036854775817 :: Int)
After
module Main where

import Data.Word (Word8)

main :: IO ()
main = do
    -- Word8 can represent values in range (0,255)
    -- prints 255
    print (255 :: Word8)

    -- Int can represent values in range (-9223372036854775808,9223372036854775807)
    -- prints 9223372036854775807
    print (9223372036854775807 :: Int)