[Git][ghc/ghc][master] 3 commits: Fix registerArch for riscv64
Marge Bot (@marge-bot)
gitlab at gitlab.haskell.org
Thu Oct 3 02:24:53 UTC 2024
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
af59749a by Matthew Pickering at 2024-10-02T22:23:11-04:00
Fix registerArch for riscv64
The register allocator doesn't support vector registers on riscv64,
therefore advertise as NoVectors.
Fixes #25314
- - - - -
a49e66fc by Matthew Pickering at 2024-10-02T22:23:11-04:00
riscv: Avoid using csrr instruction to test for vector registers
The csrr instruction isn't allowed in qemu user-mode, and raises an
illegal instruction error when it is encountered.
Therefore for now, we just hard-code that there is no support for vector
registers since the rest of the compiler doesn't support vector
registers for riscv.
Fixes #25312
- - - - -
115a30e9 by Andreas Klebinger at 2024-10-02T22:23:11-04:00
Add support for fp min/max to riscv
Fixes #25313
- - - - -
5 changed files:
- compiler/GHC/CmmToAsm/RV64/CodeGen.hs
- compiler/GHC/CmmToAsm/RV64/Instr.hs
- compiler/GHC/CmmToAsm/RV64/Ppr.hs
- compiler/GHC/Platform/Reg/Class.hs
- rts/CheckVectorSupport.c
Changes:
=====================================
compiler/GHC/CmmToAsm/RV64/CodeGen.hs
=====================================
@@ -1109,6 +1109,8 @@ getRegister' config plat expr =
MO_F_Mul w -> floatOp w (\d x y -> unitOL $ annExpr expr (MUL d x y))
MO_F_Quot w -> floatOp w (\d x y -> unitOL $ annExpr expr (DIV d x y))
-- Floating point comparison
+ MO_F_Min w -> floatOp w (\d x y -> unitOL $ annExpr expr (FMIN d x y))
+ MO_F_Max w -> floatOp w (\d x y -> unitOL $ annExpr expr (FMAX d x y))
MO_F_Eq w -> floatCond w (\d x y -> unitOL $ annExpr expr (CSET d x y EQ))
MO_F_Ne w -> floatCond w (\d x y -> unitOL $ annExpr expr (CSET d x y NE))
MO_F_Ge w -> floatCond w (\d x y -> unitOL $ annExpr expr (CSET d x y FGE))
@@ -2208,6 +2210,8 @@ makeFarBranches {- only used when debugging -} _platform statics basic_blocks =
FENCE {} -> 1
FCVT {} -> 1
FABS {} -> 1
+ FMIN {} -> 1
+ FMAX {} -> 1
FMA {} -> 1
-- estimate the subsituted size for jumps to lables
-- jumps to registers have size 1
=====================================
compiler/GHC/CmmToAsm/RV64/Instr.hs
=====================================
@@ -107,6 +107,8 @@ regUsageOfInstr platform instr = case instr of
FENCE _ _ -> usage ([], [])
FCVT _variant dst src -> usage (regOp src, regOp dst)
FABS dst src -> usage (regOp src, regOp dst)
+ FMIN dst src1 src2 -> usage (regOp src1 ++ regOp src2, regOp dst)
+ FMAX dst src1 src2 -> usage (regOp src1 ++ regOp src2, regOp dst)
FMA _ dst src1 src2 src3 ->
usage (regOp src1 ++ regOp src2 ++ regOp src3, regOp dst)
_ -> panic $ "regUsageOfInstr: " ++ instrCon instr
@@ -203,6 +205,8 @@ patchRegsOfInstr instr env = case instr of
FENCE o1 o2 -> FENCE o1 o2
FCVT variant o1 o2 -> FCVT variant (patchOp o1) (patchOp o2)
FABS o1 o2 -> FABS (patchOp o1) (patchOp o2)
+ FMIN o1 o2 o3 -> FMIN (patchOp o1) (patchOp o2) (patchOp o3)
+ FMAX o1 o2 o3 -> FMAX (patchOp o1) (patchOp o2) (patchOp o3)
FMA s o1 o2 o3 o4 ->
FMA s (patchOp o1) (patchOp o2) (patchOp o3) (patchOp o4)
_ -> panic $ "patchRegsOfInstr: " ++ instrCon instr
@@ -603,6 +607,13 @@ data Instr
FCVT FcvtVariant Operand Operand
| -- | Floating point ABSolute value
FABS Operand Operand
+
+ | -- | Min
+ -- dest = min(r1)
+ FMIN Operand Operand Operand
+ | -- | Max
+ FMAX Operand Operand Operand
+
| -- | Floating-point fused multiply-add instructions
--
-- - fmadd : d = r1 * r2 + r3
@@ -658,6 +669,8 @@ instrCon i =
FENCE {} -> "FENCE"
FCVT {} -> "FCVT"
FABS {} -> "FABS"
+ FMIN {} -> "FMIN"
+ FMAX {} -> "FMAX"
FMA variant _ _ _ _ ->
case variant of
FMAdd -> "FMADD"
=====================================
compiler/GHC/CmmToAsm/RV64/Ppr.hs
=====================================
@@ -666,6 +666,10 @@ pprInstr platform instr = case instr of
$ line (pprOp platform o1 <> text "->" <> pprOp platform o2)
FABS o1 o2 | isSingleOp o2 -> op2 (text "\tfabs.s") o1 o2
FABS o1 o2 | isDoubleOp o2 -> op2 (text "\tfabs.d") o1 o2
+ FMIN o1 o2 o3 | isSingleOp o1 -> op3 (text "\tfmin.s") o1 o2 o3
+ | isDoubleOp o2 -> op3 (text "\tfmin.d") o1 o2 o3
+ FMAX o1 o2 o3 | isSingleOp o1 -> op3 (text "\tfmax.s") o1 o2 o3
+ | isDoubleOp o2 -> op3 (text "\tfmax.d") o1 o2 o3
FMA variant d r1 r2 r3 ->
let fma = case variant of
FMAdd -> text "\tfmadd" <> dot <> floatPrecission d
=====================================
compiler/GHC/Platform/Reg/Class.hs
=====================================
@@ -49,5 +49,8 @@ registerArch arch =
ArchPPC -> Unified
ArchPPC_64 {} -> Unified
ArchAArch64 -> Unified
- ArchRISCV64 -> Separate
+ -- Support for vector registers not yet implemented for RISC-V
+ -- see panic in `getFreeRegs`.
+ --ArchRISCV64 -> Separate
+ ArchRISCV64 -> NoVectors
_ -> NoVectors
=====================================
rts/CheckVectorSupport.c
=====================================
@@ -65,12 +65,16 @@ int checkVectorSupport(void) {
*/
#elif defined(__riscv)
- unsigned long vlenb;
- asm volatile ("csrr %0, vlenb" : "=r" (vlenb));
+// csrr instruction nott allowed in user-mode qemu emulation of riscv
+// Backend doesn't yet support vector registers, so hard-coded to no vector support
+// for now.
+//
+// unsigned long vlenb;
+// asm volatile ("csrr %0, vlenb" : "=r" (vlenb));
// VLENB gives the length in bytes
- supports_V16 = vlenb >= 16;
- supports_V32 = vlenb >= 32;
- supports_V64 = vlenb >= 64;
+ supports_V16 = 0;
+ supports_V32 = 0;
+ supports_V64 = 0;
#else
// On other platforms, we conservatively return no vector support.
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/92976985625ffba551f1e1422f5e3a0cbf7beb89...115a30e9142b4481de3ba735396e9d0417d46445
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/92976985625ffba551f1e1422f5e3a0cbf7beb89...115a30e9142b4481de3ba735396e9d0417d46445
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/20241002/bca1f918/attachment-0001.html>
More information about the ghc-commits
mailing list