re PR tree-optimization/85863 (ICE in compiling spec2006 fortran test case solib...
authorRichard Biener <rguenther@suse.de>
Tue, 22 May 2018 09:55:49 +0000 (09:55 +0000)
committerRichard Biener <rguenth@gcc.gnu.org>
Tue, 22 May 2018 09:55:49 +0000 (09:55 +0000)
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

gcc/ChangeLog
gcc/testsuite/ChangeLog
gcc/testsuite/gfortran.fortran-torture/compile/pr85863.f [new file with mode: 0644]
gcc/tree-vect-stmts.c

index cec289203f6d7ad97ce3f13fa740d37e176dd1c7..c3ecb0be3a296d820406f5776a8e6a37ea7dbe17 100644 (file)
@@ -1,3 +1,11 @@
+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>
 
        PR target/85657
index b903b58401aa114b9302896efd682ae559a24472..939702c3187a3144f0c9c79748d91cc018bc0263 100644 (file)
@@ -1,3 +1,8 @@
+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>
 
        PR fortran/85841
diff --git a/gcc/testsuite/gfortran.fortran-torture/compile/pr85863.f b/gcc/testsuite/gfortran.fortran-torture/compile/pr85863.f
new file mode 100644 (file)
index 0000000..57673fd
--- /dev/null
@@ -0,0 +1,22 @@
+! { 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
index 4539f6a160ecb8930b0e48ce7524f5ab8bfbe7ee..169d8c029e8701e8b20c8cd5a816bb67bae5117e 100644 (file)
@@ -8661,7 +8661,7 @@ vect_is_simple_cond (tree cond, vec_info *vinfo,
 
   *comp_vectype = vectype1 ? vectype1 : vectype2;
   /* Invariant comparison.  */
-  if (! *comp_vectype)
+  if (! *comp_vectype && vectype)
     {
       tree scalar_type = TREE_TYPE (lhs);
       /* If we can widen the comparison to match vectype do so.  */
@@ -8773,7 +8773,7 @@ vectorizable_condition (gimple *stmt, gimple_stmt_iterator *gsi,
   else_clause = gimple_assign_rhs3 (stmt);
 
   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)
     return false;