Sub-word arithmetic right shift with AArch64 NCG
Summary
An expression involving sub-word arithmetic right shift may yield a wrong value with AArch64 NCG.
This was found while investigating test-primops#8.
Steps to reproduce
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE ExtendedLiterals #-}
import GHC.Word
import GHC.Exts
f :: Int16# -> Word16#
f x = let !w = int16ToWord16# (x `uncheckedShiftRAInt16#` 1#)
in w `remWord16#` 13#Word16
{-# NOINLINE f #-}
main :: IO ()
main = print (W16# (f (-1798#Int16)))
-- int16ToWord16 (-1798 `shiftR` 1) `rem` 13
-- = int16ToWord16 (-899) `rem` 13
-- = 64637 `rem` 13
-- = 1
$ uname -m
arm64
$ ghc -fforce-recomp subwordarshift.hs
$ ./subwordarshift # wrong
7
$ ghc -fforce-recomp -fllvm subwordarshift.hs
$ ./subwordarshift # correct
1
Expected behavior
The reproducer should print 1
.
Environment
- GHC version used: 9.8.4, 9.10.2, 9.12.2, 9.13.20250520 (c9abb87c)
- Operating System: macOS
- System Architecture: AArch64