From 95d2ce05fb32e663bc7553438ccee7f4d4e36a35 Mon Sep 17 00:00:00 2001 From: Lehua Ding <lehua.ding@rivai.ai> Date: Mon, 18 Sep 2023 19:37:17 +0800 Subject: [PATCH] RISC-V: Refactor and cleanup fma patterns At present, FMA autovec's patterns do not fully use the corresponding pattern in vector.md. The previous reason is that the merge operand of pattern in vector.md cannot be VUNDEF. Now allowing it to be VUNDEF, reunify insn used for reload pass into vector.md, and the corresponding vlmax pattern in autovec.md is used for combine. This patch also refactors the corresponding combine pattern inside autovec-opt.md and removes the unused ones. gcc/ChangeLog: * config/riscv/autovec-opt.md (*<optab>_fma<mode>): Removed old combine patterns. (*single_<optab>mult_plus<mode>): Ditto. (*double_<optab>mult_plus<mode>): Ditto. (*sign_zero_extend_fma): Ditto. (*zero_sign_extend_fma): Ditto. (*double_widen_fma<mode>): Ditto. (*single_widen_fma<mode>): Ditto. (*double_widen_fnma<mode>): Ditto. (*single_widen_fnma<mode>): Ditto. (*double_widen_fms<mode>): Ditto. (*single_widen_fms<mode>): Ditto. (*double_widen_fnms<mode>): Ditto. (*single_widen_fnms<mode>): Ditto. (*reduc_plus_scal_<mode>): Adjust name. (*widen_reduc_plus_scal_<mode>): Adjust name. (*dual_widen_fma<mode>): New combine pattern. (*dual_widen_fmasu<mode>): Ditto. (*dual_widen_fmaus<mode>): Ditto. (*dual_fma<mode>): Ditto. (*single_fma<mode>): Ditto. (*dual_fnma<mode>): Ditto. (*single_fnma<mode>): Ditto. (*dual_fms<mode>): Ditto. (*single_fms<mode>): Ditto. (*dual_fnms<mode>): Ditto. (*single_fnms<mode>): Ditto. * config/riscv/autovec.md (fma<mode>4): Reafctor fma pattern. (*fma<VI:mode><P:mode>): Removed. (fnma<mode>4): Reafctor. (*fnma<VI:mode><P:mode>): Removed. (*fma<VF:mode><P:mode>): Removed. (*fnma<VF:mode><P:mode>): Removed. (fms<mode>4): Reafctor. (*fms<VF:mode><P:mode>): Removed. (fnms<mode>4): Reafctor. (*fnms<VF:mode><P:mode>): Removed. * config/riscv/riscv-protos.h (prepare_ternary_operands): Adjust prototype. * config/riscv/riscv-v.cc (prepare_ternary_operands): Refactor. * config/riscv/vector.md (*pred_mul_plus<mode>_undef): New pattern. (*pred_mul_plus<mode>): Removed. (*pred_mul_plus<mode>_scalar): Removed. (*pred_mul_plus<mode>_extended_scalar): Removed. (*pred_minus_mul<mode>_undef): New pattern. (*pred_minus_mul<mode>): Removed. (*pred_minus_mul<mode>_scalar): Removed. (*pred_minus_mul<mode>_extended_scalar): Removed. (*pred_mul_<optab><mode>_undef): New pattern. (*pred_mul_<optab><mode>): Removed. (*pred_mul_<optab><mode>_scalar): Removed. (*pred_mul_neg_<optab><mode>_undef): New pattern. (*pred_mul_neg_<optab><mode>): Removed. (*pred_mul_neg_<optab><mode>_scalar): Removed. --- gcc/config/riscv/autovec-opt.md | 736 ++++++++++++++------------------ gcc/config/riscv/autovec.md | 301 ++++--------- gcc/config/riscv/riscv-protos.h | 2 +- gcc/config/riscv/riscv-v.cc | 14 +- gcc/config/riscv/vector.md | 439 ++++++------------- 5 files changed, 528 insertions(+), 964 deletions(-) diff --git a/gcc/config/riscv/autovec-opt.md b/gcc/config/riscv/autovec-opt.md index b47bae16193a..cef9f157e996 100644 --- a/gcc/config/riscv/autovec-opt.md +++ b/gcc/config/riscv/autovec-opt.md @@ -110,166 +110,6 @@ [(set_attr "type" "vmalu") (set_attr "mode" "<MODE>")]) -;; ========================================================================= -;; == Widening Ternary arithmetic -;; ========================================================================= - -;; ------------------------------------------------------------------------- -;; ---- [INT] VWMACC -;; ------------------------------------------------------------------------- -;; Includes: -;; - vwmacc.vv -;; - vwmaccu.vv -;; ------------------------------------------------------------------------- - -;; Combine ext + ext + fma ===> widen fma. -;; Most of circumstantces, LoopVectorizer will generate the following IR: -;; vect__8.64_40 = (vector([4,4]) int) vect__7.63_41; -;; vect__11.68_35 = (vector([4,4]) int) vect__10.67_36; -;; vect__13.70_33 = .FMA (vect__11.68_35, vect__8.64_40, vect__4.60_45); -(define_insn_and_split "*<optab>_fma<mode>" - [(set (match_operand:VWEXTI 0 "register_operand") - (plus:VWEXTI - (mult:VWEXTI - (any_extend:VWEXTI - (match_operand:<V_DOUBLE_TRUNC> 2 "register_operand")) - (any_extend:VWEXTI - (match_operand:<V_DOUBLE_TRUNC> 3 "register_operand"))) - (match_operand:VWEXTI 1 "register_operand")))] - "TARGET_VECTOR && can_create_pseudo_p ()" - "#" - "&& 1" - [(const_int 0)] - { - riscv_vector::emit_vlmax_insn (code_for_pred_widen_mul_plus (<CODE>, <MODE>mode), - riscv_vector::WIDEN_TERNARY_OP, operands); - DONE; - } - [(set_attr "type" "viwmuladd") - (set_attr "mode" "<V_DOUBLE_TRUNC>")]) - -;; This helps to match ext + fma. -(define_insn_and_split "*single_<optab>mult_plus<mode>" - [(set (match_operand:VWEXTI 0 "register_operand") - (plus:VWEXTI - (mult:VWEXTI - (any_extend:VWEXTI - (match_operand:<V_DOUBLE_TRUNC> 2 "register_operand")) - (match_operand:VWEXTI 3 "register_operand")) - (match_operand:VWEXTI 1 "register_operand")))] - "TARGET_VECTOR && can_create_pseudo_p ()" - "#" - "&& 1" - [(const_int 0)] - { - insn_code icode = code_for_pred_vf2 (<CODE>, <MODE>mode); - rtx tmp = gen_reg_rtx (<MODE>mode); - rtx ext_ops[] = {tmp, operands[2]}; - riscv_vector::emit_vlmax_insn (icode, riscv_vector::UNARY_OP, ext_ops); - - rtx dst = expand_ternary_op (<MODE>mode, fma_optab, tmp, operands[3], - operands[1], operands[0], 0); - emit_move_insn (operands[0], dst); - DONE; - } - [(set_attr "type" "viwmuladd") - (set_attr "mode" "<V_DOUBLE_TRUNC>")]) - -;; Combine ext + ext + mult + plus ===> widen fma. -;; We have some special cases generated by LoopVectorizer: -;; vect__8.18_46 = (vector([8,8]) signed short) vect__7.17_47; -;; vect__11.22_41 = (vector([8,8]) signed short) vect__10.21_42; -;; vect__12.23_40 = vect__11.22_41 * vect__8.18_46; -;; vect__14.25_38 = vect__13.24_39 + vect__5.14_51; -;; This situation doesn't generate FMA IR. -(define_insn_and_split "*double_<optab>mult_plus<mode>" - [(set (match_operand:VWEXTI 0 "register_operand") - (if_then_else:VWEXTI - (unspec:<VM> - [(match_operand:<VM> 1 "vector_mask_operand") - (match_operand 6 "vector_length_operand") - (match_operand 7 "const_int_operand") - (match_operand 8 "const_int_operand") - (match_operand 9 "const_int_operand") - (reg:SI VL_REGNUM) - (reg:SI VTYPE_REGNUM)] UNSPEC_VPREDICATE) - (plus:VWEXTI - (if_then_else:VWEXTI - (unspec:<VM> - [(match_dup 1) - (match_dup 6) - (match_dup 7) - (match_dup 8) - (match_dup 9) - (reg:SI VL_REGNUM) - (reg:SI VTYPE_REGNUM)] UNSPEC_VPREDICATE) - (mult:VWEXTI - (any_extend:VWEXTI - (match_operand:<V_DOUBLE_TRUNC> 4 "register_operand")) - (any_extend:VWEXTI - (match_operand:<V_DOUBLE_TRUNC> 5 "register_operand"))) - (match_operand:VWEXTI 2 "vector_undef_operand")) - (match_operand:VWEXTI 3 "register_operand")) - (match_dup 2)))] - "TARGET_VECTOR && can_create_pseudo_p ()" - "#" - "&& 1" - [(const_int 0)] - { - emit_insn (gen_pred_widen_mul_plus (<CODE>, <MODE>mode, operands[0], - operands[1], operands[3], operands[4], - operands[5], operands[6], operands[7], - operands[8], operands[9])); - DONE; - } - [(set_attr "type" "viwmuladd") - (set_attr "mode" "<V_DOUBLE_TRUNC>")]) - -;; Combine sign_extend + zero_extend + fma ===> widen fma (su). -(define_insn_and_split "*sign_zero_extend_fma" - [(set (match_operand:VWEXTI 0 "register_operand") - (plus:VWEXTI - (mult:VWEXTI - (sign_extend:VWEXTI - (match_operand:<V_DOUBLE_TRUNC> 2 "register_operand")) - (zero_extend:VWEXTI - (match_operand:<V_DOUBLE_TRUNC> 3 "register_operand"))) - (match_operand:VWEXTI 1 "register_operand")))] - "TARGET_VECTOR && can_create_pseudo_p ()" - "#" - "&& 1" - [(const_int 0)] - { - riscv_vector::emit_vlmax_insn (code_for_pred_widen_mul_plussu (<MODE>mode), - riscv_vector::WIDEN_TERNARY_OP, operands); - DONE; - } - [(set_attr "type" "viwmuladd") - (set_attr "mode" "<V_DOUBLE_TRUNC>")]) - -;; This helps to match zero_extend + sign_extend + fma. -(define_insn_and_split "*zero_sign_extend_fma" - [(set (match_operand:VWEXTI 0 "register_operand") - (plus:VWEXTI - (mult:VWEXTI - (zero_extend:VWEXTI - (match_operand:<V_DOUBLE_TRUNC> 2 "register_operand")) - (sign_extend:VWEXTI - (match_operand:<V_DOUBLE_TRUNC> 3 "register_operand"))) - (match_operand:VWEXTI 1 "register_operand")))] - "TARGET_VECTOR && can_create_pseudo_p ()" - "#" - "&& 1" - [(const_int 0)] - { - rtx ops[] = {operands[0], operands[1], operands[3], operands[2]}; - riscv_vector::emit_vlmax_insn (code_for_pred_widen_mul_plussu (<MODE>mode), - riscv_vector::WIDEN_TERNARY_OP, ops); - DONE; - } - [(set_attr "type" "viwmuladd") - (set_attr "mode" "<V_DOUBLE_TRUNC>")]) - ;; ------------------------------------------------------------------------- ;; ---- [INT] Binary narrow shifts. ;; ------------------------------------------------------------------------- @@ -345,269 +185,9 @@ [(set_attr "type" "vimovvx") (set_attr "mode" "<MODE>")]) -;; ------------------------------------------------------------------------- -;; ---- [FP] VFWMACC -;; ------------------------------------------------------------------------- -;; Includes: -;; - vfwmacc.vv -;; ------------------------------------------------------------------------- - -;; Combine ext + ext + fma ===> widen fma. -;; Most of circumstantces, LoopVectorizer will generate the following IR: -;; vect__8.176_40 = (vector([2,2]) double) vect__7.175_41; -;; vect__11.180_35 = (vector([2,2]) double) vect__10.179_36; -;; vect__13.182_33 = .FMA (vect__11.180_35, vect__8.176_40, vect__4.172_45); -(define_insn_and_split "*double_widen_fma<mode>" - [(set (match_operand:VWEXTF 0 "register_operand") - (unspec:VWEXTF - [(fma:VWEXTF - (float_extend:VWEXTF - (match_operand:<V_DOUBLE_TRUNC> 2 "register_operand")) - (float_extend:VWEXTF - (match_operand:<V_DOUBLE_TRUNC> 3 "register_operand")) - (match_operand:VWEXTF 1 "register_operand")) - (reg:SI FRM_REGNUM)] UNSPEC_VFFMA))] - "TARGET_VECTOR && can_create_pseudo_p ()" - "#" - "&& 1" - [(const_int 0)] - { - riscv_vector::emit_vlmax_insn (code_for_pred_widen_mul (PLUS, <MODE>mode), - riscv_vector::WIDEN_TERNARY_OP_FRM_DYN, operands); - DONE; - } - [(set_attr "type" "vfwmuladd") - (set_attr "mode" "<V_DOUBLE_TRUNC>") - (set (attr "frm_mode") (symbol_ref "riscv_vector::FRM_DYN"))]) - -;; This helps to match ext + fma. -(define_insn_and_split "*single_widen_fma<mode>" - [(set (match_operand:VWEXTF 0 "register_operand") - (unspec:VWEXTF - [(fma:VWEXTF - (float_extend:VWEXTF - (match_operand:<V_DOUBLE_TRUNC> 2 "register_operand")) - (match_operand:VWEXTF 3 "register_operand") - (match_operand:VWEXTF 1 "register_operand")) - (reg:SI FRM_REGNUM)] UNSPEC_VFFMA))] - "TARGET_VECTOR && can_create_pseudo_p ()" - "#" - "&& 1" - [(const_int 0)] - { - insn_code icode = code_for_pred_extend (<MODE>mode); - rtx tmp = gen_reg_rtx (<MODE>mode); - rtx ext_ops[] = {tmp, operands[2]}; - riscv_vector::emit_vlmax_insn (icode, riscv_vector::UNARY_OP, ext_ops); - - rtx dst = expand_ternary_op (<MODE>mode, fma_optab, tmp, operands[3], - operands[1], operands[0], 0); - emit_move_insn (operands[0], dst); - DONE; - } - [(set_attr "type" "vfwmuladd") - (set_attr "mode" "<V_DOUBLE_TRUNC>") - (set (attr "frm_mode") (symbol_ref "riscv_vector::FRM_DYN"))]) - -;; ------------------------------------------------------------------------- -;; ---- [FP] VFWNMSAC -;; ------------------------------------------------------------------------- -;; Includes: -;; - vfwnmsac.vv -;; ------------------------------------------------------------------------- - -;; Combine ext + ext + fnma ===> widen fnma. -;; Most of circumstantces, LoopVectorizer will generate the following IR: -;; vect__8.176_40 = (vector([2,2]) double) vect__7.175_41; -;; vect__11.180_35 = (vector([2,2]) double) vect__10.179_36; -;; vect__13.182_33 = .FNMA (vect__11.180_35, vect__8.176_40, vect__4.172_45); -(define_insn_and_split "*double_widen_fnma<mode>" - [(set (match_operand:VWEXTF 0 "register_operand") - (unspec:VWEXTF - [(fma:VWEXTF - (neg:VWEXTF - (float_extend:VWEXTF - (match_operand:<V_DOUBLE_TRUNC> 2 "register_operand"))) - (float_extend:VWEXTF - (match_operand:<V_DOUBLE_TRUNC> 3 "register_operand")) - (match_operand:VWEXTF 1 "register_operand")) - (reg:SI FRM_REGNUM)] UNSPEC_VFFMA))] - "TARGET_VECTOR && can_create_pseudo_p ()" - "#" - "&& 1" - [(const_int 0)] - { - riscv_vector::emit_vlmax_insn (code_for_pred_widen_mul_neg (PLUS, <MODE>mode), - riscv_vector::WIDEN_TERNARY_OP_FRM_DYN, operands); - DONE; - } - [(set_attr "type" "vfwmuladd") - (set_attr "mode" "<V_DOUBLE_TRUNC>") - (set (attr "frm_mode") (symbol_ref "riscv_vector::FRM_DYN"))]) - -;; This helps to match ext + fnma. -(define_insn_and_split "*single_widen_fnma<mode>" - [(set (match_operand:VWEXTF 0 "register_operand") - (unspec:VWEXTF - [(fma:VWEXTF - (neg:VWEXTF - (float_extend:VWEXTF - (match_operand:<V_DOUBLE_TRUNC> 2 "register_operand"))) - (match_operand:VWEXTF 3 "register_operand") - (match_operand:VWEXTF 1 "register_operand")) - (reg:SI FRM_REGNUM)] UNSPEC_VFFMA))] - "TARGET_VECTOR && can_create_pseudo_p ()" - "#" - "&& 1" - [(const_int 0)] - { - insn_code icode = code_for_pred_extend (<MODE>mode); - rtx tmp = gen_reg_rtx (<MODE>mode); - rtx ext_ops[] = {tmp, operands[2]}; - riscv_vector::emit_vlmax_insn (icode, riscv_vector::UNARY_OP, ext_ops); - - rtx dst = expand_ternary_op (<MODE>mode, fnma_optab, tmp, operands[3], - operands[1], operands[0], 0); - emit_move_insn (operands[0], dst); - DONE; - } - [(set_attr "type" "vfwmuladd") - (set_attr "mode" "<V_DOUBLE_TRUNC>") - (set (attr "frm_mode") (symbol_ref "riscv_vector::FRM_DYN"))]) - -;; ------------------------------------------------------------------------- -;; ---- [FP] VFWMSAC -;; ------------------------------------------------------------------------- -;; Includes: -;; - vfwmsac.vv -;; ------------------------------------------------------------------------- - -;; Combine ext + ext + fms ===> widen fms. -;; Most of circumstantces, LoopVectorizer will generate the following IR: -;; vect__8.176_40 = (vector([2,2]) double) vect__7.175_41; -;; vect__11.180_35 = (vector([2,2]) double) vect__10.179_36; -;; vect__13.182_33 = .FMS (vect__11.180_35, vect__8.176_40, vect__4.172_45); -(define_insn_and_split "*double_widen_fms<mode>" - [(set (match_operand:VWEXTF 0 "register_operand") - (unspec:VWEXTF - [(fma:VWEXTF - (float_extend:VWEXTF - (match_operand:<V_DOUBLE_TRUNC> 2 "register_operand")) - (float_extend:VWEXTF - (match_operand:<V_DOUBLE_TRUNC> 3 "register_operand")) - (neg:VWEXTF - (match_operand:VWEXTF 1 "register_operand"))) - (reg:SI FRM_REGNUM)] UNSPEC_VFFMA))] - "TARGET_VECTOR && can_create_pseudo_p ()" - "#" - "&& 1" - [(const_int 0)] - { - riscv_vector::emit_vlmax_insn (code_for_pred_widen_mul (MINUS, <MODE>mode), - riscv_vector::WIDEN_TERNARY_OP_FRM_DYN, operands); - DONE; - } - [(set_attr "type" "vfwmuladd") - (set_attr "mode" "<V_DOUBLE_TRUNC>") - (set (attr "frm_mode") (symbol_ref "riscv_vector::FRM_DYN"))]) - -;; This helps to match ext + fms. -(define_insn_and_split "*single_widen_fms<mode>" - [(set (match_operand:VWEXTF 0 "register_operand") - (unspec:VWEXTF - [(fma:VWEXTF - (float_extend:VWEXTF - (match_operand:<V_DOUBLE_TRUNC> 2 "register_operand")) - (match_operand:VWEXTF 3 "register_operand") - (neg:VWEXTF - (match_operand:VWEXTF 1 "register_operand"))) - (reg:SI FRM_REGNUM)] UNSPEC_VFFMA))] - "TARGET_VECTOR && can_create_pseudo_p ()" - "#" - "&& 1" - [(const_int 0)] - { - insn_code icode = code_for_pred_extend (<MODE>mode); - rtx tmp = gen_reg_rtx (<MODE>mode); - rtx ext_ops[] = {tmp, operands[2]}; - riscv_vector::emit_vlmax_insn (icode, riscv_vector::UNARY_OP, ext_ops); - - rtx dst = expand_ternary_op (<MODE>mode, fms_optab, tmp, operands[3], - operands[1], operands[0], 0); - emit_move_insn (operands[0], dst); - DONE; - } - [(set_attr "type" "vfwmuladd") - (set_attr "mode" "<V_DOUBLE_TRUNC>") - (set (attr "frm_mode") (symbol_ref "riscv_vector::FRM_DYN"))]) - -;; ------------------------------------------------------------------------- -;; ---- [FP] VFWNMACC -;; ------------------------------------------------------------------------- -;; Includes: -;; - vfwnmacc.vv -;; ------------------------------------------------------------------------- - -;; Combine ext + ext + fnms ===> widen fnms. -;; Most of circumstantces, LoopVectorizer will generate the following IR: -;; vect__8.176_40 = (vector([2,2]) double) vect__7.175_41; -;; vect__11.180_35 = (vector([2,2]) double) vect__10.179_36; -;; vect__13.182_33 = .FNMS (vect__11.180_35, vect__8.176_40, vect__4.172_45); -(define_insn_and_split "*double_widen_fnms<mode>" - [(set (match_operand:VWEXTF 0 "register_operand") - (unspec:VWEXTF - [(fma:VWEXTF - (neg:VWEXTF - (float_extend:VWEXTF - (match_operand:<V_DOUBLE_TRUNC> 2 "register_operand"))) - (float_extend:VWEXTF - (match_operand:<V_DOUBLE_TRUNC> 3 "register_operand")) - (neg:VWEXTF - (match_operand:VWEXTF 1 "register_operand"))) - (reg:SI FRM_REGNUM)] UNSPEC_VFFMA))] - "TARGET_VECTOR && can_create_pseudo_p ()" - "#" - "&& 1" - [(const_int 0)] - { - riscv_vector::emit_vlmax_insn (code_for_pred_widen_mul_neg (MINUS, <MODE>mode), - riscv_vector::WIDEN_TERNARY_OP_FRM_DYN, operands); - DONE; - } - [(set_attr "type" "vfwmuladd") - (set_attr "mode" "<V_DOUBLE_TRUNC>") - (set (attr "frm_mode") (symbol_ref "riscv_vector::FRM_DYN"))]) - -;; This helps to match ext + fnms. -(define_insn_and_split "*single_widen_fnms<mode>" - [(set (match_operand:VWEXTF 0 "register_operand") - (unspec:VWEXTF - [(fma:VWEXTF - (neg:VWEXTF - (float_extend:VWEXTF - (match_operand:<V_DOUBLE_TRUNC> 2 "register_operand"))) - (match_operand:VWEXTF 3 "register_operand") - (neg:VWEXTF - (match_operand:VWEXTF 1 "register_operand"))) - (reg:SI FRM_REGNUM)] UNSPEC_VFFMA))] - "TARGET_VECTOR && can_create_pseudo_p ()" - "#" - "&& 1" - [(const_int 0)] - { - insn_code icode = code_for_pred_extend (<MODE>mode); - rtx tmp = gen_reg_rtx (<MODE>mode); - rtx ext_ops[] = {tmp, operands[2]}; - riscv_vector::emit_vlmax_insn (icode, riscv_vector::UNARY_OP, ext_ops); - - rtx dst = expand_ternary_op (<MODE>mode, fnms_optab, tmp, operands[3], - operands[1], operands[0], 0); - emit_move_insn (operands[0], dst); - DONE; - } - [(set_attr "type" "vfwmuladd") - (set_attr "mode" "<V_DOUBLE_TRUNC>") - (set (attr "frm_mode") (symbol_ref "riscv_vector::FRM_DYN"))]) +;; ============================================================================= +;; All combine patterns for combine pass. +;; ============================================================================= ;; ============================================================================= ;; Combine op + vmerge to cond_op @@ -1197,7 +777,7 @@ [(set_attr "type" "vfwmul")]) ;; Combine extend + vredsum to vwredsum[u] -(define_insn_and_split "*reduc_plus_scal_<mode>" +(define_insn_and_split "*widen_reduc_plus_scal_<mode>" [(set (match_operand:<V_DOUBLE_EXTEND_VEL> 0 "register_operand") (unspec:<V_DOUBLE_EXTEND_VEL> [ (any_extend:<V_DOUBLE_EXTEND> @@ -1216,7 +796,7 @@ [(set_attr "type" "vector")]) ;; Combine extend + vfredusum to vfwredusum -(define_insn_and_split "*reduc_plus_scal_<mode>" +(define_insn_and_split "*widen_reduc_plus_scal_<mode>" [(set (match_operand:<V_DOUBLE_EXTEND_VEL> 0 "register_operand") (unspec:<V_DOUBLE_EXTEND_VEL> [ (float_extend:<V_DOUBLE_EXTEND> @@ -1284,6 +864,312 @@ } [(set_attr "type" "vector")]) +;; ============================================================================= +;; Combine extend + ternop to widen_ternop +;; ============================================================================= + +;; Combine ext + fma(vmacc,vmadd) to widen_fma (vwmacc) +(define_insn_and_split "*dual_widen_fma<mode>" + [(set (match_operand:VWEXTI 0 "register_operand") + (plus:VWEXTI + (mult:VWEXTI + (any_extend:VWEXTI + (match_operand:<V_DOUBLE_TRUNC> 2 "register_operand")) + (any_extend:VWEXTI + (match_operand:<V_DOUBLE_TRUNC> 3 "register_operand"))) + (match_operand:VWEXTI 1 "register_operand")))] + "TARGET_VECTOR && can_create_pseudo_p ()" + "#" + "&& 1" + [(const_int 0)] + { + rtx ops[] = {operands[0], operands[1], operands[2], operands[3]}; + riscv_vector::emit_vlmax_insn (code_for_pred_widen_mul_plus (<CODE>, <MODE>mode), + riscv_vector::WIDEN_TERNARY_OP, ops); + DONE; + } + [(set_attr "type" "viwmuladd")]) + +;; Combine sign_extend + zero_extend + fma to widen_fma (vwmaccsu) +(define_insn_and_split "*dual_widen_fmasu<mode>" + [(set (match_operand:VWEXTI 0 "register_operand") + (plus:VWEXTI + (mult:VWEXTI + (sign_extend:VWEXTI + (match_operand:<V_DOUBLE_TRUNC> 2 "register_operand")) + (zero_extend:VWEXTI + (match_operand:<V_DOUBLE_TRUNC> 3 "register_operand"))) + (match_operand:VWEXTI 1 "register_operand")))] + "TARGET_VECTOR && can_create_pseudo_p ()" + "#" + "&& 1" + [(const_int 0)] + { + rtx ops[] = {operands[0], operands[1], operands[2], operands[3]}; + riscv_vector::emit_vlmax_insn (code_for_pred_widen_mul_plussu (<MODE>mode), + riscv_vector::WIDEN_TERNARY_OP, ops); + DONE; + } + [(set_attr "type" "viwmuladd")]) + +;; Combine zero_extend + sign_extend + fma to widen_fma (vwmaccsu) +(define_insn_and_split "*dual_widen_fmaus<mode>" + [(set (match_operand:VWEXTI 0 "register_operand") + (plus:VWEXTI + (mult:VWEXTI + (zero_extend:VWEXTI + (match_operand:<V_DOUBLE_TRUNC> 3 "register_operand")) + (sign_extend:VWEXTI + (match_operand:<V_DOUBLE_TRUNC> 2 "register_operand"))) + (match_operand:VWEXTI 1 "register_operand")))] + "TARGET_VECTOR && can_create_pseudo_p ()" + "#" + "&& 1" + [(const_int 0)] + { + rtx ops[] = {operands[0], operands[1], operands[2], operands[3]}; + riscv_vector::emit_vlmax_insn (code_for_pred_widen_mul_plussu (<MODE>mode), + riscv_vector::WIDEN_TERNARY_OP, ops); + DONE; + } + [(set_attr "type" "viwmuladd")]) + +;; This combine pattern does not correspond to an single instruction. +;; This is a temporary pattern produced by a combine pass and if there +;; is no further combine into widen pattern, then fall back to extend +;; pattern and non-widen fma pattern. +(define_insn_and_split "*single_widen_fma<mode>" + [(set (match_operand:VWEXTI 0 "register_operand") + (plus:VWEXTI + (mult:VWEXTI + (any_extend:VWEXTI + (match_operand:<V_DOUBLE_TRUNC> 2 "register_operand")) + (match_operand:VWEXTI 3 "register_operand")) + (match_operand:VWEXTI 1 "register_operand")))] + "TARGET_VECTOR && can_create_pseudo_p ()" + "#" + "&& 1" + [(const_int 0)] + { + insn_code extend_icode = code_for_pred_vf2 (<CODE>, <MODE>mode); + rtx tmp = gen_reg_rtx (<MODE>mode); + rtx extend_ops[] = {tmp, operands[2]}; + riscv_vector::emit_vlmax_insn (extend_icode, riscv_vector::UNARY_OP, + extend_ops); + + rtx ops[] = {operands[0], tmp, operands[3], operands[1]}; + riscv_vector::emit_vlmax_insn (code_for_pred_mul_plus (<MODE>mode), + riscv_vector::TERNARY_OP, ops); + DONE; + } + [(set_attr "type" "viwmuladd")]) + +;; Combine extend + fma to widen_fma (vfwmacc) +(define_insn_and_split "*dual_fma<mode>" + [(set (match_operand:VWEXTF 0 "register_operand") + (plus:VWEXTF + (mult:VWEXTF + (float_extend:VWEXTF + (match_operand:<V_DOUBLE_TRUNC> 2 "register_operand")) + (float_extend:VWEXTF + (match_operand:<V_DOUBLE_TRUNC> 3 "register_operand"))) + (match_operand:VWEXTF 1 "register_operand")))] + "TARGET_VECTOR && can_create_pseudo_p ()" + "#" + "&& 1" + [(const_int 0)] + { + rtx ops[] = {operands[0], operands[1], operands[2], operands[3]}; + riscv_vector::emit_vlmax_insn (code_for_pred_widen_mul (PLUS, <MODE>mode), + riscv_vector::WIDEN_TERNARY_OP_FRM_DYN, ops); + DONE; + } + [(set_attr "type" "vfwmuladd")]) + +;; This combine pattern does not correspond to an single instruction. +;; This is a temporary pattern produced by a combine pass and if there +;; is no further combine into widen pattern, then fall back to extend +;; pattern and non-widen fma pattern. +(define_insn_and_split "*single_fma<mode>" + [(set (match_operand:VWEXTF 0 "register_operand") + (plus:VWEXTF + (mult:VWEXTF + (float_extend:VWEXTF + (match_operand:<V_DOUBLE_TRUNC> 2 "register_operand")) + (match_operand:VWEXTF 3 "register_operand")) + (match_operand:VWEXTF 1 "register_operand")))] + "TARGET_VECTOR && can_create_pseudo_p ()" + "#" + "&& 1" + [(const_int 0)] + { + insn_code icode = code_for_pred_extend (<MODE>mode); + rtx tmp = gen_reg_rtx (<MODE>mode); + rtx ext_ops[] = {tmp, operands[2]}; + riscv_vector::emit_vlmax_insn (icode, riscv_vector::UNARY_OP, ext_ops); + + rtx ops[] = {operands[0], tmp, operands[3], operands[1]}; + riscv_vector::emit_vlmax_insn (code_for_pred_mul (PLUS, <MODE>mode), + riscv_vector::TERNARY_OP_FRM_DYN, ops); + DONE; + } + [(set_attr "type" "vfwmuladd")]) + +;; Combine extend + fnma to widen_fnma (vfwnmsac) +(define_insn_and_split "*dual_fnma<mode>" + [(set (match_operand:VWEXTF 0 "register_operand") + (minus:VWEXTF + (match_operand:VWEXTF 1 "register_operand") + (mult:VWEXTF + (float_extend:VWEXTF + (match_operand:<V_DOUBLE_TRUNC> 2 "register_operand")) + (float_extend:VWEXTF + (match_operand:<V_DOUBLE_TRUNC> 3 "register_operand")))))] + "TARGET_VECTOR && can_create_pseudo_p ()" + "#" + "&& 1" + [(const_int 0)] + { + rtx ops[] = {operands[0], operands[1], operands[2], operands[3]}; + riscv_vector::emit_vlmax_insn (code_for_pred_widen_mul_neg (PLUS, <MODE>mode), + riscv_vector::WIDEN_TERNARY_OP_FRM_DYN, ops); + DONE; + } + [(set_attr "type" "vfwmuladd")]) + +;; This combine pattern does not correspond to an single instruction. +;; This is a temporary pattern produced by a combine pass and if there +;; is no further combine into widen pattern, then fall back to extend +;; pattern and non-widen fnma pattern. +(define_insn_and_split "*single_fnma<mode>" + [(set (match_operand:VWEXTF 0 "register_operand") + (minus:VWEXTF + (match_operand:VWEXTF 1 "register_operand") + (mult:VWEXTF + (float_extend:VWEXTF + (match_operand:<V_DOUBLE_TRUNC> 2 "register_operand")) + (match_operand:VWEXTF 3 "register_operand"))))] + "TARGET_VECTOR && can_create_pseudo_p ()" + "#" + "&& 1" + [(const_int 0)] + { + insn_code icode = code_for_pred_extend (<MODE>mode); + rtx tmp = gen_reg_rtx (<MODE>mode); + rtx ext_ops[] = {tmp, operands[2]}; + riscv_vector::emit_vlmax_insn (icode, riscv_vector::UNARY_OP, ext_ops); + + rtx ops[] = {operands[0], tmp, operands[3], operands[1]}; + riscv_vector::emit_vlmax_insn (code_for_pred_mul_neg (PLUS, <MODE>mode), + riscv_vector::TERNARY_OP_FRM_DYN, ops); + DONE; + } + [(set_attr "type" "vfwmuladd")]) + +;; Combine extend + fms to widen_fms (vfwmsac) +(define_insn_and_split "*dual_fms<mode>" + [(set (match_operand:VWEXTF 0 "register_operand") + (minus:VWEXTF + (mult:VWEXTF + (float_extend:VWEXTF + (match_operand:<V_DOUBLE_TRUNC> 2 "register_operand")) + (float_extend:VWEXTF + (match_operand:<V_DOUBLE_TRUNC> 3 "register_operand"))) + (match_operand:VWEXTF 1 "register_operand")))] + "TARGET_VECTOR && can_create_pseudo_p ()" + "#" + "&& 1" + [(const_int 0)] + { + rtx ops[] = {operands[0], operands[1], operands[2], operands[3]}; + riscv_vector::emit_vlmax_insn (code_for_pred_widen_mul (MINUS, <MODE>mode), + riscv_vector::WIDEN_TERNARY_OP_FRM_DYN, ops); + DONE; + } + [(set_attr "type" "vfwmuladd")]) + +;; This combine pattern does not correspond to an single instruction. +;; This is a temporary pattern produced by a combine pass and if there +;; is no further combine into widen pattern, then fall back to extend +;; pattern and non-widen fms pattern. +(define_insn_and_split "*single_fms<mode>" + [(set (match_operand:VWEXTF 0 "register_operand") + (minus:VWEXTF + (mult:VWEXTF + (float_extend:VWEXTF + (match_operand:<V_DOUBLE_TRUNC> 2 "register_operand")) + (match_operand:VWEXTF 3 "register_operand")) + (match_operand:VWEXTF 1 "register_operand")))] + "TARGET_VECTOR && can_create_pseudo_p ()" + "#" + "&& 1" + [(const_int 0)] + { + insn_code icode = code_for_pred_extend (<MODE>mode); + rtx tmp = gen_reg_rtx (<MODE>mode); + rtx ext_ops[] = {tmp, operands[2]}; + riscv_vector::emit_vlmax_insn (icode, riscv_vector::UNARY_OP, ext_ops); + + rtx ops[] = {operands[0], tmp, operands[3], operands[1]}; + riscv_vector::emit_vlmax_insn (code_for_pred_mul (MINUS, <MODE>mode), + riscv_vector::TERNARY_OP_FRM_DYN, ops); + DONE; + } + [(set_attr "type" "vfwmuladd")]) + +;; Combine extend + fnms to widen_fnms (vfwnmacc) +(define_insn_and_split "*dual_fnms<mode>" + [(set (match_operand:VWEXTF 0 "register_operand") + (minus:VWEXTF + (mult:VWEXTF + (neg:VWEXTF + (float_extend:VWEXTF + (match_operand:<V_DOUBLE_TRUNC> 2 "register_operand"))) + (float_extend:VWEXTF + (match_operand:<V_DOUBLE_TRUNC> 3 "register_operand"))) + (match_operand:VWEXTF 1 "register_operand")))] + "TARGET_VECTOR && can_create_pseudo_p ()" + "#" + "&& 1" + [(const_int 0)] + { + rtx ops[] = {operands[0], operands[1], operands[2], operands[3]}; + riscv_vector::emit_vlmax_insn (code_for_pred_widen_mul_neg (MINUS, <MODE>mode), + riscv_vector::WIDEN_TERNARY_OP_FRM_DYN, ops); + DONE; + } + [(set_attr "type" "vfwmuladd")]) + +;; This combine pattern does not correspond to an single instruction. +;; This is a temporary pattern produced by a combine pass and if there +;; is no further combine into widen pattern, then fall back to extend +;; pattern and non-widen fnms pattern. +(define_insn_and_split "*single_fnms<mode>" + [(set (match_operand:VWEXTF 0 "register_operand") + (minus:VWEXTF + (mult:VWEXTF + (neg:VWEXTF + (match_operand:VWEXTF 3 "register_operand")) + (float_extend:VWEXTF + (match_operand:<V_DOUBLE_TRUNC> 2 "register_operand"))) + (match_operand:VWEXTF 1 "register_operand")))] + "TARGET_VECTOR && can_create_pseudo_p ()" + "#" + "&& 1" + [(const_int 0)] + { + insn_code icode = code_for_pred_extend (<MODE>mode); + rtx tmp = gen_reg_rtx (<MODE>mode); + rtx ext_ops[] = {tmp, operands[2]}; + riscv_vector::emit_vlmax_insn (icode, riscv_vector::UNARY_OP, ext_ops); + + rtx ops[] = {operands[0], tmp, operands[3], operands[1]}; + riscv_vector::emit_vlmax_insn (code_for_pred_mul_neg (MINUS, <MODE>mode), + riscv_vector::TERNARY_OP_FRM_DYN, ops); + DONE; + } + [(set_attr "type" "vfwmuladd")]) + ;; ============================================================================= ;; Misc combine patterns ;; ============================================================================= diff --git a/gcc/config/riscv/autovec.md b/gcc/config/riscv/autovec.md index b968c6ddef3f..ac7599f3e0ad 100644 --- a/gcc/config/riscv/autovec.md +++ b/gcc/config/riscv/autovec.md @@ -1078,57 +1078,25 @@ ;; - vmadd ;; ------------------------------------------------------------------------- -;; We can't expand FMA for the following reasons: -;; 1. Before RA, we don't know which multiply-add instruction is the ideal one. -;; The vmacc is the ideal instruction when operands[3] overlaps operands[0]. -;; The vmadd is the ideal instruction when operands[1|2] overlaps operands[0]. -;; 2. According to vector.md, the multiply-add patterns has 'merge' operand which -;; is the operands[5]. Since operands[5] should overlap operands[0], this operand -;; should be allocated the same regno as operands[1|2|3]. -;; 3. The 'merge' operand is always a real merge operand and we don't allow undefined -;; operand. -;; 4. The operation of FMA pattern needs VLMAX vsetlvi which needs a VL operand. -;; -;; In this situation, we design the codegen of FMA as follows: -;; 1. clobber a scratch in the expand pattern of FMA. -;; 2. Let's RA decide which input operand (operands[1|2|3]) overlap operands[0]. -;; 3. Generate instructions (vmacc or vmadd) according to the register allocation -;; result after reload_completed. -(define_expand "fma<mode>4" - [(parallel - [(set (match_operand:VI 0 "register_operand") - (plus:VI - (mult:VI - (match_operand:VI 1 "register_operand") - (match_operand:VI 2 "register_operand")) - (match_operand:VI 3 "register_operand"))) - (clobber (match_dup 4))])] - "TARGET_VECTOR" - { - operands[4] = gen_reg_rtx (Pmode); - }) - -(define_insn_and_split "*fma<VI:mode><P:mode>" - [(set (match_operand:VI 0 "register_operand" "=vr, vr, ?&vr") +(define_insn_and_split "fma<mode>4" + [(set (match_operand:VI 0 "register_operand") (plus:VI (mult:VI - (match_operand:VI 1 "register_operand" " %0, vr, vr") - (match_operand:VI 2 "register_operand" " vr, vr, vr")) - (match_operand:VI 3 "register_operand" " vr, 0, vr"))) - (clobber (match_operand:P 4 "register_operand" "=r,r,r"))] - "TARGET_VECTOR" + (match_operand:VI 1 "register_operand") + (match_operand:VI 2 "register_operand")) + (match_operand:VI 3 "register_operand")))] + "TARGET_VECTOR && can_create_pseudo_p ()" "#" - "&& reload_completed" + "&& 1" [(const_int 0)] { - riscv_vector::emit_vlmax_vsetvl (<VI:MODE>mode, operands[4]); - rtx ops[] = {operands[0], operands[1], operands[2], operands[3], operands[0]}; - riscv_vector::emit_vlmax_insn_lra (code_for_pred_mul_plus (<VI:MODE>mode), - riscv_vector::TERNARY_OP, ops, operands[4]); + rtx ops[] = {operands[0], operands[1], operands[2], operands[3], + RVV_VUNDEF(<MODE>mode)}; + riscv_vector::emit_vlmax_insn (code_for_pred_mul_plus (<MODE>mode), + riscv_vector::TERNARY_OP, ops); DONE; } - [(set_attr "type" "vimuladd") - (set_attr "mode" "<VI:MODE>")]) + [(set_attr "type" "vector")]) ;; ------------------------------------------------------------------------- ;; ---- [INT] VNMSAC and VNMSUB @@ -1138,41 +1106,25 @@ ;; - vnmsub ;; ------------------------------------------------------------------------- -(define_expand "fnma<mode>4" - [(parallel - [(set (match_operand:VI 0 "register_operand") - (minus:VI - (match_operand:VI 3 "register_operand") - (mult:VI - (match_operand:VI 1 "register_operand") - (match_operand:VI 2 "register_operand")))) - (clobber (match_dup 4))])] - "TARGET_VECTOR" - { - operands[4] = gen_reg_rtx (Pmode); - }) - -(define_insn_and_split "*fnma<VI:mode><P:mode>" - [(set (match_operand:VI 0 "register_operand" "=vr, vr, ?&vr") - (minus:VI - (match_operand:VI 3 "register_operand" " vr, 0, vr") - (mult:VI - (match_operand:VI 1 "register_operand" " %0, vr, vr") - (match_operand:VI 2 "register_operand" " vr, vr, vr")))) - (clobber (match_operand:P 4 "register_operand" "=r,r,r"))] - "TARGET_VECTOR" +(define_insn_and_split "fnma<mode>4" + [(set (match_operand:VI 0 "register_operand") + (minus:VI + (match_operand:VI 3 "register_operand") + (mult:VI + (match_operand:VI 1 "register_operand") + (match_operand:VI 2 "register_operand"))))] + "TARGET_VECTOR && can_create_pseudo_p ()" "#" - "&& reload_completed" + "&& 1" [(const_int 0)] { - riscv_vector::emit_vlmax_vsetvl (<VI:MODE>mode, operands[4]); - rtx ops[] = {operands[0], operands[1], operands[2], operands[3], operands[0]}; - riscv_vector::emit_vlmax_insn_lra (code_for_pred_minus_mul (<VI:MODE>mode), - riscv_vector::TERNARY_OP, ops, operands[4]); + rtx ops[] = {operands[0], operands[1], operands[2], operands[3], + RVV_VUNDEF(<MODE>mode)}; + riscv_vector::emit_vlmax_insn (code_for_pred_minus_mul (<MODE>mode), + riscv_vector::TERNARY_OP, ops); DONE; } - [(set_attr "type" "vimuladd") - (set_attr "mode" "<VI:MODE>")]) + [(set_attr "type" "vector")]) ;; ------------------------------------------------------------------------- ;; ---- [FP] VFMACC and VFMADD @@ -1182,45 +1134,25 @@ ;; - vfmadd ;; ------------------------------------------------------------------------- -(define_expand "fma<mode>4" - [(parallel - [(set (match_operand:VF 0 "register_operand") - (unspec:VF - [(fma:VF - (match_operand:VF 1 "register_operand") - (match_operand:VF 2 "register_operand") - (match_operand:VF 3 "register_operand")) - (reg:SI FRM_REGNUM)] UNSPEC_VFFMA)) - (clobber (match_dup 4))])] - "TARGET_VECTOR" - { - operands[4] = gen_reg_rtx (Pmode); - } - [(set (attr "frm_mode") (symbol_ref "riscv_vector::FRM_DYN"))]) - -(define_insn_and_split "*fma<VF:mode><P:mode>" - [(set (match_operand:VF 0 "register_operand" "=vr, vr, ?&vr") - (unspec:VF - [(fma:VF - (match_operand:VF 1 "register_operand" " %0, vr, vr") - (match_operand:VF 2 "register_operand" " vr, vr, vr") - (match_operand:VF 3 "register_operand" " vr, 0, vr")) - (reg:SI FRM_REGNUM)] UNSPEC_VFFMA)) - (clobber (match_operand:P 4 "register_operand" "=r,r,r"))] - "TARGET_VECTOR" +(define_insn_and_split "fma<mode>4" + [(set (match_operand:VF 0 "register_operand") + (plus:VF + (mult:VF + (match_operand:VF 1 "register_operand") + (match_operand:VF 2 "register_operand")) + (match_operand:VF 3 "register_operand")))] + "TARGET_VECTOR && can_create_pseudo_p ()" "#" - "&& reload_completed" + "&& 1" [(const_int 0)] { - riscv_vector::emit_vlmax_vsetvl (<VF:MODE>mode, operands[4]); - rtx ops[] = {operands[0], operands[1], operands[2], operands[3], operands[0]}; - riscv_vector::emit_vlmax_insn_lra (code_for_pred_mul (PLUS, <VF:MODE>mode), - riscv_vector::TERNARY_OP_FRM_DYN, ops, operands[4]); + rtx ops[] = {operands[0], operands[1], operands[2], operands[3], + RVV_VUNDEF(<MODE>mode)}; + riscv_vector::emit_vlmax_insn (code_for_pred_mul (PLUS, <MODE>mode), + riscv_vector::TERNARY_OP_FRM_DYN, ops); DONE; } - [(set_attr "type" "vfmuladd") - (set_attr "mode" "<VF:MODE>") - (set (attr "frm_mode") (symbol_ref "riscv_vector::FRM_DYN"))]) + [(set_attr "type" "vector")]) ;; ------------------------------------------------------------------------- ;; ---- [FP] VFNMSAC and VFNMSUB @@ -1230,47 +1162,25 @@ ;; - vfnmsub ;; ------------------------------------------------------------------------- -(define_expand "fnma<mode>4" - [(parallel - [(set (match_operand:VF 0 "register_operand") - (unspec:VF - [(fma:VF - (neg:VF - (match_operand:VF 1 "register_operand")) - (match_operand:VF 2 "register_operand") - (match_operand:VF 3 "register_operand")) - (reg:SI FRM_REGNUM)] UNSPEC_VFFMA)) - (clobber (match_dup 4))])] - "TARGET_VECTOR" - { - operands[4] = gen_reg_rtx (Pmode); - } - [(set (attr "frm_mode") (symbol_ref "riscv_vector::FRM_DYN"))]) - -(define_insn_and_split "*fnma<VF:mode><P:mode>" - [(set (match_operand:VF 0 "register_operand" "=vr, vr, ?&vr") - (unspec:VF - [(fma:VF - (neg:VF - (match_operand:VF 1 "register_operand" " %0, vr, vr")) - (match_operand:VF 2 "register_operand" " vr, vr, vr") - (match_operand:VF 3 "register_operand" " vr, 0, vr")) - (reg:SI FRM_REGNUM)] UNSPEC_VFFMA)) - (clobber (match_operand:P 4 "register_operand" "=r,r,r"))] - "TARGET_VECTOR" +(define_insn_and_split "fnma<mode>4" + [(set (match_operand:VF 0 "register_operand") + (minus:VF + (match_operand:VF 3 "register_operand") + (mult:VF + (match_operand:VF 1 "register_operand") + (match_operand:VF 2 "register_operand"))))] + "TARGET_VECTOR && can_create_pseudo_p ()" "#" - "&& reload_completed" + "&& 1" [(const_int 0)] { - riscv_vector::emit_vlmax_vsetvl (<VF:MODE>mode, operands[4]); - rtx ops[] = {operands[0], operands[1], operands[2], operands[3], operands[0]}; - riscv_vector::emit_vlmax_insn_lra (code_for_pred_mul_neg (PLUS, <VF:MODE>mode), - riscv_vector::TERNARY_OP_FRM_DYN, ops, operands[4]); + rtx ops[] = {operands[0], operands[1], operands[2], operands[3], + RVV_VUNDEF(<MODE>mode)}; + riscv_vector::emit_vlmax_insn (code_for_pred_mul_neg (PLUS, <MODE>mode), + riscv_vector::TERNARY_OP_FRM_DYN, ops); DONE; } - [(set_attr "type" "vfmuladd") - (set_attr "mode" "<VF:MODE>") - (set (attr "frm_mode") (symbol_ref "riscv_vector::FRM_DYN"))]) + [(set_attr "type" "vector")]) ;; ------------------------------------------------------------------------- ;; ---- [FP] VFMSAC and VFMSUB @@ -1280,47 +1190,25 @@ ;; - vfmsub ;; ------------------------------------------------------------------------- -(define_expand "fms<mode>4" - [(parallel - [(set (match_operand:VF 0 "register_operand") - (unspec:VF - [(fma:VF - (match_operand:VF 1 "register_operand") - (match_operand:VF 2 "register_operand") - (neg:VF - (match_operand:VF 3 "register_operand"))) - (reg:SI FRM_REGNUM)] UNSPEC_VFFMA)) - (clobber (match_dup 4))])] - "TARGET_VECTOR" - { - operands[4] = gen_reg_rtx (Pmode); - } - [(set (attr "frm_mode") (symbol_ref "riscv_vector::FRM_DYN"))]) - -(define_insn_and_split "*fms<VF:mode><P:mode>" - [(set (match_operand:VF 0 "register_operand" "=vr, vr, ?&vr") - (unspec:VF - [(fma:VF - (match_operand:VF 1 "register_operand" " %0, vr, vr") - (match_operand:VF 2 "register_operand" " vr, vr, vr") - (neg:VF - (match_operand:VF 3 "register_operand" " vr, 0, vr"))) - (reg:SI FRM_REGNUM)] UNSPEC_VFFMA)) - (clobber (match_operand:P 4 "register_operand" "=r,r,r"))] - "TARGET_VECTOR" +(define_insn_and_split "fms<mode>4" + [(set (match_operand:VF 0 "register_operand") + (minus:VF + (mult:VF + (match_operand:VF 1 "register_operand") + (match_operand:VF 2 "register_operand")) + (match_operand:VF 3 "register_operand")))] + "TARGET_VECTOR && can_create_pseudo_p ()" "#" - "&& reload_completed" + "&& 1" [(const_int 0)] { - riscv_vector::emit_vlmax_vsetvl (<VF:MODE>mode, operands[4]); - rtx ops[] = {operands[0], operands[1], operands[2], operands[3], operands[0]}; - riscv_vector::emit_vlmax_insn_lra (code_for_pred_mul (MINUS, <VF:MODE>mode), - riscv_vector::TERNARY_OP_FRM_DYN, ops, operands[4]); + rtx ops[] = {operands[0], operands[1], operands[2], operands[3], + RVV_VUNDEF(<MODE>mode)}; + riscv_vector::emit_vlmax_insn (code_for_pred_mul (MINUS, <MODE>mode), + riscv_vector::TERNARY_OP_FRM_DYN, ops); DONE; } - [(set_attr "type" "vfmuladd") - (set_attr "mode" "<VF:MODE>") - (set (attr "frm_mode") (symbol_ref "riscv_vector::FRM_DYN"))]) + [(set_attr "type" "vector")]) ;; ------------------------------------------------------------------------- ;; ---- [FP] VFNMACC and VFNMADD @@ -1330,49 +1218,26 @@ ;; - vfnmadd ;; ------------------------------------------------------------------------- -(define_expand "fnms<mode>4" - [(parallel - [(set (match_operand:VF 0 "register_operand") - (unspec:VF - [(fma:VF - (neg:VF - (match_operand:VF 1 "register_operand")) - (match_operand:VF 2 "register_operand") - (neg:VF - (match_operand:VF 3 "register_operand"))) - (reg:SI FRM_REGNUM)] UNSPEC_VFFMA)) - (clobber (match_dup 4))])] - "TARGET_VECTOR" - { - operands[4] = gen_reg_rtx (Pmode); - } - [(set (attr "frm_mode") (symbol_ref "riscv_vector::FRM_DYN"))]) - -(define_insn_and_split "*fnms<VF:mode><P:mode>" - [(set (match_operand:VF 0 "register_operand" "=vr, vr, ?&vr") - (unspec:VF - [(fma:VF - (neg:VF - (match_operand:VF 1 "register_operand" " %0, vr, vr")) - (match_operand:VF 2 "register_operand" " vr, vr, vr") - (neg:VF - (match_operand:VF 3 "register_operand" " vr, 0, vr"))) - (reg:SI FRM_REGNUM)] UNSPEC_VFFMA)) - (clobber (match_operand:P 4 "register_operand" "=r,r,r"))] - "TARGET_VECTOR" +(define_insn_and_split "fnms<mode>4" + [(set (match_operand:VF 0 "register_operand") + (minus:VF + (neg:VF + (mult:VF + (match_operand:VF 1 "register_operand") + (match_operand:VF 2 "register_operand"))) + (match_operand:VF 3 "register_operand")))] + "TARGET_VECTOR && can_create_pseudo_p ()" "#" - "&& reload_completed" + "&& 1" [(const_int 0)] { - riscv_vector::emit_vlmax_vsetvl (<VF:MODE>mode, operands[4]); - rtx ops[] = {operands[0], operands[1], operands[2], operands[3], operands[0]}; - riscv_vector::emit_vlmax_insn_lra (code_for_pred_mul_neg (MINUS, <VF:MODE>mode), - riscv_vector::TERNARY_OP_FRM_DYN, ops, operands[4]); + rtx ops[] = {operands[0], operands[1], operands[2], operands[3], + RVV_VUNDEF(<MODE>mode)}; + riscv_vector::emit_vlmax_insn (code_for_pred_mul_neg (MINUS, <MODE>mode), + riscv_vector::TERNARY_OP_FRM_DYN, ops); DONE; } - [(set_attr "type" "vfmuladd") - (set_attr "mode" "<VF:MODE>") - (set (attr "frm_mode") (symbol_ref "riscv_vector::FRM_DYN"))]) + [(set_attr "type" "vector")]) ;; ========================================================================= ;; == SELECT_VL diff --git a/gcc/config/riscv/riscv-protos.h b/gcc/config/riscv/riscv-protos.h index 6d9367d96021..9ea0bcf15d36 100644 --- a/gcc/config/riscv/riscv-protos.h +++ b/gcc/config/riscv/riscv-protos.h @@ -459,7 +459,7 @@ void expand_select_vl (rtx *); void expand_load_store (rtx *, bool); void expand_gather_scatter (rtx *, bool); void expand_cond_len_ternop (unsigned, rtx *); -void prepare_ternary_operands (rtx *, bool = false); +void prepare_ternary_operands (rtx *); void expand_lanes_load_store (rtx *, bool); void expand_fold_extract_last (rtx *); diff --git a/gcc/config/riscv/riscv-v.cc b/gcc/config/riscv/riscv-v.cc index a9287e5d671f..f4dab9fceb8e 100644 --- a/gcc/config/riscv/riscv-v.cc +++ b/gcc/config/riscv/riscv-v.cc @@ -3246,15 +3246,15 @@ expand_reduction (unsigned unspec, unsigned insn_flags, rtx *ops, rtx init) /* Prepare ops for ternary operations. It can be called before or after RA. */ void -prepare_ternary_operands (rtx *ops, bool split_p) +prepare_ternary_operands (rtx *ops) { machine_mode mode = GET_MODE (ops[0]); - if (split_p - || (!rtx_equal_p (ops[2], ops[5]) - && !rtx_equal_p (ops[3], ops[5]) - && !rtx_equal_p (ops[4], ops[5]) - && riscv_get_v_regno_alignment (mode) == 8)) + if (!rtx_equal_p (ops[5], RVV_VUNDEF (mode)) + && (VECTOR_MODE_P (GET_MODE (ops[2])) + && !rtx_equal_p (ops[2], ops[5])) + && !rtx_equal_p (ops[3], ops[5]) + && !rtx_equal_p (ops[4], ops[5])) { /* RA will fail to find vector REG and report ICE, so we pre-merge the ops for LMUL = 8. */ @@ -3279,6 +3279,8 @@ prepare_ternary_operands (rtx *ops, bool split_p) /* TODO: ??? Maybe we could support splitting FMA (a, 4, b) into PLUS (ASHIFT (a, 2), b) according to uarchs. */ } + gcc_assert (rtx_equal_p (ops[5], RVV_VUNDEF (mode)) + || rtx_equal_p (ops[5], ops[2]) || rtx_equal_p (ops[5], ops[4])); } /* Expand VEC_MASK_LEN_{LOAD_LANES,STORE_LANES}. */ diff --git a/gcc/config/riscv/vector.md b/gcc/config/riscv/vector.md index 6d3c43e05ee2..c7c6ec3d6f13 100644 --- a/gcc/config/riscv/vector.md +++ b/gcc/config/riscv/vector.md @@ -5159,12 +5159,40 @@ (match_operand:VI 2 "register_operand") (match_operand:VI 3 "register_operand")) (match_operand:VI 4 "register_operand")) - (match_operand:VI 5 "register_operand")))] + (match_operand:VI 5 "vector_merge_operand")))] "TARGET_VECTOR" { riscv_vector::prepare_ternary_operands (operands); }) +(define_insn "*pred_mul_plus<mode>_undef" + [(set (match_operand:VI 0 "register_operand" "=vd, vd,?&vd, vr, vr,?&vr") + (if_then_else:VI + (unspec:<VM> + [(match_operand:<VM> 1 "vector_mask_operand" " vm, vm, vm,Wc1,Wc1, Wc1") + (match_operand 6 "vector_length_operand" " rK, rK, rK, rK, rK, rK") + (match_operand 7 "const_int_operand" " i, i, i, i, i, i") + (match_operand 8 "const_int_operand" " i, i, i, i, i, i") + (match_operand 9 "const_int_operand" " i, i, i, i, i, i") + (reg:SI VL_REGNUM) + (reg:SI VTYPE_REGNUM)] UNSPEC_VPREDICATE) + (plus:VI + (mult:VI + (match_operand:VI 3 "register_operand" " 0, vr, vr, 0, vr, vr") + (match_operand:VI 4 "register_operand" " vr, vr, vr, vr, vr, vr")) + (match_operand:VI 5 "register_operand" " vr, 0, vr, vr, 0, vr")) + (match_operand:VI 2 "vector_undef_operand")))] + "TARGET_VECTOR" + "@ + vmadd.vv\t%0,%4,%5%p1 + vmacc.vv\t%0,%3,%4%p1 + vmv.v.v\t%0,%4\;vmacc.vv\t%0,%3,%4%p1 + vmadd.vv\t%0,%4,%5%p1 + vmacc.vv\t%0,%3,%4%p1 + vmv.v.v\t%0,%5\;vmacc.vv\t%0,%3,%4%p1" + [(set_attr "type" "vimuladd") + (set_attr "mode" "<MODE>")]) + (define_insn "*pred_madd<mode>" [(set (match_operand:VI 0 "register_operand" "=vd,?&vd, vr,?&vr") (if_then_else:VI @@ -5227,35 +5255,6 @@ (set (attr "ma") (symbol_ref "riscv_vector::get_ma(operands[7])")) (set (attr "avl_type") (symbol_ref "INTVAL (operands[8])"))]) -(define_insn_and_rewrite "*pred_mul_plus<mode>" - [(set (match_operand:VI 0 "register_operand" "=&vr") - (if_then_else:VI - (unspec:<VM> - [(match_operand:<VM> 1 "vector_mask_operand" "vmWc1") - (match_operand 6 "vector_length_operand" " rK") - (match_operand 7 "const_int_operand" " i") - (match_operand 8 "const_int_operand" " i") - (match_operand 9 "const_int_operand" " i") - (reg:SI VL_REGNUM) - (reg:SI VTYPE_REGNUM)] UNSPEC_VPREDICATE) - (plus:VI - (mult:VI - (match_operand:VI 2 "register_operand" " vr") - (match_operand:VI 3 "register_operand" " vr")) - (match_operand:VI 4 "register_operand" " vr")) - (match_operand:VI 5 "register_operand" " vr")))] - "TARGET_VECTOR - && !rtx_equal_p (operands[2], operands[5]) - && !rtx_equal_p (operands[3], operands[5]) - && !rtx_equal_p (operands[4], operands[5])" - "#" - "&& reload_completed" - { - riscv_vector::prepare_ternary_operands (operands, true); - } - [(set_attr "type" "vimuladd") - (set_attr "mode" "<MODE>")]) - (define_expand "@pred_mul_plus<mode>_scalar" [(set (match_operand:VI_QHS 0 "register_operand") (if_then_else:VI_QHS @@ -5341,35 +5340,6 @@ (set (attr "ma") (symbol_ref "riscv_vector::get_ma(operands[7])")) (set (attr "avl_type") (symbol_ref "INTVAL (operands[8])"))]) -(define_insn_and_rewrite "*pred_mul_plus<mode>_scalar" - [(set (match_operand:VI 0 "register_operand" "=&vr") - (if_then_else:VI - (unspec:<VM> - [(match_operand:<VM> 1 "vector_mask_operand" "vmWc1") - (match_operand 6 "vector_length_operand" " rK") - (match_operand 7 "const_int_operand" " i") - (match_operand 8 "const_int_operand" " i") - (match_operand 9 "const_int_operand" " i") - (reg:SI VL_REGNUM) - (reg:SI VTYPE_REGNUM)] UNSPEC_VPREDICATE) - (plus:VI - (mult:VI - (vec_duplicate:VI - (match_operand:<VEL> 2 "register_operand" " r")) - (match_operand:VI 3 "register_operand" " vr")) - (match_operand:VI 4 "vector_arith_operand" " vr")) - (match_operand:VI 5 "register_operand" " vr")))] - "TARGET_VECTOR - && !rtx_equal_p (operands[3], operands[5]) - && !rtx_equal_p (operands[4], operands[5])" - "#" - "&& reload_completed" - { - riscv_vector::prepare_ternary_operands (operands, true); - } - [(set_attr "type" "vimuladd") - (set_attr "mode" "<MODE>")]) - (define_expand "@pred_mul_plus<mode>_scalar" [(set (match_operand:VI_D 0 "register_operand") (if_then_else:VI_D @@ -5470,36 +5440,6 @@ (set (attr "ma") (symbol_ref "riscv_vector::get_ma(operands[7])")) (set (attr "avl_type") (symbol_ref "INTVAL (operands[8])"))]) -(define_insn_and_rewrite "*pred_mul_plus<mode>_extended_scalar" - [(set (match_operand:VI_D 0 "register_operand" "=&vr") - (if_then_else:VI_D - (unspec:<VM> - [(match_operand:<VM> 1 "vector_mask_operand" "vmWc1") - (match_operand 6 "vector_length_operand" " rK") - (match_operand 7 "const_int_operand" " i") - (match_operand 8 "const_int_operand" " i") - (match_operand 9 "const_int_operand" " i") - (reg:SI VL_REGNUM) - (reg:SI VTYPE_REGNUM)] UNSPEC_VPREDICATE) - (plus:VI_D - (mult:VI_D - (vec_duplicate:VI_D - (sign_extend:<VEL> - (match_operand:<VSUBEL> 2 "register_operand" " r"))) - (match_operand:VI_D 3 "register_operand" " vr")) - (match_operand:VI_D 4 "register_operand" " vr")) - (match_operand:VI_D 5 "register_operand" " vr")))] - "TARGET_VECTOR - && !rtx_equal_p (operands[3], operands[5]) - && !rtx_equal_p (operands[4], operands[5])" - "#" - "&& reload_completed" - { - riscv_vector::prepare_ternary_operands (operands, true); - } - [(set_attr "type" "vimuladd") - (set_attr "mode" "<MODE>")]) - (define_expand "@pred_minus_mul<mode>" [(set (match_operand:VI 0 "register_operand") (if_then_else:VI @@ -5516,12 +5456,40 @@ (mult:VI (match_operand:VI 2 "register_operand") (match_operand:VI 3 "register_operand"))) - (match_operand:VI 5 "register_operand")))] + (match_operand:VI 5 "vector_merge_operand")))] "TARGET_VECTOR" { riscv_vector::prepare_ternary_operands (operands); }) +(define_insn "*pred_minus_mul<mode>_undef" + [(set (match_operand:VI 0 "register_operand" "=vd, vd,?&vd, vr, vr,?&vr") + (if_then_else:VI + (unspec:<VM> + [(match_operand:<VM> 1 "vector_mask_operand" " vm, vm, vm,Wc1,Wc1, Wc1") + (match_operand 6 "vector_length_operand" " rK, rK, rK, rK, rK, rK") + (match_operand 7 "const_int_operand" " i, i, i, i, i, i") + (match_operand 8 "const_int_operand" " i, i, i, i, i, i") + (match_operand 9 "const_int_operand" " i, i, i, i, i, i") + (reg:SI VL_REGNUM) + (reg:SI VTYPE_REGNUM)] UNSPEC_VPREDICATE) + (minus:VI + (match_operand:VI 5 "register_operand" " vr, 0, vr, vr, 0, vr") + (mult:VI + (match_operand:VI 3 "register_operand" " 0, vr, vr, 0, vr, vr") + (match_operand:VI 4 "register_operand" " vr, vr, vr, vr, vr, vr"))) + (match_operand:VI 2 "vector_undef_operand")))] + "TARGET_VECTOR" + "@ + vnmsub.vv\t%0,%4,%5%p1 + vnmsac.vv\t%0,%3,%4%p1 + vmv.v.v\t%0,%3\;vnmsub.vv\t%0,%4,%5%p1 + vnmsub.vv\t%0,%4,%5%p1 + vnmsac.vv\t%0,%3,%4%p1 + vmv.v.v\t%0,%3\;vnmsub.vv\t%0,%4,%5%p1" + [(set_attr "type" "vimuladd") + (set_attr "mode" "<MODE>")]) + (define_insn "*pred_nmsub<mode>" [(set (match_operand:VI 0 "register_operand" "=vd,?&vd, vr,?&vr") (if_then_else:VI @@ -5584,35 +5552,6 @@ (set (attr "ma") (symbol_ref "riscv_vector::get_ma(operands[7])")) (set (attr "avl_type") (symbol_ref "INTVAL (operands[8])"))]) -(define_insn_and_rewrite "*pred_minus_mul<mode>" - [(set (match_operand:VI 0 "register_operand" "=&vr") - (if_then_else:VI - (unspec:<VM> - [(match_operand:<VM> 1 "vector_mask_operand" "vmWc1") - (match_operand 6 "vector_length_operand" " rK") - (match_operand 7 "const_int_operand" " i") - (match_operand 8 "const_int_operand" " i") - (match_operand 9 "const_int_operand" " i") - (reg:SI VL_REGNUM) - (reg:SI VTYPE_REGNUM)] UNSPEC_VPREDICATE) - (minus:VI - (match_operand:VI 4 "vector_arith_operand" " vr") - (mult:VI - (match_operand:VI 2 "register_operand" " vr") - (match_operand:VI 3 "register_operand" " vr"))) - (match_operand:VI 5 "register_operand" " vr")))] - "TARGET_VECTOR - && !rtx_equal_p (operands[2], operands[5]) - && !rtx_equal_p (operands[3], operands[5]) - && !rtx_equal_p (operands[4], operands[5])" - "#" - "&& reload_completed" - { - riscv_vector::prepare_ternary_operands (operands, true); - } - [(set_attr "type" "vimuladd") - (set_attr "mode" "<MODE>")]) - (define_expand "@pred_minus_mul<mode>_scalar" [(set (match_operand:VI_QHS 0 "register_operand") (if_then_else:VI_QHS @@ -5698,35 +5637,6 @@ (set (attr "ma") (symbol_ref "riscv_vector::get_ma(operands[7])")) (set (attr "avl_type") (symbol_ref "INTVAL (operands[8])"))]) -(define_insn_and_rewrite "*pred_minus_mul<mode>_scalar" - [(set (match_operand:VI 0 "register_operand" "=&vr") - (if_then_else:VI - (unspec:<VM> - [(match_operand:<VM> 1 "vector_mask_operand" "vmWc1") - (match_operand 6 "vector_length_operand" " rK") - (match_operand 7 "const_int_operand" " i") - (match_operand 8 "const_int_operand" " i") - (match_operand 9 "const_int_operand" " i") - (reg:SI VL_REGNUM) - (reg:SI VTYPE_REGNUM)] UNSPEC_VPREDICATE) - (minus:VI - (match_operand:VI 4 "vector_arith_operand" " vr") - (mult:VI - (vec_duplicate:VI - (match_operand:<VEL> 2 "register_operand" " r")) - (match_operand:VI 3 "register_operand" " vr"))) - (match_operand:VI 5 "register_operand" " vr")))] - "TARGET_VECTOR - && !rtx_equal_p (operands[3], operands[5]) - && !rtx_equal_p (operands[4], operands[5])" - "#" - "&& reload_completed" - { - riscv_vector::prepare_ternary_operands (operands, true); - } - [(set_attr "type" "vimuladd") - (set_attr "mode" "<MODE>")]) - (define_expand "@pred_minus_mul<mode>_scalar" [(set (match_operand:VI_D 0 "register_operand") (if_then_else:VI_D @@ -5827,36 +5737,6 @@ (set (attr "ma") (symbol_ref "riscv_vector::get_ma(operands[7])")) (set (attr "avl_type") (symbol_ref "INTVAL (operands[8])"))]) -(define_insn_and_rewrite "*pred_minus_mul<mode>_extended_scalar" - [(set (match_operand:VI_D 0 "register_operand" "=&vr") - (if_then_else:VI_D - (unspec:<VM> - [(match_operand:<VM> 1 "vector_mask_operand" "vmWc1") - (match_operand 6 "vector_length_operand" " rK") - (match_operand 7 "const_int_operand" " i") - (match_operand 8 "const_int_operand" " i") - (match_operand 9 "const_int_operand" " i") - (reg:SI VL_REGNUM) - (reg:SI VTYPE_REGNUM)] UNSPEC_VPREDICATE) - (minus:VI_D - (match_operand:VI_D 4 "vector_arith_operand" " vr") - (mult:VI_D - (vec_duplicate:VI_D - (sign_extend:<VEL> - (match_operand:<VSUBEL> 2 "register_operand" " r"))) - (match_operand:VI_D 3 "register_operand" " vr"))) - (match_operand:VI_D 5 "register_operand" " vr")))] - "TARGET_VECTOR - && !rtx_equal_p (operands[3], operands[5]) - && !rtx_equal_p (operands[4], operands[5])" - "#" - "&& reload_completed" - { - riscv_vector::prepare_ternary_operands (operands, true); - } - [(set_attr "type" "vimuladd") - (set_attr "mode" "<MODE>")]) - ;; ------------------------------------------------------------------------------- ;; ---- Predicated widen integer ternary operations ;; ------------------------------------------------------------------------------- @@ -6433,12 +6313,44 @@ (match_operand:VF 2 "register_operand") (match_operand:VF 3 "register_operand")) (match_operand:VF 4 "register_operand")) - (match_operand:VF 5 "register_operand")))] + (match_operand:VF 5 "vector_merge_operand")))] "TARGET_VECTOR" { riscv_vector::prepare_ternary_operands (operands); }) +(define_insn "*pred_mul_<optab><mode>_undef" + [(set (match_operand:VF 0 "register_operand" "=vd,vd,?&vd, vr, vr,?&vr") + (if_then_else:VF + (unspec:<VM> + [(match_operand:<VM> 1 "vector_mask_operand" " vm,vm, vm,Wc1,Wc1, Wc1") + (match_operand 6 "vector_length_operand" " rK,rK, rK, rK, rK, rK") + (match_operand 7 "const_int_operand" " i, i, i, i, i, i") + (match_operand 8 "const_int_operand" " i, i, i, i, i, i") + (match_operand 9 "const_int_operand" " i, i, i, i, i, i") + (match_operand 10 "const_int_operand" " i, i, i, i, i, i") + (reg:SI VL_REGNUM) + (reg:SI VTYPE_REGNUM) + (reg:SI FRM_REGNUM)] UNSPEC_VPREDICATE) + (plus_minus:VF + (mult:VF + (match_operand:VF 3 "register_operand" " 0,vr, vr, 0, vr, vr") + (match_operand:VF 4 "register_operand" " vr,vr, vr, vr, vr, vr")) + (match_operand:VF 5 "register_operand" " vr, 0, vr, vr, 0, vr")) + (match_operand:VF 2 "vector_undef_operand")))] + "TARGET_VECTOR" + "@ + vf<madd_msub>.vv\t%0,%4,%5%p1 + vf<macc_msac>.vv\t%0,%3,%4%p1 + vmv.v.v\t%0,%3\;vf<madd_msub>.vv\t%0,%4,%5%p1 + vf<madd_msub>.vv\t%0,%4,%5%p1 + vf<macc_msac>.vv\t%0,%3,%4%p1 + vmv.v.v\t%0,%3\;vf<madd_msub>.vv\t%0,%4,%5%p1" + [(set_attr "type" "vfmuladd") + (set_attr "mode" "<MODE>") + (set (attr "frm_mode") + (symbol_ref "riscv_vector::get_frm_mode (operands[10])"))]) + (define_insn "*pred_<madd_msub><mode>" [(set (match_operand:VF 0 "register_operand" "=vd, ?&vd, vr, ?&vr") (if_then_else:VF @@ -6509,39 +6421,6 @@ (set (attr "frm_mode") (symbol_ref "riscv_vector::get_frm_mode (operands[9])"))]) -(define_insn_and_rewrite "*pred_mul_<optab><mode>" - [(set (match_operand:VF 0 "register_operand" "=&vr") - (if_then_else:VF - (unspec:<VM> - [(match_operand:<VM> 1 "vector_mask_operand" "vmWc1") - (match_operand 6 "vector_length_operand" " rK") - (match_operand 7 "const_int_operand" " i") - (match_operand 8 "const_int_operand" " i") - (match_operand 9 "const_int_operand" " i") - (match_operand 10 "const_int_operand" " i") - (reg:SI VL_REGNUM) - (reg:SI VTYPE_REGNUM) - (reg:SI FRM_REGNUM)] UNSPEC_VPREDICATE) - (plus_minus:VF - (mult:VF - (match_operand:VF 2 "register_operand" " vr") - (match_operand:VF 3 "register_operand" " vr")) - (match_operand:VF 4 "register_operand" " vr")) - (match_operand:VF 5 "register_operand" " vr")))] - "TARGET_VECTOR - && !rtx_equal_p (operands[2], operands[5]) - && !rtx_equal_p (operands[3], operands[5]) - && !rtx_equal_p (operands[4], operands[5])" - "#" - "&& reload_completed" - { - riscv_vector::prepare_ternary_operands (operands, true); - } - [(set_attr "type" "vfmuladd") - (set_attr "mode" "<MODE>") - (set (attr "frm_mode") - (symbol_ref "riscv_vector::get_frm_mode (operands[10])"))]) - (define_expand "@pred_mul_<optab><mode>_scalar" [(set (match_operand:VF 0 "register_operand") (if_then_else:VF @@ -6637,39 +6516,6 @@ (set (attr "frm_mode") (symbol_ref "riscv_vector::get_frm_mode (operands[9])"))]) -(define_insn_and_rewrite "*pred_mul_<optab><mode>_scalar" - [(set (match_operand:VF 0 "register_operand" "=&vr") - (if_then_else:VF - (unspec:<VM> - [(match_operand:<VM> 1 "vector_mask_operand" "vmWc1") - (match_operand 6 "vector_length_operand" " rK") - (match_operand 7 "const_int_operand" " i") - (match_operand 8 "const_int_operand" " i") - (match_operand 9 "const_int_operand" " i") - (match_operand 10 "const_int_operand" " i") - (reg:SI VL_REGNUM) - (reg:SI VTYPE_REGNUM) - (reg:SI FRM_REGNUM)] UNSPEC_VPREDICATE) - (plus_minus:VF - (mult:VF - (vec_duplicate:VF - (match_operand:<VEL> 2 "register_operand" " f")) - (match_operand:VF 3 "register_operand" " vr")) - (match_operand:VF 4 "vector_arith_operand" " vr")) - (match_operand:VF 5 "register_operand" " vr")))] - "TARGET_VECTOR - && !rtx_equal_p (operands[3], operands[5]) - && !rtx_equal_p (operands[4], operands[5])" - "#" - "&& reload_completed" - { - riscv_vector::prepare_ternary_operands (operands, true); - } - [(set_attr "type" "vfmuladd") - (set_attr "mode" "<MODE>") - (set (attr "frm_mode") - (symbol_ref "riscv_vector::get_frm_mode (operands[10])"))]) - (define_expand "@pred_mul_neg_<optab><mode>" [(set (match_operand:VF 0 "register_operand") (if_then_else:VF @@ -6689,12 +6535,45 @@ (match_operand:VF 2 "register_operand") (match_operand:VF 3 "register_operand"))) (match_operand:VF 4 "register_operand")) - (match_operand:VF 5 "register_operand")))] + (match_operand:VF 5 "vector_merge_operand")))] "TARGET_VECTOR" { riscv_vector::prepare_ternary_operands (operands); }) +(define_insn "*pred_mul_neg_<optab><mode>_undef" + [(set (match_operand:VF 0 "register_operand" "=vd,vd,?&vd, vr, vr,?&vr") + (if_then_else:VF + (unspec:<VM> + [(match_operand:<VM> 1 "vector_mask_operand" " vm,vm, vm,Wc1,Wc1, Wc1") + (match_operand 6 "vector_length_operand" " rK,rK, rK, rK, rK, rK") + (match_operand 7 "const_int_operand" " i, i, i, i, i, i") + (match_operand 8 "const_int_operand" " i, i, i, i, i, i") + (match_operand 9 "const_int_operand" " i, i, i, i, i, i") + (match_operand 10 "const_int_operand" " i, i, i, i, i, i") + (reg:SI VL_REGNUM) + (reg:SI VTYPE_REGNUM) + (reg:SI FRM_REGNUM)] UNSPEC_VPREDICATE) + (plus_minus:VF + (neg:VF + (mult:VF + (match_operand:VF 3 "register_operand" " 0,vr, vr, 0, vr, vr") + (match_operand:VF 4 "register_operand" " vr,vr, vr, vr, vr, vr"))) + (match_operand:VF 5 "register_operand" " vr, 0, vr, vr, 0, vr")) + (match_operand:VF 2 "vector_undef_operand")))] + "TARGET_VECTOR" + "@ + vf<nmsub_nmadd>.vv\t%0,%4,%5%p1 + vf<nmsac_nmacc>.vv\t%0,%3,%4%p1 + vmv.v.v\t%0,%3\;vf<nmsub_nmadd>.vv\t%0,%4,%5%p1 + vf<nmsub_nmadd>.vv\t%0,%4,%5%p1 + vf<nmsac_nmacc>.vv\t%0,%3,%4%p1 + vmv.v.v\t%0,%3\;vf<nmsub_nmadd>.vv\t%0,%4,%5%p1" + [(set_attr "type" "vfmuladd") + (set_attr "mode" "<MODE>") + (set (attr "frm_mode") + (symbol_ref "riscv_vector::get_frm_mode (operands[10])"))]) + (define_insn "*pred_<nmsub_nmadd><mode>" [(set (match_operand:VF 0 "register_operand" "=vd, ?&vd, vr, ?&vr") (if_then_else:VF @@ -6767,40 +6646,6 @@ (set (attr "frm_mode") (symbol_ref "riscv_vector::get_frm_mode (operands[9])"))]) -(define_insn_and_rewrite "*pred_mul_neg_<optab><mode>" - [(set (match_operand:VF 0 "register_operand" "=&vr") - (if_then_else:VF - (unspec:<VM> - [(match_operand:<VM> 1 "vector_mask_operand" "vmWc1") - (match_operand 6 "vector_length_operand" " rK") - (match_operand 7 "const_int_operand" " i") - (match_operand 8 "const_int_operand" " i") - (match_operand 9 "const_int_operand" " i") - (match_operand 10 "const_int_operand" " i") - (reg:SI VL_REGNUM) - (reg:SI VTYPE_REGNUM) - (reg:SI FRM_REGNUM)] UNSPEC_VPREDICATE) - (plus_minus:VF - (neg:VF - (mult:VF - (match_operand:VF 2 "register_operand" " vr") - (match_operand:VF 3 "register_operand" " vr"))) - (match_operand:VF 4 "vector_arith_operand" " vr")) - (match_operand:VF 5 "register_operand" " vr")))] - "TARGET_VECTOR - && !rtx_equal_p (operands[2], operands[5]) - && !rtx_equal_p (operands[3], operands[5]) - && !rtx_equal_p (operands[4], operands[5])" - "#" - "&& reload_completed" - { - riscv_vector::prepare_ternary_operands (operands, true); - } - [(set_attr "type" "vfmuladd") - (set_attr "mode" "<MODE>") - (set (attr "frm_mode") - (symbol_ref "riscv_vector::get_frm_mode (operands[10])"))]) - (define_expand "@pred_mul_neg_<optab><mode>_scalar" [(set (match_operand:VF 0 "register_operand") (if_then_else:VF @@ -6899,40 +6744,6 @@ (set (attr "frm_mode") (symbol_ref "riscv_vector::get_frm_mode (operands[9])"))]) -(define_insn_and_rewrite "*pred_mul_neg_<optab><mode>_scalar" - [(set (match_operand:VF 0 "register_operand" "=&vr") - (if_then_else:VF - (unspec:<VM> - [(match_operand:<VM> 1 "vector_mask_operand" "vmWc1") - (match_operand 6 "vector_length_operand" " rK") - (match_operand 7 "const_int_operand" " i") - (match_operand 8 "const_int_operand" " i") - (match_operand 9 "const_int_operand" " i") - (match_operand 10 "const_int_operand" " i") - (reg:SI VL_REGNUM) - (reg:SI VTYPE_REGNUM) - (reg:SI FRM_REGNUM)] UNSPEC_VPREDICATE) - (plus_minus:VF - (neg:VF - (mult:VF - (vec_duplicate:VF - (match_operand:<VEL> 2 "register_operand" " f")) - (match_operand:VF 3 "register_operand" " vr"))) - (match_operand:VF 4 "vector_arith_operand" " vr")) - (match_operand:VF 5 "register_operand" " vr")))] - "TARGET_VECTOR - && !rtx_equal_p (operands[3], operands[5]) - && !rtx_equal_p (operands[4], operands[5])" - "#" - "&& reload_completed" - { - riscv_vector::prepare_ternary_operands (operands, true); - } - [(set_attr "type" "vfmuladd") - (set_attr "mode" "<MODE>") - (set (attr "frm_mode") - (symbol_ref "riscv_vector::get_frm_mode (operands[10])"))]) - ;; ------------------------------------------------------------------------------- ;; ---- Predicated floating-point unary operations ;; ------------------------------------------------------------------------------- -- GitLab