Fails due to the (explicit or implicitly added) 'bind' clause as
tree-nested.c did not handle them.

In convert_nonlocal_omp_clauses, the following clauses are
missing: OMP_CLAUSE_AFFINITY, OMP_CLAUSE_DEVICE_TYPE,
OMP_CLAUSE_EXCLUSIVE, OMP_CLAUSE_INCLUSIVE.

I am not sure which of them should or must be added – but the
'bind' clause for sure; I did add 'affinity' but it is currently
removed during gimplification – hence, I think leaving it out
would also be an option.

Lightly tested. OK once/when testing has succeeded?

Tobias

-----------------
Mentor Graphics (Deutschland) GmbH, Arnulfstrasse 201, 80634 München 
Registergericht München HRB 106955, Geschäftsführer: Thomas Heurung, Frank 
Thürauf
OpenMP: Handle bind clause in tree-nested.c [PR100905]

	PR middle-end/100905

gcc/ChangeLog:

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

gcc/testsuite/ChangeLog:

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

diff --git a/gcc/testsuite/gfortran.dg/gomp/loop-3.f90 b/gcc/testsuite/gfortran.dg/gomp/loop-3.f90
new file mode 100644
index 00000000000..6d25b19735d
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/gomp/loop-3.f90
@@ -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
diff --git a/gcc/tree-nested.c b/gcc/tree-nested.c
index cea917a4d58..6ab3bfd5184 100644
--- a/gcc/tree-nested.c
+++ b/gcc/tree-nested.c
@@ -1365,6 +1365,7 @@ convert_nonlocal_omp_clauses (tree *pclauses, struct walk_stmt_info *wi)
 	case OMP_CLAUSE_FINAL:
 	case OMP_CLAUSE_IF:
 	case OMP_CLAUSE_NUM_THREADS:
+	case OMP_CLAUSE_AFFINITY:
 	case OMP_CLAUSE_DEPEND:
 	case OMP_CLAUSE_DEVICE:
 	case OMP_CLAUSE_NUM_TEAMS:
@@ -1484,6 +1485,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;
@@ -2140,6 +2142,7 @@ convert_local_omp_clauses (tree *pclauses, struct walk_stmt_info *wi)
 	case OMP_CLAUSE_IF:
 	case OMP_CLAUSE_NUM_THREADS:
 	case OMP_CLAUSE_DEPEND:
+	case OMP_CLAUSE_AFFINITY:
 	case OMP_CLAUSE_DEVICE:
 	case OMP_CLAUSE_NUM_TEAMS:
 	case OMP_CLAUSE_THREAD_LIMIT:
@@ -2264,6 +2267,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;

Reply via email to