re PR tree-optimization/79315 (ICE while building SPEC CPU 2006 FP with -Ofast -ftree...
authorRichard Biener <rguenther@suse.de>
Wed, 1 Feb 2017 12:47:25 +0000 (12:47 +0000)
committerRichard Biener <rguenth@gcc.gnu.org>
Wed, 1 Feb 2017 12:47:25 +0000 (12:47 +0000)
2017-02-01  Richard Biener  <rguenther@suse.de>

PR middle-end/79315
* tree-cfg.c (move_stmt_op): Never set TREE_BLOCK when it
was not set before.

* gfortran.dg/pr79315.f90: New testcase.

From-SVN: r245089

gcc/ChangeLog
gcc/testsuite/ChangeLog
gcc/testsuite/gfortran.dg/pr79315.f90 [new file with mode: 0644]
gcc/tree-cfg.c

index 1b62c0b..40a1a92 100644 (file)
@@ -1,5 +1,11 @@
 2017-02-01  Richard Biener  <rguenther@suse.de>
 
+       PR middle-end/79315
+       * tree-cfg.c (move_stmt_op): Never set TREE_BLOCK when it
+       was not set before.
+
+2017-02-01  Richard Biener  <rguenther@suse.de>
+
        PR tree-optimization/71824
        * graphite-scop-detection.c (scop_detection::build_scop_breadth):
        Verify the loops are valid in the merged SESE region.
index dbbd485..489ecaf 100644 (file)
@@ -1,5 +1,10 @@
 2017-02-01  Richard Biener  <rguenther@suse.de>
 
+       PR middle-end/79315
+       * gfortran.dg/pr79315.f90: New testcase.
+
+2017-02-01  Richard Biener  <rguenther@suse.de>
+
        PR tree-optimization/71824
        * gcc.dg/graphite/pr71824.c: New testcase.
 
diff --git a/gcc/testsuite/gfortran.dg/pr79315.f90 b/gcc/testsuite/gfortran.dg/pr79315.f90
new file mode 100644 (file)
index 0000000..8cd8969
--- /dev/null
@@ -0,0 +1,52 @@
+! { dg-do compile }
+! { dg-require-effective-target pthread }
+! { dg-options "-Ofast -ftree-parallelize-loops=4" }
+
+SUBROUTINE wsm32D(t, &
+   w, &
+   den, &
+   p, &
+   delz, &
+                     its,&
+   ite, &
+   kts, &
+   kte  &
+                      )
+  REAL, DIMENSION( its:ite , kts:kte ),                           &
+        INTENT(INOUT) ::                                          &
+                                                               t
+  REAL, DIMENSION( ims:ime , kms:kme ),                           &
+        INTENT(IN   ) ::                                       w, &
+                                                             den, &
+                                                               p, &
+                                                            delz
+  REAL, DIMENSION( its:ite , kts:kte ) ::                         &
+        qs, &
+        xl, &
+        work1, &
+        work2, &
+        qs0, &
+        n0sfac
+      diffus(x,y) = 8.794e-5*x**1.81/y
+      diffac(a,b,c,d,e) = d*a*a/(xka(c,d)*rv*c*c)+1./(e*diffus(c,b))
+      venfac(a,b,c) = (viscos(b,c)/diffus(b,a))**(.3333333)       &
+             /viscos(b,c)**(.5)*(den0/c)**0.25
+      do loop = 1,loops
+      xa=-dldt/rv
+      do k = kts, kte
+        do i = its, ite
+          tr=ttp/t(i,k)
+          if(t(i,k).lt.ttp) then
+            qs(i,k) =psat*(tr**xa)*exp(xb*(1.-tr))
+          endif
+          qs0(i,k)  =psat*(tr**xa)*exp(xb*(1.-tr))
+        enddo
+        do i = its, ite
+          if(t(i,k).ge.t0c) then
+            work1(i,k) = diffac(xl(i,k),p(i,k),t(i,k),den(i,k),qs(i,k))
+          endif
+          work2(i,k) = venfac(p(i,k),t(i,k),den(i,k))
+        enddo
+      enddo
+      enddo                  ! big loops
+END SUBROUTINE wsm32D
index 315d0e1..a540416 100644 (file)
@@ -6636,11 +6636,12 @@ move_stmt_op (tree *tp, int *walk_subtrees, void *data)
   if (EXPR_P (t))
     {
       tree block = TREE_BLOCK (t);
-      if (block == p->orig_block
-         || (p->orig_block == NULL_TREE
-             && block != NULL_TREE))
+      if (block == NULL_TREE)
+       ;
+      else if (block == p->orig_block
+              || p->orig_block == NULL_TREE)
        TREE_SET_BLOCK (t, p->new_block);
-      else if (flag_checking && block != NULL_TREE)
+      else if (flag_checking)
        {
          while (block && TREE_CODE (block) == BLOCK && block != p->orig_block)
            block = BLOCK_SUPERCONTEXT (block);