From f949481a1f7ab973608a4ffcc0e342ab5a74e8e4 Mon Sep 17 00:00:00 2001 From: Richard Biener <rguenther@suse.de> Date: Tue, 16 Apr 2024 11:33:48 +0200 Subject: [PATCH] tree-optimization/114736 - SLP DFS walk issue The following fixes a DFS walk issue when identifying to be ignored latch edges. We have (bogus) SLP_TREE_REPRESENTATIVEs for VEC_PERM nodes so those have to be explicitly ignored as possibly being PHIs. PR tree-optimization/114736 * tree-vect-slp.cc (vect_optimize_slp_pass::is_cfg_latch_edge): Do not consider VEC_PERM_EXPRs as PHI use. * gfortran.dg/vect/pr114736.f90: New testcase. --- gcc/testsuite/gfortran.dg/vect/pr114736.f90 | 14 ++++++++++++++ gcc/tree-vect-slp.cc | 3 ++- 2 files changed, 16 insertions(+), 1 deletion(-) create mode 100644 gcc/testsuite/gfortran.dg/vect/pr114736.f90 diff --git a/gcc/testsuite/gfortran.dg/vect/pr114736.f90 b/gcc/testsuite/gfortran.dg/vect/pr114736.f90 new file mode 100644 index 000000000000..cdbfb6f415a9 --- /dev/null +++ b/gcc/testsuite/gfortran.dg/vect/pr114736.f90 @@ -0,0 +1,14 @@ +! { dg-do compile } +! { dg-additional-options "-O3" } + +SUBROUTINE MY_ROUTINE (N, A, B ) +IMPLICIT NONE +INTEGER, INTENT(IN) :: N +COMPLEX, INTENT(IN) :: A(N) +COMPLEX, INTENT(OUT) :: B(N) +INTEGER :: II +B(:) = (1.,0.) +DO II = 1, N-1 + B(II) = A(N-II+1) / A(N-II) +ENDDO +END SUBROUTINE MY_ROUTINE diff --git a/gcc/tree-vect-slp.cc b/gcc/tree-vect-slp.cc index f57684ca6856..30589e19a175 100644 --- a/gcc/tree-vect-slp.cc +++ b/gcc/tree-vect-slp.cc @@ -4309,7 +4309,8 @@ vect_optimize_slp_pass::is_cfg_latch_edge (graph_edge *ud) { slp_tree use = m_vertices[ud->src].node; slp_tree def = m_vertices[ud->dest].node; - if (SLP_TREE_DEF_TYPE (use) != vect_internal_def + if ((SLP_TREE_DEF_TYPE (use) != vect_internal_def + || SLP_TREE_CODE (use) == VEC_PERM_EXPR) || SLP_TREE_DEF_TYPE (def) != vect_internal_def) return false; -- GitLab