OpenMP: Handle bind clause in tree-nested.c [PR100905]
authorTobias Burnus <tobias@codesourcery.com>
Fri, 4 Jun 2021 18:52:33 +0000 (20:52 +0200)
committerTobias Burnus <tobias@codesourcery.com>
Fri, 4 Jun 2021 18:52:33 +0000 (20:52 +0200)
PR middle-end/100905

gcc/ChangeLog:

* tree-nested.c (convert_nonlocal_omp_clauses,
convert_local_omp_clauses): Handle OMP_CLAUSE_BIND.

gcc/testsuite/ChangeLog:

* gfortran.dg/gomp/loop-3.f90: New test.

gcc/testsuite/gfortran.dg/gomp/loop-3.f90 [new file with mode: 0644]
gcc/tree-nested.c

diff --git a/gcc/testsuite/gfortran.dg/gomp/loop-3.f90 b/gcc/testsuite/gfortran.dg/gomp/loop-3.f90
new file mode 100644 (file)
index 0000000..6d25b19
--- /dev/null
@@ -0,0 +1,55 @@
+! PR middle-end/100905
+!
+PROGRAM test_loop_order_concurrent
+  implicit none
+  integer :: a, cc(64), dd(64)
+
+  dd = 54
+  cc = 99
+
+  call test_loop()
+  call test_affinity(a)
+  if (a /= 5) stop 3
+  call test_scan(cc, dd)
+  if (any (cc /= 99)) stop 4
+  if (dd(1) /= 5  .or. dd(2) /= 104) stop 5
+
+CONTAINS
+
+  SUBROUTINE test_loop()
+    INTEGER,DIMENSION(1024):: a, b, c
+    INTEGER:: i
+
+    DO i = 1, 1024
+       a(i) = 1
+       b(i) = i + 1
+       c(i) = 2*(i + 1)
+    END DO
+
+   !$omp loop order(concurrent) bind(thread)
+    DO i = 1, 1024
+       a(i) = a(i) + b(i)*c(i)
+    END DO
+
+    DO i = 1, 1024
+       if (a(i) /= 1 + (b(i)*c(i))) stop 1
+    END DO
+  END SUBROUTINE test_loop
+
+  SUBROUTINE test_affinity(aa)
+    integer :: aa
+    !$omp task affinity(aa)
+      a = 5
+    !$omp end task
+  end 
+
+  subroutine test_scan(c, d)
+    integer i, c(*), d(*)
+    !$omp simd reduction (inscan, +: a)
+    do i = 1, 64
+      d(i) = a
+      !$omp scan exclusive (a)
+      a = a + c(i)
+    end do
+  end
+END PROGRAM test_loop_order_concurrent
index cea917a..41cbca9 100644 (file)
@@ -1484,6 +1484,7 @@ convert_nonlocal_omp_clauses (tree *pclauses, struct walk_stmt_info *wi)
        case OMP_CLAUSE_AUTO:
        case OMP_CLAUSE_IF_PRESENT:
        case OMP_CLAUSE_FINALIZE:
+       case OMP_CLAUSE_BIND:
        case OMP_CLAUSE__CONDTEMP_:
        case OMP_CLAUSE__SCANTEMP_:
          break;
@@ -2264,6 +2265,7 @@ convert_local_omp_clauses (tree *pclauses, struct walk_stmt_info *wi)
        case OMP_CLAUSE_AUTO:
        case OMP_CLAUSE_IF_PRESENT:
        case OMP_CLAUSE_FINALIZE:
+       case OMP_CLAUSE_BIND:
        case OMP_CLAUSE__CONDTEMP_:
        case OMP_CLAUSE__SCANTEMP_:
          break;