Skip to content

GHC 8.8 heap overflow regression

The following program throws a heap overflow if you compile it with optimization on GHC 8.8 and HEAD:

module Bug where

import Data.Bits (setBit)

f :: Int
f = foldl setter 0 $ zip [0..] [()]
  where
    setter v (ix, _) = setBit v ix
$ ~/Software/ghc3/inplace/bin/ghc-stage2 -fforce-recomp -O Bug.hs
[1 of 1] Compiling Bug              ( Bug.hs, Bug.o )
ghc-stage2: panic! (the 'impossible' happened)
  (GHC version 8.9.20190309 for x86_64-unknown-linux):
        heap overflow

This does not happen with GHC 8.6.4.

The FontyFruity package on Hackage fails to build on GHC HEAD due to this regression.

Edited by Ryan Scott
To upload designs, you'll need to enable LFS and have an admin enable hashed storage. More information