GHC 9.4.2 regresses being able to do math on aarch64
Summary
I found this test failure while working on nixpkgs on aarch64. This is extremely alarming, before I reduced it to a simpler program using only base, at which point I am out-of-this-world alarmed.
https://github.com/haskell-foundation/foundation/issues/571
Steps to reproduce
Stick this in Main.hs
:
{-# LANGUAGE NoImplicitPrelude, OverloadedStrings, RankNTypes, ScopedTypeVariables, NoRebindableSyntax #-}
module Main where
import Prelude
import System.Environment
import Data.Word
testF :: Word8 -> Word8 -> Bool
testF a b =
if b == 0 then True
else a == (a `div` b) * b + (a `mod` b)
main :: IO ()
main = do
args <- getArgs
let [a :: Word8, b] = read <$> args
putStrLn . show $ testF a b
Then:
co/ghc942bug » ghc -O1 app/Main.hs
[1 of 2] Compiling Main ( app/Main.hs, app/Main.o )
[2 of 2] Linking app/Main
co/ghc942bug » app/Main 217 161
False
co/ghc942bug » ghc -O0 app/Main.hs
[1 of 2] Compiling Main ( app/Main.hs, app/Main.o ) [Optimisation flags changed]
[2 of 2] Linking app/Main [Objects changed]
co/ghc942bug » app/Main 217 161
True
Note that it's fine on 9.2.4:
co/ghc942bug » ghcup set 9.2.4
[ Warn ] This is an old-style command for setting GHC. Use 'ghcup set ghc' instead.
[ Info ] GHC 9.2.4 successfully set as default version
co/ghc942bug » ghc -O0 app/Main.hs
[1 of 1] Compiling Main ( app/Main.hs, app/Main.o )
Linking app/Main ...
co/ghc942bug » app/Main 217 161
True
co/ghc942bug » ghc -O1 app/Main.hs
[1 of 1] Compiling Main ( app/Main.hs, app/Main.o ) [Optimisation flags changed]
Linking app/Main ...
co/ghc942bug » app/Main 217 161
True
On Linux, GHC 9.4.2 from nixpkgs (qemu on Apple Silicon):
~ » ghc -O1 Repro.hs
[1 of 2] Compiling Main ( Repro.hs, Repro.o )
[2 of 2] Linking Repro
~ » ./Repro 217 161
False
~ » ghc -O0 Repro.hs
[1 of 2] Compiling Main ( Repro.hs, Repro.o ) [Optimisation flags changed]
[2 of 2] Linking Repro [Objects changed]
~ » ./Repro 217 161
True
~ » uname -a
Linux thinnix 5.15.47 #1-NixOS SMP Tue Jun 14 16:36:28 UTC 2022 aarch64 GNU/Linux
Expected behavior
It should return True in both optimization configurations.
Environment
- GHC version used: 9.4.2 from ghcup although it also happens on ghc from nix. It's fine in ghc 9.2.4.
Optional:
- Operating System: macOS, although it also happens on aarch64-linux
- System Architecture: aarch64