Commit 4515e413 by Richard Biener Committed by Richard Biener

re PR tree-optimization/85863 (ICE in compiling spec2006 fortran test case…

re PR tree-optimization/85863 (ICE in compiling spec2006 fortran test case solib.fppized.f starting with r260283)

2018-05-22  Richard Biener  <rguenther@suse.de>

	PR tree-optimization/85863
	* tree-vect-stmts.c (vect_is_simple_cond): Only widen invariant
	comparisons when vectype is specified.
	(vectorizable_condition): Do not specify vectype for
	vect_is_simple_cond when SLP vectorizing.

	* gfortran.fortran-torture/compile/pr85863.f: New testcase.

From-SVN: r260501
parent c5470754
2018-05-22 Richard Biener <rguenther@suse.de>
PR tree-optimization/85863
* tree-vect-stmts.c (vect_is_simple_cond): Only widen invariant
comparisons when vectype is specified.
(vectorizable_condition): Do not specify vectype for
vect_is_simple_cond when SLP vectorizing.
2018-05-21 Michael Meissner <meissner@linux.ibm.com> 2018-05-21 Michael Meissner <meissner@linux.ibm.com>
PR target/85657 PR target/85657
......
2018-05-22 Richard Biener <rguenther@suse.de>
PR tree-optimization/85863
* gfortran.fortran-torture/compile/pr85863.f: New testcase.
2018-05-22 Janus Weil <janus@gcc.gnu.org> 2018-05-22 Janus Weil <janus@gcc.gnu.org>
PR fortran/85841 PR fortran/85841
......
! { dg-do compile }
! { dg-additional-options "-ffast-math -ftree-vectorize" }
SUBROUTINE SOBOOK(MHSO,HSOMAX,MS)
IMPLICIT DOUBLE PRECISION(A-H,O-Z)
COMPLEX*16 HSOT,HSO1(2)
PARAMETER (ZERO=0.0D+00,TWO=2.0D+00)
DIMENSION SOL1(3,2),SOL2(3)
CALL FOO(SOL1,SOL2)
SQRT2=SQRT(TWO)
DO IH=1,MHSO
IF(MS.EQ.0) THEN
HSO1(IH) = DCMPLX(ZERO,-SOL1(3,IH))
HSOT = DCMPLX(ZERO,-SOL2(3))
ELSE
HSO1(IH) = DCMPLX(-SOL1(2,IH),SOL1(1,IH))/SQRT2
HSOT = DCMPLX(-SOL2(2),SOL2(1))/SQRT2
ENDIF
ENDDO
HSOT=HSOT+HSO1(1)
HSOMAX=MAX(HSOMAX,ABS(HSOT))
RETURN
END
...@@ -8661,7 +8661,7 @@ vect_is_simple_cond (tree cond, vec_info *vinfo, ...@@ -8661,7 +8661,7 @@ vect_is_simple_cond (tree cond, vec_info *vinfo,
*comp_vectype = vectype1 ? vectype1 : vectype2; *comp_vectype = vectype1 ? vectype1 : vectype2;
/* Invariant comparison. */ /* Invariant comparison. */
if (! *comp_vectype) if (! *comp_vectype && vectype)
{ {
tree scalar_type = TREE_TYPE (lhs); tree scalar_type = TREE_TYPE (lhs);
/* If we can widen the comparison to match vectype do so. */ /* If we can widen the comparison to match vectype do so. */
...@@ -8773,7 +8773,7 @@ vectorizable_condition (gimple *stmt, gimple_stmt_iterator *gsi, ...@@ -8773,7 +8773,7 @@ vectorizable_condition (gimple *stmt, gimple_stmt_iterator *gsi,
else_clause = gimple_assign_rhs3 (stmt); else_clause = gimple_assign_rhs3 (stmt);
if (!vect_is_simple_cond (cond_expr, stmt_info->vinfo, if (!vect_is_simple_cond (cond_expr, stmt_info->vinfo,
&comp_vectype, &dts[0], vectype) &comp_vectype, &dts[0], slp_node ? NULL : vectype)
|| !comp_vectype) || !comp_vectype)
return false; return false;
......
Markdown is supported
0% or
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment