[Git][ghc/ghc][wip/angerman/aarch64-ncg] 2 commits: Address Takenobu Tani's comments.
Moritz Angermann
gitlab at gitlab.haskell.org
Sun Jul 12 07:06:11 UTC 2020
Moritz Angermann pushed to branch wip/angerman/aarch64-ncg at Glasgow Haskell Compiler / GHC
Commits:
0b41dc6b by Moritz Angermann at 2020-07-12T06:19:36+00:00
Address Takenobu Tani's comments.
Thanks!
- - - - -
1feaa00a by Moritz Angermann at 2020-07-12T07:05:56+00:00
Fix gcd :blush:
- - - - -
4 changed files:
- compiler/GHC/CmmToAsm/AArch64/CodeGen.hs
- compiler/GHC/CmmToAsm/AArch64/Cond.hs
- compiler/GHC/CmmToAsm/AArch64/Instr.hs
- compiler/GHC/CmmToAsm/AArch64/Ppr.hs
Changes:
=====================================
compiler/GHC/CmmToAsm/AArch64/CodeGen.hs
=====================================
@@ -629,6 +629,9 @@ getRegister' config plat expr
when ((isFloatFormat format_x && isIntFormat format_y) || (isIntFormat format_x && isFloatFormat format_y)) $ pprPanic "getRegister:genOp" (text "formats don't match:" <+> text (show format_x) <+> text "/=" <+> text (show format_y))
return $ Any format_x (\dst -> code_x `appOL` code_y `appOL` op (OpReg w dst) (OpReg w reg_x) (OpReg w reg_y))
+ withTempIntReg w op = OpReg w <$> getNewRegNat (intFormat w) >>= op
+ withTempFloatReg w op = OpReg w <$> getNewRegNat (floatFormat w) >>= op
+
intOp w op = do
-- compute x<m> <- x
-- compute x<o> <- y
@@ -694,18 +697,20 @@ getRegister' config plat expr
MO_S_Quot w -> intOp w (\d x y -> unitOL $ SDIV d x y)
-- No native rem instruction. So we'll compute the following
- -- Rd <- Rx / Ry | 2 <- 7 / 3 -- SDIV Rd Rx Ry
- -- Rd <- Rx - Rd * Ry | 1 <- 7 - 2 * 3 -- MSUB Rd Rd Ry Rx
- -- | '---|----------------|---' |
- -- | '----------------|-------'
- -- '--------------------------'
+ -- Rd <- Rx / Ry | 2 <- 7 / 3 -- SDIV Rd Rx Ry
+ -- Rd' <- Rx - Rd * Ry | 1 <- 7 - 2 * 3 -- MSUB Rd' Rd Ry Rx
+ -- | '---|----------------|---' |
+ -- | '----------------|-------'
+ -- '--------------------------'
-- Note the swap in Rx and Ry.
- MO_S_Rem w -> intOp w (\d x y -> toOL [ SDIV d x y, MSUB d d y x ])
+ MO_S_Rem w -> withTempIntReg w $ \t ->
+ intOp w (\d x y -> toOL [ SDIV t x y, MSUB d t y x ])
-- Unsigned multiply/divide
MO_U_MulMayOflo _w -> unsupported expr
MO_U_Quot w -> intOp w (\d x y -> unitOL $ UDIV d x y)
- MO_U_Rem w -> intOp w (\d x y -> toOL [ UDIV d x y, MSUB d d y x ])
+ MO_U_Rem w -> withTempIntReg w $ \t ->
+ intOp w (\d x y -> toOL [ UDIV t x y, MSUB d t y x ])
-- Signed comparisons -- see above for the CSET discussion
MO_S_Ge w -> intOp w (\d x y -> toOL [ CMP x y, CSET d SGE ])
=====================================
compiler/GHC/CmmToAsm/AArch64/Cond.hs
=====================================
@@ -4,6 +4,8 @@ import GHC.Prelude
import GHC.Utils.Panic
+-- https://developer.arm.com/documentation/den0024/a/the-a64-instruction-set/data-processing-instructions/conditional-instructions
+
-- XXX: This appears to go a bit overboard? Maybe we should stick with what LLVM
-- settled on for fcmp?
-- false: always yields false, regardless of operands.
@@ -60,7 +62,7 @@ data Cond
| UOGE -- b.pl
| UOGT -- b.hi
-- others
- | NEVER -- ne
+ | NEVER -- b.nv
| VS -- oVerflow set
| VC -- oVerflow clear
deriving Eq
\ No newline at end of file
=====================================
compiler/GHC/CmmToAsm/AArch64/Instr.hs
=====================================
@@ -208,7 +208,7 @@ callerSavedRegisters :: [Reg]
callerSavedRegisters
= map regSingle [0..18]
++ map regSingle [32..39]
- ++ map regSingle [48..62]
+ ++ map regSingle [48..63]
-- | Apply a given mapping to all the register references in this
-- instruction.
@@ -514,7 +514,7 @@ data Instr
| MOVK Operand Operand
-- | MOVN Operand Operand
-- | MOVZ Operand Operand
- | MVN Operand Operand -- rd = -rn
+ | MVN Operand Operand -- rd = ~rn
| ORN Operand Operand Operand -- rd = rn | ∼op2
| ORR Operand Operand Operand -- rd = rn | op2
| ROR Operand Operand Operand -- rd = rn ≫ rm or rd = rn ≫ #i, i is 6 bits
=====================================
compiler/GHC/CmmToAsm/AArch64/Ppr.hs
=====================================
@@ -489,7 +489,7 @@ pprCond c = case c of
UGE -> text "hs" -- Carry set/unsigned higher or same ; Greater than or equal, or unordered
UGT -> text "hi" -- Unsigned higher ; Greater than, or unordered
- NEVER -> text "ne" -- Never
+ NEVER -> text "nv" -- Never
VS -> text "vs" -- Overflow ; Unordered (at least one NaN operand)
VC -> text "vc" -- No overflow ; Not unordered
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/27ea955ba4ed6d547ac86428bbe95272652a48dc...1feaa00a0df65e15c4f170a54e14d4d1f1e5fc6a
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/27ea955ba4ed6d547ac86428bbe95272652a48dc...1feaa00a0df65e15c4f170a54e14d4d1f1e5fc6a
You're receiving this email because of your account on gitlab.haskell.org.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20200712/cadab932/attachment-0001.html>
More information about the ghc-commits
mailing list