Skip to content

Nondeterministic segfault on simple hspec program with GHC 9.0 only

(Originally reported at https://github.com/ekmett/reflection/issues/51.)

The reflection-2.1.6 test suite nondeterministically segfaults on Linux and macOS when compiled with GHC 9.0.1 or 9.0.2. The furthest I've managed to minimize the issue is:

{-# LANGUAGE PackageImports #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Main (main) where

import Control.Exception (ArithException(..), evaluate)
import Numeric.Natural (Natural)
import "hspec" Test.Hspec
import "hspec" Test.Hspec.QuickCheck
import "QuickCheck" Test.QuickCheck (Negative(..), NonNegative(..))

main :: IO ()
main = hspec spec

spec :: Spec
spec =
  describe "A" $ do
    describe "B" $ do
      prop "identity" $
        \(NonNegative (i :: Integer)) -> i `shouldBe` i
      prop "should throw an Underflow exception on negative inputs" $
        \(Negative (i :: Integer)) ->
          evaluate (fromInteger i :: Natural) `shouldThrow` (== Underflow)

With GHC 8.10.7 or 9.2.1, this works as expected:

$ ghc-8.10.7 Bug.hs && ./Bug
Loaded package environment from /home/ryanglscott/Documents/Hacking/Haskell/ci-maintenance/checkout/ekmett/reflection/.ghc.environment.x86_64-linux-8.10.7
[1 of 1] Compiling Main             ( Bug.hs, Bug.o )
Linking Bug ...

A
  B
    identity [✔]
      +++ OK, passed 100 tests.
    should throw an Underflow exception on negative inputs [✔]
      +++ OK, passed 100 tests.

Finished in 0.0009 seconds
2 examples, 0 failures

$ ghc-9.2.1 Bug.hs && ./Bug
Loaded package environment from /home/ryanglscott/Documents/Hacking/Haskell/ci-maintenance/checkout/ekmett/reflection/.ghc.environment.x86_64-linux-9.2.1
[1 of 1] Compiling Main             ( Bug.hs, Bug.o )
Linking Bug ...

A
  B
    identity [✔]
      +++ OK, passed 100 tests.
    should throw an Underflow exception on negative inputs [✔]
      +++ OK, passed 100 tests.

Finished in 0.0013 seconds
2 examples, 0 failures

With GHC 9.0.2, however, this can segfault:

$ ghc-9.0.2 Bug.hs && ./Bug
Loaded package environment from /home/ryanglscott/Documents/Hacking/Haskell/ci-maintenance/checkout/ekmett/reflection/.ghc.environment.x86_64-linux-9.0.2
[1 of 1] Compiling Main             ( Bug.hs, Bug.o )
Linking Bug ...

A
  B
    identity [✔]
      +++ OK, passed 100 tests.
    should throw an Underflow exception on negative inputs [ ]Segmentation fault (core dumped)

This is somewhat nondeterministic. In situations where it doesn't segfault, an incorrect runtime result will be observed:

$ ./Bug

A
  B
    identity [✔]
      +++ OK, passed 100 tests.
    should throw an Underflow exception on negative inputs [✘]

Failures:

  Bug.hs:22:47: 
  1) A.B should throw an Underflow exception on negative inputs
       Falsifiable (after 54 tests and 2 shrinks):
         Negative {getNegative = -1}
       did not get expected exception: ArithException

  To rerun use: --match "/A/B/should throw an Underflow exception on negative inputs/"

Randomized with seed 1065015581

Finished in 0.0028 seconds
2 examples, 1 failure

This example proves remarkably resistant to minimization, as attempting to delete code in various places seemingly makes the bug disappear.

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