From cdffc76393488a73671b70481cf8a4b7c289029d Mon Sep 17 00:00:00 2001 From: Jakub Jelinek <jakub@redhat.com> Date: Tue, 25 Feb 2025 09:33:21 +0100 Subject: [PATCH] openmp: Mark OpenMP atomic write expression as read [PR119000] The following testcase was emitting false positive warning that the rhs of #pragma omp atomic write was stored but not read, when the atomic actually does read it. The following patch fixes that by calling default_function_array_read_conversion on it, so that it is marked as read as well as converted from lvalue to rvalue. Furthermore, the code had if (code == NOP_EXPR) ... else ... if (code == NOP_EXPR) ... with none of ... parts changing code, so I've merged the two ifs. 2025-02-25 Jakub Jelinek <jakub@redhat.com> PR c/119000 * c-parser.cc (c_parser_omp_atomic): For omp write call default_function_array_read_conversion on the rhs expression. Merge the two adjacent if (code == NOP_EXPR) blocks. * c-c++-common/gomp/pr119000.c: New test. --- gcc/c/c-parser.cc | 22 ++++++++++------------ gcc/testsuite/c-c++-common/gomp/pr119000.c | 16 ++++++++++++++++ 2 files changed, 26 insertions(+), 12 deletions(-) create mode 100644 gcc/testsuite/c-c++-common/gomp/pr119000.c diff --git a/gcc/c/c-parser.cc b/gcc/c/c-parser.cc index 62c6bc031d69..7672e06fdd0d 100644 --- a/gcc/c/c-parser.cc +++ b/gcc/c/c-parser.cc @@ -22884,9 +22884,16 @@ c_parser_omp_atomic (location_t loc, c_parser *parser, bool openacc) goto saw_error; if (code == NOP_EXPR) { - lhs = c_parser_expression (parser).value; - lhs = c_fully_fold (lhs, false, NULL); - if (lhs == error_mark_node) + eloc = c_parser_peek_token (parser)->location; + expr = c_parser_expression (parser); + expr = default_function_array_read_conversion (eloc, expr); + /* atomic write is represented by OMP_ATOMIC with NOP_EXPR + opcode. */ + code = OMP_ATOMIC; + lhs = v; + v = NULL_TREE; + rhs = c_fully_fold (expr.value, false, NULL); + if (rhs == error_mark_node) goto saw_error; } else @@ -22899,15 +22906,6 @@ c_parser_omp_atomic (location_t loc, c_parser *parser, bool openacc) if (non_lvalue_p) lhs = non_lvalue (lhs); } - if (code == NOP_EXPR) - { - /* atomic write is represented by OMP_ATOMIC with NOP_EXPR - opcode. */ - code = OMP_ATOMIC; - rhs = lhs; - lhs = v; - v = NULL_TREE; - } goto done; case OMP_ATOMIC_CAPTURE_NEW: if (c_parser_next_token_is (parser, CPP_OPEN_BRACE)) diff --git a/gcc/testsuite/c-c++-common/gomp/pr119000.c b/gcc/testsuite/c-c++-common/gomp/pr119000.c new file mode 100644 index 000000000000..e5b7ab0c2b8c --- /dev/null +++ b/gcc/testsuite/c-c++-common/gomp/pr119000.c @@ -0,0 +1,16 @@ +/* PR c/119000 */ +/* { dg-do compile } */ +/* { dg-options "-fopenmp -Wunused-but-set-variable" } */ + +int +foo (void) +{ + int a = 1, b, c = 1, v; /* { dg-warning "variable 'b' set but not used" } */ + #pragma omp atomic write + v = a; + #pragma omp atomic read + b = v; + #pragma omp atomic update + v += c; + return v; +} -- GitLab