re PR tree-optimization/33301 (wrong vectorization factor due to an invariant type...
authorDorit Nuzman <dorit@il.ibm.com>
Sat, 8 Sep 2007 09:19:39 +0000 (09:19 +0000)
committerDorit Nuzman <dorit@gcc.gnu.org>
Sat, 8 Sep 2007 09:19:39 +0000 (09:19 +0000)
        PR tree-optimization/33301
        * tree-vect-analyze (analyze_operations): Look at the type of the rhs
        when relevant.

From-SVN: r128265

gcc/ChangeLog
gcc/testsuite/ChangeLog
gcc/testsuite/gfortran.dg/vect/pr33301.f [new file with mode: 0644]
gcc/tree-vect-analyze.c

index 22c3c6a3536650cfd49e8b52aab145c56fc03677..9fd59ac7cb384b248c95fd709b4f64a2d7436273 100644 (file)
@@ -1,3 +1,9 @@
+2007-09-08  Dorit Nuzman  <dorit@il.ibm.com>
+
+       PR tree-optimization/33301
+       * tree-vect-analyze (analyze_operations): Look at the type of the rhs
+       when relevant.
+
 2007-09-07  Zdenek Dvorak  <ook@ucw.cz>
 
        PR tree-optimization/32183
index 9ca621c2fbfa43a9ba2e05f9c3aa0b31184b9554..71d7f211a96497e2dcbfc9a7302699939f89989c 100644 (file)
@@ -1,3 +1,8 @@
+2007-09-08  Dorit Nuzman  <dorit@il.ibm.com>
+
+       PR tree-optimization/33301
+       * gfortran.dg/vect/pr33301.f: New test.
+
 2007-09-07  Jerry DeLisle  <jvdelisle@gcc.gnu.org>
 
        PR libfortran/33307
diff --git a/gcc/testsuite/gfortran.dg/vect/pr33301.f b/gcc/testsuite/gfortran.dg/vect/pr33301.f
new file mode 100644 (file)
index 0000000..0713f3e
--- /dev/null
@@ -0,0 +1,14 @@
+c { dg-do compile }
+C Derived from lapack
+      SUBROUTINE ZGELSX( M, N, NRHS, A, LDA, B, LDB, JPVT, RCOND, RANK,
+     $                   WORK, RWORK, INFO )
+      COMPLEX(kind=8)         WORK( * )
+c     Following declaration added on transfer to gfortran testsuite.
+c     It is present in original lapack source
+      integer rank
+            DO 20 I = 1, RANK
+               WORK( ISMAX+I-1 ) = S2*WORK( ISMAX+I-1 )
+   20       CONTINUE
+      END
+
+c { dg-final { cleanup-tree-dump "vect" } }
index 35e38d01471755cd057b551a8e7cb0520c66a922..a37fcf4395b4282245601e0662018563409686db 100644 (file)
@@ -216,21 +216,38 @@ vect_determine_vectorization_factor (loop_vec_info loop_vinfo)
            }
          else
            {
+             tree operation;
+
              gcc_assert (! STMT_VINFO_DATA_REF (stmt_info)
                          && !is_pattern_stmt_p (stmt_info));
 
-             /* We set the vectype according to the type of the result (lhs).
+             /* We generally set the vectype according to the type of the 
+                result (lhs).
                 For stmts whose result-type is different than the type of the
                 arguments (e.g. demotion, promotion), vectype will be reset 
                 appropriately (later).  Note that we have to visit the smallest 
                 datatype in this function, because that determines the VF.  
                 If the smallest datatype in the loop is present only as the 
                 rhs of a promotion operation - we'd miss it here.
-                However, in such a case, that a variable of this datatype
-                does not appear in the lhs anywhere in the loop, it shouldn't
-                affect the vectorization factor.   */
+                Such a case, where a variable of this datatype does not appear 
+                in the lhs anywhere in the loop, can only occur if it's an
+                invariant: e.g.: 'int_x = (int) short_inv', which we'd expect
+                to have been optimized away by invariant motion. However, we 
+                cannot rely on invariant motion to always take invariants out
+                of the loop, and so in the case of promotion we also have to 
+                check the rhs.  */
              scalar_type = TREE_TYPE (GIMPLE_STMT_OPERAND (stmt, 0));
 
+             operation = GIMPLE_STMT_OPERAND (stmt, 1);
+             if (TREE_CODE (operation) == NOP_EXPR
+                 || TREE_CODE (operation) == CONVERT_EXPR
+                 || TREE_CODE (operation) ==  WIDEN_MULT_EXPR)
+               {
+                 tree rhs_type = TREE_TYPE (TREE_OPERAND (operation, 0));
+                 if (TYPE_SIZE_UNIT (rhs_type) < TYPE_SIZE_UNIT (scalar_type))
+                   scalar_type = TREE_TYPE (TREE_OPERAND (operation, 0));
+               }
+
              if (vect_print_dump_info (REPORT_DETAILS))
                {
                  fprintf (vect_dump, "get vectype for scalar type:  ");