Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
-
265d0024
by ARATA Mizuki at 2025-06-06T05:47:48-04:00
4 changed files:
- compiler/GHC/CmmToAsm/AArch64/CodeGen.hs
- + testsuite/tests/codeGen/should_run/T26061.hs
- + testsuite/tests/codeGen/should_run/T26061.stdout
- testsuite/tests/codeGen/should_run/all.T
Changes:
| ... | ... | @@ -928,21 +928,25 @@ getRegister' config plat expr |
| 928 | 928 | |
| 929 | 929 | CmmMachOp (MO_S_Shr w) [x, (CmmLit (CmmInt n _))] | w == W8, 0 <= n, n < 8 -> do
|
| 930 | 930 | (reg_x, _format_x, code_x) <- getSomeReg x
|
| 931 | - return $ Any (intFormat w) (\dst -> code_x `snocOL` annExpr expr (SBFX (OpReg w dst) (OpReg w reg_x) (OpImm (ImmInteger n)) (OpImm (ImmInteger (8-n)))))
|
|
| 931 | + return $ Any (intFormat w) (\dst -> code_x `snocOL` annExpr expr (SBFX (OpReg w dst) (OpReg w reg_x) (OpImm (ImmInteger n)) (OpImm (ImmInteger (8-n))))
|
|
| 932 | + `snocOL` (UXTB (OpReg w dst) (OpReg w dst))) -- See Note [Signed arithmetic on AArch64]
|
|
| 932 | 933 | CmmMachOp (MO_S_Shr w) [x, y] | w == W8 -> do
|
| 933 | 934 | (reg_x, _format_x, code_x) <- getSomeReg x
|
| 934 | 935 | (reg_y, _format_y, code_y) <- getSomeReg y
|
| 935 | 936 | return $ Any (intFormat w) (\dst -> code_x `appOL` code_y `snocOL` annExpr expr (SXTB (OpReg w reg_x) (OpReg w reg_x)) `snocOL`
|
| 936 | - (ASR (OpReg w dst) (OpReg w reg_x) (OpReg w reg_y)))
|
|
| 937 | + (ASR (OpReg w dst) (OpReg w reg_x) (OpReg w reg_y)) `snocOL`
|
|
| 938 | + (UXTB (OpReg w dst) (OpReg w dst))) -- See Note [Signed arithmetic on AArch64]
|
|
| 937 | 939 | |
| 938 | 940 | CmmMachOp (MO_S_Shr w) [x, (CmmLit (CmmInt n _))] | w == W16, 0 <= n, n < 16 -> do
|
| 939 | 941 | (reg_x, _format_x, code_x) <- getSomeReg x
|
| 940 | - return $ Any (intFormat w) (\dst -> code_x `snocOL` annExpr expr (SBFX (OpReg w dst) (OpReg w reg_x) (OpImm (ImmInteger n)) (OpImm (ImmInteger (16-n)))))
|
|
| 942 | + return $ Any (intFormat w) (\dst -> code_x `snocOL` annExpr expr (SBFX (OpReg w dst) (OpReg w reg_x) (OpImm (ImmInteger n)) (OpImm (ImmInteger (16-n))))
|
|
| 943 | + `snocOL` (UXTH (OpReg w dst) (OpReg w dst))) -- See Note [Signed arithmetic on AArch64]
|
|
| 941 | 944 | CmmMachOp (MO_S_Shr w) [x, y] | w == W16 -> do
|
| 942 | 945 | (reg_x, _format_x, code_x) <- getSomeReg x
|
| 943 | 946 | (reg_y, _format_y, code_y) <- getSomeReg y
|
| 944 | 947 | return $ Any (intFormat w) (\dst -> code_x `appOL` code_y `snocOL` annExpr expr (SXTH (OpReg w reg_x) (OpReg w reg_x)) `snocOL`
|
| 945 | - (ASR (OpReg w dst) (OpReg w reg_x) (OpReg w reg_y)))
|
|
| 948 | + (ASR (OpReg w dst) (OpReg w reg_x) (OpReg w reg_y)) `snocOL`
|
|
| 949 | + (UXTH (OpReg w dst) (OpReg w dst))) -- See Note [Signed arithmetic on AArch64]
|
|
| 946 | 950 | |
| 947 | 951 | CmmMachOp (MO_S_Shr w) [x, (CmmLit (CmmInt n _))]
|
| 948 | 952 | | w == W32 || w == W64
|
| 1 | +{-# LANGUAGE MagicHash #-}
|
|
| 2 | +{-# LANGUAGE ExtendedLiterals #-}
|
|
| 3 | +import GHC.Word
|
|
| 4 | +import GHC.Exts
|
|
| 5 | + |
|
| 6 | +f :: Int16# -> Word16#
|
|
| 7 | +f x = let !w = int16ToWord16# (x `uncheckedShiftRAInt16#` 1#)
|
|
| 8 | + in w `remWord16#` 13#Word16
|
|
| 9 | +{-# NOINLINE f #-}
|
|
| 10 | + |
|
| 11 | +g :: Int8# -> Word8#
|
|
| 12 | +g x = let !w = int8ToWord8# (x `uncheckedShiftRAInt8#` 1#)
|
|
| 13 | + in w `remWord8#` 19#Word8
|
|
| 14 | +{-# NOINLINE g #-}
|
|
| 15 | + |
|
| 16 | +h :: Int16# -> Int# -> Word16#
|
|
| 17 | +h x y = let !w = int16ToWord16# (x `uncheckedShiftRAInt16#` y)
|
|
| 18 | + in w `remWord16#` 13#Word16
|
|
| 19 | +{-# NOINLINE h #-}
|
|
| 20 | + |
|
| 21 | +i :: Int8# -> Int# -> Word8#
|
|
| 22 | +i x y = let !w = int8ToWord8# (x `uncheckedShiftRAInt8#` y)
|
|
| 23 | + in w `remWord8#` 19#Word8
|
|
| 24 | +{-# NOINLINE i #-}
|
|
| 25 | + |
|
| 26 | +main :: IO ()
|
|
| 27 | +main = do
|
|
| 28 | + print (W16# (f (-100#Int16)))
|
|
| 29 | + print (W8# (g (-100#Int8)))
|
|
| 30 | + print (W16# (h (-100#Int16) 1#))
|
|
| 31 | + print (W8# (i (-100#Int8) 1#))
|
|
| 32 | + |
|
| 33 | +-- int16ToWord16 (-100 `shiftR` 1) `rem` 13
|
|
| 34 | +-- = int16ToWord16 (-50) `rem` 13
|
|
| 35 | +-- = 65486 `rem` 13
|
|
| 36 | +-- = 5
|
|
| 37 | + |
|
| 38 | +-- int8ToWord8 (-100 `shiftR` 1) `rem` 19
|
|
| 39 | +-- = int8ToWord8 (-50) `rem` 19
|
|
| 40 | +-- = 206 `rem` 19
|
|
| 41 | +-- = 16 |
| 1 | +5
|
|
| 2 | +16
|
|
| 3 | +5
|
|
| 4 | +16 |
| ... | ... | @@ -255,3 +255,4 @@ test('T24893', normal, compile_and_run, ['-O']) |
| 255 | 255 | |
| 256 | 256 | test('CCallConv', [req_c], compile_and_run, ['CCallConv_c.c'])
|
| 257 | 257 | test('T25364', normal, compile_and_run, [''])
|
| 258 | +test('T26061', normal, compile_and_run, ['']) |