'omp scan' struct block seq update for OpenMP 5.x
While OpenMP 5.0 required a single structured block before and after the
'omp scan' directive, OpenMP 5.1 changed this to a 'structured block sequence,
denoting 2 or more executable statements in OpenMP 5.1 (ups!) and zero or more
in OpenMP 5.2. This updated C/C++ to accept zero statements (but still requires
the '{' ... '}' for the final-loop-body) and updates Fortran to accept zero or
more than one statements.
If there is no preceeding or succeeding executable statement, a warning is
shown.
gcc/c/ChangeLog:
* c-parser.cc (c_parser_omp_scan_loop_body): Handle
zero exec statements before/after 'omp scan'.
gcc/cp/ChangeLog:
* parser.cc (cp_parser_omp_scan_loop_body): Handle
zero exec statements before/after 'omp scan'.
gcc/fortran/ChangeLog:
* openmp.cc (gfc_resolve_omp_do_blocks): Handle zero
or more than one exec statements before/after 'omp scan'.
* trans-openmp.cc (gfc_trans_omp_do): Likewise.
libgomp/ChangeLog:
* testsuite/libgomp.c-c++-common/scan-1.c: New test.
* testsuite/libgomp.c/scan-23.c: New test.
* testsuite/libgomp.fortran/scan-2.f90: New test.
gcc/testsuite/ChangeLog:
* g++.dg/gomp/attrs-7.C: Update dg-error/dg-warning.
* gfortran.dg/gomp/loop-2.f90: Likewise.
* gfortran.dg/gomp/reduction5.f90: Likewise.
* gfortran.dg/gomp/reduction6.f90: Likewise.
* gfortran.dg/gomp/scan-1.f90: Likewise.
* gfortran.dg/gomp/taskloop-2.f90: Likewise.
* c-c++-common/gomp/scan-6.c: New test.
* gfortran.dg/gomp/scan-8.f90: New test.
gcc/c/c-parser.cc | 22 ++++-
gcc/cp/parser.cc | 24 ++++-
gcc/fortran/openmp.cc | 35 +++++--
gcc/fortran/trans-openmp.cc | 31 +++---
gcc/testsuite/c-c++-common/gomp/scan-6.c | 95 +++++++++++++++++++
gcc/testsuite/g++.dg/gomp/attrs-7.C | 8 +-
gcc/testsuite/gfortran.dg/gomp/loop-2.f90 | 10 +-
gcc/testsuite/gfortran.dg/gomp/reduction5.f90 | 2 +-
gcc/testsuite/gfortran.dg/gomp/reduction6.f90 | 4 +-
gcc/testsuite/gfortran.dg/gomp/scan-1.f90 | 9 +-
gcc/testsuite/gfortran.dg/gomp/scan-8.f90 | 96 +++++++++++++++++++
gcc/testsuite/gfortran.dg/gomp/taskloop-2.f90 | 12 +--
libgomp/testsuite/libgomp.c-c++-common/scan-1.c | 68 +++++++++++++
libgomp/testsuite/libgomp.c/scan-23.c | 121 ++++++++++++++++++++++++
libgomp/testsuite/libgomp.fortran/scan-2.f90 | 59 ++++++++++++
15 files changed, 545 insertions(+), 51 deletions(-)
@@ -20112,6 +20112,7 @@ c_parser_omp_scan_loop_body (c_parser *parser, bool open_brace_parsed)
tree substmt;
location_t loc;
tree clauses = NULL_TREE;
+ bool found_scan = false;
loc = c_parser_peek_token (parser)->location;
if (!open_brace_parsed
@@ -20122,7 +20123,15 @@ c_parser_omp_scan_loop_body (c_parser *parser, bool open_brace_parsed)
return;
}
- substmt = c_parser_omp_structured_block_sequence (parser, PRAGMA_OMP_SCAN);
+ if (c_parser_peek_token (parser)->pragma_kind != PRAGMA_OMP_SCAN)
+ substmt = c_parser_omp_structured_block_sequence (parser, PRAGMA_OMP_SCAN);
+ else
+ {
+ warning_at (c_parser_peek_token (parser)->location, 0,
+ "%<#pragma omp scan%> with zero preceding executable "
+ "statements");
+ substmt = build_empty_stmt (loc);
+ }
substmt = build2 (OMP_SCAN, void_type_node, substmt, NULL_TREE);
SET_EXPR_LOCATION (substmt, loc);
add_stmt (substmt);
@@ -20131,6 +20140,7 @@ c_parser_omp_scan_loop_body (c_parser *parser, bool open_brace_parsed)
if (c_parser_peek_token (parser)->pragma_kind == PRAGMA_OMP_SCAN)
{
enum omp_clause_code clause = OMP_CLAUSE_ERROR;
+ found_scan = true;
c_parser_consume_pragma (parser);
@@ -20160,7 +20170,15 @@ c_parser_omp_scan_loop_body (c_parser *parser, bool open_brace_parsed)
error ("expected %<#pragma omp scan%>");
clauses = c_finish_omp_clauses (clauses, C_ORT_OMP);
- substmt = c_parser_omp_structured_block_sequence (parser, PRAGMA_NONE);
+ if (!c_parser_next_token_is (parser, CPP_CLOSE_BRACE))
+ substmt = c_parser_omp_structured_block_sequence (parser, PRAGMA_NONE);
+ else
+ {
+ if (found_scan)
+ warning_at (loc, 0, "%<#pragma omp scan%> with zero succeeding "
+ "executable statements");
+ substmt = build_empty_stmt (loc);
+ }
substmt = build2 (OMP_SCAN, void_type_node, substmt, clauses);
SET_EXPR_LOCATION (substmt, loc);
add_stmt (substmt);
@@ -43521,19 +43521,29 @@ static void
cp_parser_omp_scan_loop_body (cp_parser *parser)
{
tree substmt, clauses = NULL_TREE;
+ bool found_scan = false;
matching_braces braces;
if (!braces.require_open (parser))
return;
- substmt = cp_parser_omp_structured_block_sequence (parser, PRAGMA_OMP_SCAN);
+ cp_token *tok = cp_lexer_peek_token (parser->lexer);
+ if (cp_parser_pragma_kind (tok) != PRAGMA_OMP_SCAN)
+ substmt = cp_parser_omp_structured_block_sequence (parser, PRAGMA_OMP_SCAN);
+ else
+ {
+ warning_at (tok->location, 0, "%<#pragma omp scan%> with zero preceding "
+ "executable statements");
+ substmt = build_empty_stmt (tok->location);
+ }
substmt = build2 (OMP_SCAN, void_type_node, substmt, NULL_TREE);
add_stmt (substmt);
- cp_token *tok = cp_lexer_peek_token (parser->lexer);
+ tok = cp_lexer_peek_token (parser->lexer);
if (cp_parser_pragma_kind (tok) == PRAGMA_OMP_SCAN)
{
enum omp_clause_code clause = OMP_CLAUSE_ERROR;
+ found_scan = true;
cp_lexer_consume_token (parser->lexer);
@@ -43564,7 +43574,15 @@ cp_parser_omp_scan_loop_body (cp_parser *parser)
error ("expected %<#pragma omp scan%>");
clauses = finish_omp_clauses (clauses, C_ORT_OMP);
- substmt = cp_parser_omp_structured_block_sequence (parser, PRAGMA_NONE);
+ if (!cp_lexer_next_token_is (parser->lexer, CPP_CLOSE_BRACE))
+ substmt = cp_parser_omp_structured_block_sequence (parser, PRAGMA_NONE);
+ else
+ {
+ if (found_scan)
+ warning_at (tok->location, 0, "%<#pragma omp scan%> with zero "
+ "succeeding executable statements");
+ substmt = build_empty_stmt (tok->location);
+ }
substmt = build2_loc (tok->location, OMP_SCAN, void_type_node, substmt,
clauses);
add_stmt (substmt);
@@ -9067,17 +9067,34 @@ gfc_resolve_omp_do_blocks (gfc_code *code, gfc_namespace *ns)
if (code->ext.omp_clauses->sched_kind != OMP_SCHED_NONE)
gfc_error ("SCHEDULE clause specified together with %<inscan%> "
"REDUCTION clause at %L", loc);
- if (!c->block
- || !c->block->next
- || !c->block->next->next
- || c->block->next->next->op != EXEC_OMP_SCAN
- || !c->block->next->next->next
- || c->block->next->next->next->next)
+ gfc_code *block = c->block ? c->block->next : NULL;
+ if (block && block->op != EXEC_OMP_SCAN)
+ while (block && block->next && block->next->op != EXEC_OMP_SCAN)
+ block = block->next;
+ if (!block
+ || (block->op != EXEC_OMP_SCAN
+ && (!block->next || block->next->op != EXEC_OMP_SCAN)))
gfc_error ("With INSCAN at %L, expected loop body with !$OMP SCAN "
- "between two structured-block-sequences", loc);
+ "between two structured block sequences", loc);
else
- /* Mark as checked; flag will be unset later. */
- c->block->next->next->ext.omp_clauses->if_present = true;
+ {
+ if (block->op == EXEC_OMP_SCAN)
+ gfc_warning (0, "!$OMP SCAN at %L with zero executable "
+ "statements in preceding structured block "
+ "sequence", &block->loc);
+ if ((block->op == EXEC_OMP_SCAN && !block->next)
+ || (block->next && block->next->op == EXEC_OMP_SCAN
+ && !block->next->next))
+ gfc_warning (0, "!$OMP SCAN at %L with zero executable "
+ "statements in succeeding structured block "
+ "sequence", block->op == EXEC_OMP_SCAN
+ ? &block->loc : &block->next->loc);
+ }
+ if (block && block->op != EXEC_OMP_SCAN)
+ block = block->next;
+ if (block && block->op == EXEC_OMP_SCAN)
+ /* Mark 'omp scan' as checked; flag will be unset later. */
+ block->ext.omp_clauses->if_present = true;
}
}
gfc_resolve_blocks (code->block, ns);
@@ -5603,26 +5603,29 @@ gfc_trans_omp_do (gfc_code *code, gfc_exec_op op, stmtblock_t *pblock,
/* Main loop body. */
if (clauses->lists[OMP_LIST_REDUCTION_INSCAN])
{
- gcc_assert (code->block->next->next->op == EXEC_OMP_SCAN);
- gcc_assert (code->block->next->next->next->next == NULL);
- locus *cloc = &code->block->next->next->loc;
- location_t loc = gfc_get_location (cloc);
-
- gfc_code code2 = *code->block->next;
- code2.next = NULL;
- tmp = gfc_trans_code (&code2);
+ gfc_code *code1, *scan, *code2, *tmpcode;
+ code1 = tmpcode = code->block->next;
+ if (tmpcode && tmpcode->op != EXEC_OMP_SCAN)
+ while (tmpcode && tmpcode->next && tmpcode->next->op != EXEC_OMP_SCAN)
+ tmpcode = tmpcode->next;
+ scan = tmpcode->op == EXEC_OMP_SCAN ? tmpcode : tmpcode->next;
+ if (code1 != scan)
+ tmpcode->next = NULL;
+ code2 = scan->next;
+ gcc_assert (scan->op == EXEC_OMP_SCAN);
+ location_t loc = gfc_get_location (&scan->loc);
+
+ tmp = code1 != scan ? gfc_trans_code (code1) : build_empty_stmt (loc);
tmp = build2 (OMP_SCAN, void_type_node, tmp, NULL_TREE);
SET_EXPR_LOCATION (tmp, loc);
gfc_add_expr_to_block (&body, tmp);
input_location = loc;
- tree c = gfc_trans_omp_clauses (&body,
- code->block->next->next->ext.omp_clauses,
- *cloc);
- code2 = *code->block->next->next->next;
- code2.next = NULL;
- tmp = gfc_trans_code (&code2);
+ tree c = gfc_trans_omp_clauses (&body, scan->ext.omp_clauses, scan->loc);
+ tmp = code2 ? gfc_trans_code (code2) : build_empty_stmt (loc);
tmp = build2 (OMP_SCAN, void_type_node, tmp, c);
SET_EXPR_LOCATION (tmp, loc);
+ if (code1 != scan)
+ tmpcode->next = scan;
}
else
tmp = gfc_trans_omp_code (code->block->next, true);
new file mode 100644
@@ -0,0 +1,95 @@
+void f1 (int, int, int);
+int iii (int, int, int);
+
+int
+s1 (int a1, int a2, int a3)
+{
+ int r = 0;
+ #pragma omp simd collapse(3) reduction (inscan, +:r)
+ for (int i = 0; i < a1; i++)
+ for (int j = 0; j < a2; j++)
+ for (int k = 0; k < a3; k++)
+ {
+ #pragma omp scan exclusive (r) /* { dg-warning "'#pragma omp scan' with zero preceding executable statements" } */
+ f1 (2, k, r);
+ }
+
+ #pragma omp simd collapse(3) reduction (inscan, +:r)
+ for (int i = 0; i < a1; i++)
+ for (int j = 0; j < a2; j++)
+ for (int k = 0; k < a3; k++)
+ {
+ r += iii (i, j, k);
+ #pragma omp scan exclusive (r) /* { dg-warning "'#pragma omp scan' with zero succeeding executable statements" } */
+ }
+
+ #pragma omp simd collapse(3) reduction (inscan, +:r)
+ for (int i = 0; i < a1; i++)
+ for (int j = 0; j < a2; j++)
+ for (int k = 0; k < a3; k++)
+ {
+ #pragma omp scan inclusive (r)
+ /* { dg-warning "'#pragma omp scan' with zero preceding executable statements" "" { target *-*-* } .-1 } */
+ /* { dg-warning "'#pragma omp scan' with zero succeeding executable statements" "" { target *-*-* } .-2 } */
+ }
+ return r;
+}
+
+int
+s2 (int a1, int a2, int a3)
+{
+ int r = 0;
+ #pragma omp simd collapse(3) reduction (inscan, +:r) /* { dg-error "'r' specified in 'inscan' 'reduction' clause but not in 'scan' directive claus" } */
+ for (int i = 0; i < a1; i++)
+ for (int j = 0; j < a2; j++)
+ for (int k = 0; k < a3; k++)
+ {
+ f1 (2, k, r);
+ r += iii (i, j, k); /* { dg-error "expected '#pragma omp scan'" "" { target c++ } } */
+ } /* { dg-error "expected '#pragma omp scan'" "" { target c } } */
+
+ r = 0;
+ #pragma omp simd collapse(3) reduction (inscan, +:r) /* { dg-error "'r' specified in 'inscan' 'reduction' clause but not in 'scan' directive claus" } */
+ for (int i = 0; i < a1; i++)
+ for (int j = 0; j < a2; j++)
+ for (int k = 0; k < a3; k++)
+ ; /* { dg-error "expected '\{' before ';' token" } */
+
+ #pragma omp simd collapse(3) reduction (inscan, +:r) /* { dg-error "'r' specified in 'inscan' 'reduction' clause but not in 'scan' directive claus" } */
+ for (int i = 0; i < a1; i++)
+ for (int j = 0; j < a2; j++)
+ for (int k = 0; k < a3; k++)
+ {
+ } /* { dg-error "expected expression before '\}' token" "" { target c } } */
+ /* { dg-error "expected primary-expression before '\}' token" "" { target c++ } .-1 } */
+ /* { dg-error "expected '#pragma omp scan'" "" { target *-*-* } .-2 } */
+
+
+ r = 0;
+ #pragma omp simd collapse(3) reduction (inscan, +:r)
+ for (int i = 0; i < a1; i++)
+ for (int j = 0; j < a2; j++)
+ for (int k = 0; k < a3; k++)
+ {
+ f1 (2, k, r);
+ #pragma omp scan inclusive (r)
+ #pragma omp scan inclusive (r) /* { dg-error "'#pragma omp scan' may only be used in a loop construct with 'inscan' 'reduction' clause" } */
+ r += iii (i, j, k);
+ }
+
+ #pragma omp scan inclusive (r) /* { dg-error "'#pragma omp scan' may only be used in a loop construct with 'inscan' 'reduction' clause" } */
+
+ r = 0;
+ #pragma omp simd collapse(3) reduction (inscan, +:r) /* { dg-error "'r' specified in 'inscan' 'reduction' clause but not in 'scan' directive clause" } */
+ for (int i = 0; i < a1; i++)
+ for (int j = 0; j < a2; j++)
+ for (int k = 0; k < a3; k++)
+ {
+ f1 (2, k, r);
+ {
+ #pragma omp scan inclusive (r) /* { dg-error "'#pragma omp scan' may only be used in a loop construct with 'inscan' 'reduction' clause" } */
+ }
+ r += iii (i, j, k); /* { dg-error "expected '#pragma omp scan'" "" { target c++ } } */
+ } /* { dg-error "expected '#pragma omp scan'" "" { target c } } */
+ return r;
+}
@@ -31,7 +31,7 @@ bar (int a, int *c, int *d, int *e, int *f)
[[omp::sequence (omp::directive (parallel), omp::directive (scan, exclusive (a)))]] // { dg-error "must be the only specified attribute on a statement" }
// { dg-error "#pragma omp scan" "" { target *-*-* } .-1 }
a += c[i]; // { dg-error "expected" }
- } // { dg-error "expected" }
+ }
[[omp::directive (parallel for reduction (inscan, +: a))]] // { dg-error "'a' specified in 'inscan' 'reduction' clause but not in 'scan' directive clause" }
for (i = 0; i < 64; i++)
{
@@ -39,7 +39,7 @@ bar (int a, int *c, int *d, int *e, int *f)
[[omp::sequence (directive (scan inclusive (a)), directive (critical))]] // { dg-error "must be the only specified attribute on a statement" }
// { dg-error "#pragma omp scan" "" { target *-*-* } .-1 }
d[i] = a; // { dg-error "expected" }
- } // { dg-error "expected" }
+ }
[[omp::directive (parallel for reduction (inscan, +: a))]] // { dg-error "'a' specified in 'inscan' 'reduction' clause but not in 'scan' directive clause" }
for (i = 0; i < 64; i++)
{
@@ -47,7 +47,7 @@ bar (int a, int *c, int *d, int *e, int *f)
[[gnu::cold]] [[omp::directive (scan, exclusive (a))]] // { dg-error "must be the only specified attribute on a statement" }
// { dg-error "#pragma omp scan" "" { target *-*-* } .-1 }
a += c[i]; // { dg-error "expected" }
- } // { dg-error "expected" }
+ }
[[omp::directive (parallel for reduction (inscan, +: a))]] // { dg-error "'a' specified in 'inscan' 'reduction' clause but not in 'scan' directive clause" }
for (i = 0; i < 64; i++)
{
@@ -55,7 +55,7 @@ bar (int a, int *c, int *d, int *e, int *f)
[[omp::directive (scan, exclusive (a)), gnu::cold]] // { dg-error "must be the only specified attribute on a statement" }
// { dg-error "#pragma omp scan" "" { target *-*-* } .-1 }
a += c[i]; // { dg-error "expected" }
- } // { dg-error "expected" }
+ }
[[omp::directive (parallel for reduction (inscan, +: a))]] // { dg-error "'a' specified in 'inscan' 'reduction' clause but not in 'scan' directive clause" }
for (i = 0; i < 64; i++)
{
@@ -18,23 +18,23 @@ do i = 1, 64
end do
!$omp loop reduction(inscan, +: r) ! { dg-error "'inscan' REDUCTION clause on construct other than DO, SIMD, DO SIMD, PARALLEL DO, PARALLEL DO SIMD" }
- ! { dg-error "With INSCAN at .1., expected loop body with ..OMP SCAN between two structured-block-sequences" "" { target *-*-* } .-1 }
+ ! { dg-error "With INSCAN at .1., expected loop body with ..OMP SCAN between two structured block sequences" "" { target *-*-* } .-1 }
do i = 1, 64
end do
!$omp teams loop reduction(inscan, +: r) ! { dg-error "'inscan' REDUCTION clause on construct other than DO, SIMD, DO SIMD, PARALLEL DO, PARALLEL DO SIMD" }
- ! { dg-error "With INSCAN at .1., expected loop body with ..OMP SCAN between two structured-block-sequences" "" { target *-*-* } .-1 }
+ ! { dg-error "With INSCAN at .1., expected loop body with ..OMP SCAN between two structured block sequences" "" { target *-*-* } .-1 }
do i = 1, 64
end do
!$omp parallel loop reduction(inscan, +: r) ! { dg-error "'inscan' REDUCTION clause on construct other than DO, SIMD, DO SIMD, PARALLEL DO, PARALLEL DO SIMD" }
- ! { dg-error "With INSCAN at .1., expected loop body with ..OMP SCAN between two structured-block-sequences" "" { target *-*-* } .-1 }
+ ! { dg-error "With INSCAN at .1., expected loop body with ..OMP SCAN between two structured block sequences" "" { target *-*-* } .-1 }
do i = 1, 64
end do
!$omp target teams loop reduction(inscan, +: r) ! { dg-error "'inscan' REDUCTION clause on construct other than DO, SIMD, DO SIMD, PARALLEL DO, PARALLEL DO SIMD" }
- ! { dg-error "With INSCAN at .1., expected loop body with ..OMP SCAN between two structured-block-sequences" "" { target *-*-* } .-1 }
+ ! { dg-error "With INSCAN at .1., expected loop body with ..OMP SCAN between two structured block sequences" "" { target *-*-* } .-1 }
do i = 1, 64
end do
!$omp target parallel loop reduction(inscan, +: r) ! { dg-error "'inscan' REDUCTION clause on construct other than DO, SIMD, DO SIMD, PARALLEL DO, PARALLEL DO SIMD" }
- ! { dg-error "With INSCAN at .1., expected loop body with ..OMP SCAN between two structured-block-sequences" "" { target *-*-* } .-1 }
+ ! { dg-error "With INSCAN at .1., expected loop body with ..OMP SCAN between two structured block sequences" "" { target *-*-* } .-1 }
do i = 1, 64
end do
@@ -21,7 +21,7 @@ end do
!$omp end task ! { dg-error "Unexpected !.OMP END TASK statement" }
!$omp taskloop reduction(inscan,+:a) in_reduction(+:b) ! { dg-error "'inscan' REDUCTION clause on construct other than DO, SIMD, DO SIMD, PARALLEL DO, PARALLEL DO SIMD" }
- ! { dg-error "34: With INSCAN at .1., expected loop body with ..OMP SCAN between two structured-block-sequences" "" { target *-*-* } .-1 }
+ ! { dg-error "34: With INSCAN at .1., expected loop body with ..OMP SCAN between two structured block sequences" "" { target *-*-* } .-1 }
! { dg-error "'inscan' and non-'inscan' 'reduction' clauses on the same construct" "" { target *-*-* } .-2 }
do i=1,10
a = a + 1
@@ -4,13 +4,13 @@ implicit none
integer :: a, b, i
a = 0
-!$omp simd reduction(inscan,+:a) ! { dg-error "30: With INSCAN at .1., expected loop body with ..OMP SCAN between two structured-block-sequences" }
+!$omp simd reduction(inscan,+:a) ! { dg-error "30: With INSCAN at .1., expected loop body with ..OMP SCAN between two structured block sequences" }
do i=1,10
a = a + 1
end do
!$omp parallel
-!$omp do reduction(inscan,+:a) ! { dg-error "28: With INSCAN at .1., expected loop body with ..OMP SCAN between two structured-block-sequences" }
+!$omp do reduction(inscan,+:a) ! { dg-error "28: With INSCAN at .1., expected loop body with ..OMP SCAN between two structured block sequences" }
do i=1,10
a = a + 1
end do
@@ -176,7 +176,7 @@ subroutine f8 (c, d, e, f)
use m
implicit none
integer i, c(64), d(64), e(64), f(64)
- !$omp do reduction (inscan, +: a, b) ! { dg-error "With INSCAN at .1., expected loop body with ..OMP SCAN between two structured-block-sequences" }
+ !$omp do reduction (inscan, +: a, b) ! { dg-error "With INSCAN at .1., expected loop body with ..OMP SCAN between two structured block sequences" }
do i = 1, 64
block
a = a + c(i)
@@ -189,7 +189,7 @@ subroutine f8 (c, d, e, f)
end block
end do
- !$omp do reduction (inscan, +: a, b) ! { dg-error "With INSCAN at .1., expected loop body with ..OMP SCAN between two structured-block-sequences" }
+ !$omp do reduction (inscan, +: a, b) ! { dg-error "With INSCAN at .1., expected loop body with ..OMP SCAN between two structured block sequences" }
do i = 1, 64
block
a = a + c(i)
@@ -207,12 +207,11 @@ subroutine f9
use m
implicit none
integer i
-! The first error (exit) causes two follow-up errors:
- !$omp simd reduction (inscan, +: a) ! { dg-error "With INSCAN at .1., expected loop body with ..OMP SCAN between two structured-block-sequences" }
+ !$omp simd reduction (inscan, +: a)
do i = 1, 64
if (i == 23) &
exit ! { dg-error "EXIT statement at .1. terminating ..OMP DO loop" } */
- !$omp scan exclusive (a) ! { dg-error "Unexpected ..OMP SCAN at .1. outside loop construct with 'inscan' REDUCTION clause" }
+ !$omp scan exclusive (a) ! { dg-warning "!.OMP SCAN at .1. with zero executable statements in preceding structured block sequence" }
a = a + 1
end do
end
new file mode 100644
@@ -0,0 +1,96 @@
+integer function s1 (a1, a2, a3) result(r)
+ implicit none
+ integer :: a1, a2, a3
+ integer :: i, j, k
+ procedure(integer) :: iii
+
+ r = 0
+ !$omp simd collapse(3) reduction (inscan, +:r)
+ do i = 1, a1
+ do j = 1, a2
+ do k = 1, a3
+ !$omp scan exclusive (r) ! { dg-warning "!.OMP SCAN at .1. with zero executable statements in preceding structured block sequence" }
+ call f1 (2, k, r)
+ end do
+ end do
+ end do
+
+ !$omp simd collapse(3) reduction (inscan, +:r)
+ do i = 1, a1
+ do j = 1, a2
+ do k = 1, a3
+ r = r + iii (i, j, k)
+ !$omp scan exclusive (r) ! { dg-warning "!.OMP SCAN at .1. with zero executable statements in succeeding structured block sequence" }
+ end do
+ end do
+ end do
+
+ !$omp simd collapse(3) reduction (inscan, +:r)
+ do i = 1, a1
+ do j = 1, a2
+ do k = 1, a3
+ !$omp scan inclusive (r)
+ ! { dg-warning "!.OMP SCAN at .1. with zero executable statements in preceding structured block sequence" "" { target *-*-* } .-1 }
+ ! { dg-warning "!.OMP SCAN at .1. with zero executable statements in succeeding structured block sequence" "" { target *-*-* } .-2 }
+ end do
+ end do
+ end do
+end function
+
+integer function s2 (a1, a2, a3) result(r)
+ implicit none
+ integer :: a1, a2, a3
+ integer :: i, j, k
+ procedure(integer) :: iii
+
+ r = 0
+ !$omp simd collapse(3) reduction (inscan, +:r) ! { dg-error "With INSCAN at .1., expected loop body with !.OMP SCAN between two structured block sequences" }
+ do i = 1, a1
+ do j = 1, a2
+ do k = 1, a3
+ call f1 (2, k, r)
+ r = r + iii (i, j, k)
+ end do
+ end do
+ end do
+
+ r = 0
+ !$omp simd collapse(3) reduction (inscan, +:r) ! { dg-error "With INSCAN at .1., expected loop body with !.OMP SCAN between two structured block sequences" }
+ do i = 1, a1
+ do j = 1, a2
+ do k = 1, a3
+ end do
+ end do
+ end do
+
+ r = 0
+ !$omp simd collapse(3) reduction (inscan, +:r)
+ do i = 1, a1
+ do j = 1, a2
+ do k = 1, a3
+ call f1 (2, k, r)
+ !$omp scan inclusive (r)
+ !$omp scan inclusive (r) ! { dg-error "Unexpected !.OMP SCAN at .1. outside loop construct with 'inscan' REDUCTION clause" }
+ r = r + iii (i, j, k)
+ end do
+ end do
+ end do
+
+ !$omp scan inclusive (r) ! { dg-error "Unexpected !.OMP SCAN at .1. outside loop construct with 'inscan' REDUCTION clause" }
+
+ r = 0
+ !$omp simd collapse(3) reduction (inscan, +:r) ! { dg-error "With INSCAN at .1., expected loop body with !.OMP SCAN between two structured block sequences" }
+ do i = 1, a1
+ do j = 1, a2
+ do k = 1, a3
+ call f1 (2, k, r)
+ block
+ !$omp scan inclusive (r) ! { dg-error "Unexpected !.OMP SCAN at .1. outside loop construct with 'inscan' REDUCTION clause" }
+ end block
+ r = r + iii (i, j, k)
+ end do
+ end do
+ end do
+
+
+end function
@@ -21,24 +21,24 @@ do i = 1, 64
end do
!$omp taskloop reduction(inscan, +: r) ! { dg-error "'inscan' REDUCTION clause on construct other than DO, SIMD, DO SIMD, PARALLEL DO, PARALLEL DO SIMD" }
-do i = 1, 64 ! { dg-error "OMP SCAN between two structured-block-sequences" "" { target *-*-* } .-1 }
+do i = 1, 64 ! { dg-error "OMP SCAN between two structured block sequences" "" { target *-*-* } .-1 }
end do
!$omp taskloop simd reduction(inscan, +: r) ! { dg-error "'inscan' REDUCTION clause on construct other than DO, SIMD, DO SIMD, PARALLEL DO, PARALLEL DO SIMD" }
-do i = 1, 64 ! { dg-error "OMP SCAN between two structured-block-sequences" "" { target *-*-* } .-1 }
+do i = 1, 64 ! { dg-error "OMP SCAN between two structured block sequences" "" { target *-*-* } .-1 }
end do
!$omp master taskloop reduction(inscan, +: r) ! { dg-error "'inscan' REDUCTION clause on construct other than DO, SIMD, DO SIMD, PARALLEL DO, PARALLEL DO SIMD" }
- ! { dg-error "With INSCAN at .1., expected loop body with ..OMP SCAN between two structured-block-sequences" "" { target *-*-* } .-1 }
+ ! { dg-error "With INSCAN at .1., expected loop body with ..OMP SCAN between two structured block sequences" "" { target *-*-* } .-1 }
do i = 1, 64
end do
!$omp master taskloop simd reduction(inscan, +: r) ! { dg-error "'inscan' REDUCTION clause on construct other than DO, SIMD, DO SIMD, PARALLEL DO, PARALLEL DO SIMD" }
- ! { dg-error "With INSCAN at .1., expected loop body with ..OMP SCAN between two structured-block-sequences" "" { target *-*-* } .-1 }
+ ! { dg-error "With INSCAN at .1., expected loop body with ..OMP SCAN between two structured block sequences" "" { target *-*-* } .-1 }
do i = 1, 64
end do
!$omp parallel master taskloop reduction(inscan, +: r) ! { dg-error "'inscan' REDUCTION clause on construct other than DO, SIMD, DO SIMD, PARALLEL DO, PARALLEL DO SIMD" }
-do i = 1, 64 ! { dg-error "OMP SCAN between two structured-block-sequences" "" { target *-*-* } .-1 }
+do i = 1, 64 ! { dg-error "OMP SCAN between two structured block sequences" "" { target *-*-* } .-1 }
end do
!$omp parallel master taskloop simd reduction(inscan, +: r) ! { dg-error "'inscan' REDUCTION clause on construct other than DO, SIMD, DO SIMD, PARALLEL DO, PARALLEL DO SIMD" }
-do i = 1, 64 ! { dg-error "OMP SCAN between two structured-block-sequences" "" { target *-*-* } .-1 }
+do i = 1, 64 ! { dg-error "OMP SCAN between two structured block sequences" "" { target *-*-* } .-1 }
end do
end
new file mode 100644
@@ -0,0 +1,68 @@
+#define N 30
+#define M 3
+
+int a[N][M], b[N][M], c[N][M];
+
+int
+main()
+{
+ int x, y, shift;
+ int j = 0;
+ for (int i = 0; i < N; i++)
+ {
+ a[i][0] = (i+1)*32;
+ a[i][1] = (i+1)*17;
+ a[i][2] = (i+1)*11;
+ b[i][0] = (i+1)*7;
+ b[i][1] = (i+1)*5;
+ b[i][2] = (i+1)*3;
+ }
+
+ x = 0;
+ #pragma omp parallel for simd collapse(2) reduction(inscan,+: x) private(shift)
+ for (int i = 0; i < N; i++)
+ for (int j = 0; j < M; j++)
+ {
+ x += a[i][j];
+ x += b[i][j];
+ #pragma omp scan inclusive(x)
+ shift = i + 29*j;
+ c[i][j] = x + shift;
+ }
+
+ y = 0;
+ for (int i = 0; i < N; i++)
+ for (int j = 0; j < M; j++)
+ {
+ y += a[i][j] + b[i][j];
+ if (c[i][j] != y + i + 29*j)
+ __builtin_abort ();
+ }
+ if (x != y)
+ __builtin_abort ();
+
+ x = 0;
+ #pragma omp parallel for simd collapse(2) reduction(inscan,+: x) private(shift)
+ for (int i = 0; i < N; i++)
+ for (int j = 0; j < M; j++)
+ {
+ shift = i + 29*j;
+ c[i][j] = x + shift;
+ #pragma omp scan exclusive(x)
+ x += a[i][j];
+ x += b[i][j];
+ }
+
+ y = 0;
+ for (int i = 0; i < N; i++)
+ for (int j = 0; j < M; j++)
+ {
+ if (c[i][j] != y + i + 29*j)
+ __builtin_abort ();
+ y += a[i][j] + b[i][j];
+ }
+ if (x != y)
+ __builtin_abort ();
+
+ return 0;
+}
new file mode 100644
@@ -0,0 +1,121 @@
+/* { dg-require-effective-target size32plus } */
+/* Same as scan-9.c, instead of using { ... } it simply uses multiple
+ executable stmt before 'omp scan'. */
+
+extern void abort (void);
+int r, a[1024], b[1024], x, y, z;
+
+__attribute__((noipa)) void
+foo (int *a, int *b)
+{
+ #pragma omp for reduction (inscan, +:r) lastprivate (conditional: z) firstprivate (x) private (y)
+ for (int i = 0; i < 1024; i++)
+ {
+ y = a[i];
+ r += y + x + 12;
+ #pragma omp scan inclusive(r)
+ b[i] = r;
+ if ((i & 1) == 0 && i < 937)
+ z = r;
+ }
+}
+
+__attribute__((noipa)) int
+bar (void)
+{
+ int s = 0;
+ #pragma omp parallel
+ #pragma omp for reduction (inscan, +:s) firstprivate (x) private (y) lastprivate (z)
+ for (int i = 0; i < 1024; i++)
+ {
+ y = 2 * a[i]; s += y; z = y;
+ #pragma omp scan inclusive(s)
+ y = s; b[i] = y + x + 12;
+ }
+ return s;
+}
+
+__attribute__((noipa)) void
+baz (int *a, int *b)
+{
+ #pragma omp parallel for reduction (inscan, +:r) firstprivate (x) lastprivate (x)
+ for (int i = 0; i < 1024; i++)
+ {
+ r += a[i] + x + 12; if (i == 1023) x = 29;
+ #pragma omp scan inclusive(r)
+ b[i] = r;
+ }
+}
+
+__attribute__((noipa)) int
+qux (void)
+{
+ int s = 0;
+ #pragma omp parallel for reduction (inscan, +:s) lastprivate (conditional: x, y)
+ for (int i = 0; i < 1024; i++)
+ {
+ s += 2 * a[i]; if ((a[i] & 1) == 1 && i < 825) x = a[i];
+ #pragma omp scan inclusive(s)
+ b[i] = s; if ((a[i] & 1) == 0 && i < 829) y = a[i];
+ }
+ return s;
+}
+
+int
+main ()
+{
+ int s = 0;
+ x = -12;
+ for (int i = 0; i < 1024; ++i)
+ {
+ a[i] = i;
+ b[i] = -1;
+ asm ("" : "+g" (i));
+ }
+ #pragma omp parallel
+ foo (a, b);
+ if (r != 1024 * 1023 / 2 || x != -12 || z != b[936])
+ abort ();
+ for (int i = 0; i < 1024; ++i)
+ {
+ s += i;
+ if (b[i] != s)
+ abort ();
+ else
+ b[i] = 25;
+ }
+ if (bar () != 1024 * 1023 || x != -12 || z != 2 * 1023)
+ abort ();
+ s = 0;
+ for (int i = 0; i < 1024; ++i)
+ {
+ s += 2 * i;
+ if (b[i] != s)
+ abort ();
+ else
+ b[i] = -1;
+ }
+ r = 0;
+ baz (a, b);
+ if (r != 1024 * 1023 / 2 || x != 29)
+ abort ();
+ s = 0;
+ for (int i = 0; i < 1024; ++i)
+ {
+ s += i;
+ if (b[i] != s)
+ abort ();
+ else
+ b[i] = -25;
+ }
+ if (qux () != 1024 * 1023 || x != 823 || y != 828)
+ abort ();
+ s = 0;
+ for (int i = 0; i < 1024; ++i)
+ {
+ s += 2 * i;
+ if (b[i] != s)
+ abort ();
+ }
+ return 0;
+}
new file mode 100644
@@ -0,0 +1,59 @@
+implicit none
+integer, parameter :: N = 30
+integer, parameter :: M = 3
+
+integer :: a(M,N), b(M,N), c(M,N)
+integer :: x, y, shift
+integer :: i, j
+
+do i = 1, N
+ a(1,i) = i*32
+ a(2,i) = i*17
+ a(3,i) = i*11
+ b(1,i) = i*7
+ b(2,i) = i*5
+ b(3,i) = i*3
+end do
+
+x = 0
+!$omp parallel do simd collapse(2) reduction(inscan,+: x) private(shift)
+do i = 1, N
+ do j = 1, M
+ x = x + a(j,i)
+ x = x + b(j,i)
+ !$omp scan inclusive(x)
+ shift = i + 29*j
+ c(j,i) = x + shift;
+ end do
+end do
+
+y = 0
+do i = 1, N
+ do j = 1, M
+ y = y + a(j,i) + b(j,i)
+ if (c(j,i) /= y + i + 29*j) error stop 1
+ end do
+end do
+if (x /= y) error stop 2
+
+x = 0
+!$omp parallel do simd collapse(2) reduction(inscan,+: x) private(shift)
+do i = 1, N
+ do j = 1, M
+ shift = i + 29*j
+ c(j,i) = x + shift;
+ !$omp scan exclusive(x)
+ x = x + a(j,i)
+ x = x + b(j,i)
+ end do
+end do
+
+y = 0
+do i = 1, N
+ do j = 1, M
+ if (c(j,i) /= y + i + 29*j) error stop 1
+ y = y + a(j,i) + b(j,i)
+ end do
+end do
+if (x /= y) error stop 2
+end