From 37127ed975e09813eaa2d1cf1062055fce45dd16 Mon Sep 17 00:00:00 2001 From: Jakub Jelinek <jakub@redhat.com> Date: Thu, 22 Feb 2024 19:32:02 +0100 Subject: [PATCH] c: Handle scoped attributes in __has*attribute and scoped attribute parsing changes in -std=c11 etc. modes [PR114007] We aren't able to parse __has_attribute (vendor::attr) (and __has_c_attribute and __has_cpp_attribute) in strict C < C23 modes. While in -std=gnu* modes or in -std=c23 there is CPP_SCOPE token, in -std=c* (except for -std=c23) there are is just a pair of CPP_COLON tokens. The c-lex.cc hunk adds support for that. That leads to a question if we should return 1 or 0 from __has_attribute (gnu::unused) or not, because while [[gnu::unused]] is parsed fine in -std=gnu*/-std=c23 modes (sure, with pedwarn for < C23), we do not parse it at all in -std=c* (except for -std=c23), we only parse [[__extension__ gnu::unused]] there. While the __extension__ in there helps to avoid the pedwarn, I think it is better to be consistent between GNU and strict C < C23 modes and parse [[gnu::unused]] too; on the other side, I think parsing [[__extension__ gnu : : unused]] is too weird and undesirable. So, the following patch adds a flag during preprocessing at the point where we normally create CPP_SCOPE tokens out of 2 consecutive colons on the first CPP_COLON to mark the consecutive case (as we are tight on the bits, I've reused the PURE_ZERO flag, which is used just by the C++ FE and only ever set (both C and C++) on CPP_NUMBER tokens, this new flag has the same value and is only ever used on CPP_COLON tokens) and instead of checking loose_scope_p argument (i.e. whether it is [[__extension__ ...]] or not), it just parses CPP_SCOPE or CPP_COLON with CLONE_SCOPE flag followed by another CPP_COLON the same. The latter will never appear in >= C23 or -std=gnu* modes, though guarding its use say with flag_iso && !flag_isoc23 && doesn't really work because the __extension__ case temporarily clears flag_iso flag. This makes the -std=c11 etc. behavior more similar to -std=gnu11 or -std=c23, the only difference I'm aware of are the #define JOIN2(A, B) A##B [[vendor JOIN2(:,:) attr]] [[__extension__ vendor JOIN2(:,:) attr]] cases, which are accepted in the latter modes, but results in error in -std=c11; but the error is during preprocessing that :: doesn't form a valid preprocessing token, which is true, so just don't do that if you try to have __STRICT_ANSI__ && __STDC_VERSION__ <= 201710L compatibility. 2024-02-22 Jakub Jelinek <jakub@redhat.com> PR c/114007 gcc/ * doc/extend.texi: (__extension__): Remove comments about scope tokens vs. two colons. gcc/c-family/ * c-lex.cc (c_common_has_attribute): Parse 2 CPP_COLONs with the first one with COLON_SCOPE flag the same as CPP_SCOPE. gcc/c/ * c-parser.cc (c_parser_std_attribute): Remove loose_scope_p argument. Instead of checking it, parse 2 CPP_COLONs with the first one with COLON_SCOPE flag the same as CPP_SCOPE. (c_parser_std_attribute_list): Remove loose_scope_p argument, don't pass it to c_parser_std_attribute. (c_parser_std_attribute_specifier): Adjust c_parser_std_attribute_list caller. gcc/testsuite/ * gcc.dg/c23-attr-syntax-6.c: Adjust testcase for :: being valid even in -std=c11 even without __extension__ and : : etc. not being valid anymore even with __extension__. * gcc.dg/c23-attr-syntax-7.c: Likewise. * gcc.dg/c23-attr-syntax-8.c: New test. libcpp/ * include/cpplib.h (COLON_SCOPE): Define to PURE_ZERO. * lex.cc (_cpp_lex_direct): When lexing CPP_COLON with another colon after it, if !CPP_OPTION (pfile, scope) set COLON_SCOPE flag on the first CPP_COLON token. --- gcc/c-family/c-lex.cc | 22 ++++++++- gcc/c/c-parser.cc | 14 +++--- gcc/doc/extend.texi | 5 +-- gcc/testsuite/gcc.dg/c23-attr-syntax-6.c | 57 +++++++++++++++++------- gcc/testsuite/gcc.dg/c23-attr-syntax-7.c | 54 +++++++++++++++------- gcc/testsuite/gcc.dg/c23-attr-syntax-8.c | 12 +++++ libcpp/include/cpplib.h | 1 + libcpp/lex.cc | 9 +++- 8 files changed, 127 insertions(+), 47 deletions(-) create mode 100644 gcc/testsuite/gcc.dg/c23-attr-syntax-8.c diff --git a/gcc/c-family/c-lex.cc b/gcc/c-family/c-lex.cc index 8b0987ee0741..ff5ce2bf729a 100644 --- a/gcc/c-family/c-lex.cc +++ b/gcc/c-family/c-lex.cc @@ -357,7 +357,27 @@ c_common_has_attribute (cpp_reader *pfile, bool std_syntax) do nxt_token = cpp_peek_token (pfile, idx++); while (nxt_token->type == CPP_PADDING); - if (nxt_token->type == CPP_SCOPE) + if (!c_dialect_cxx () + && nxt_token->type == CPP_COLON + && (nxt_token->flags & COLON_SCOPE) != 0) + { + const cpp_token *prev_token = nxt_token; + do + nxt_token = cpp_peek_token (pfile, idx++); + while (nxt_token->type == CPP_PADDING); + if (nxt_token->type == CPP_COLON) + { + /* __has_attribute (vendor::attr) in -std=c17 etc. modes. + :: isn't CPP_SCOPE but 2 CPP_COLON tokens, where the + first one should have COLON_SCOPE flag to distinguish + it from : :. */ + have_scope = true; + get_token_no_padding (pfile); // Eat first colon. + } + else + nxt_token = prev_token; + } + if (nxt_token->type == CPP_SCOPE || have_scope) { have_scope = true; get_token_no_padding (pfile); // Eat scope. diff --git a/gcc/c/c-parser.cc b/gcc/c/c-parser.cc index 3be91d666a58..8019e60b1e02 100644 --- a/gcc/c/c-parser.cc +++ b/gcc/c/c-parser.cc @@ -5705,8 +5705,7 @@ c_parser_omp_sequence_args (c_parser *parser, tree attribute) indicates whether this relaxation is in effect. */ static tree -c_parser_std_attribute (c_parser *parser, bool for_tm, - bool loose_scope_p = false) +c_parser_std_attribute (c_parser *parser, bool for_tm) { c_token *token = c_parser_peek_token (parser); tree ns, name, attribute; @@ -5720,8 +5719,8 @@ c_parser_std_attribute (c_parser *parser, bool for_tm, name = canonicalize_attr_name (token->value); c_parser_consume_token (parser); if (c_parser_next_token_is (parser, CPP_SCOPE) - || (loose_scope_p - && c_parser_next_token_is (parser, CPP_COLON) + || (c_parser_next_token_is (parser, CPP_COLON) + && (c_parser_peek_token (parser)->flags & COLON_SCOPE) != 0 && c_parser_peek_2nd_token (parser)->type == CPP_COLON)) { ns = name; @@ -5841,8 +5840,7 @@ c_parser_std_attribute (c_parser *parser, bool for_tm, } static tree -c_parser_std_attribute_list (c_parser *parser, bool for_tm, - bool loose_scope_p = false) +c_parser_std_attribute_list (c_parser *parser, bool for_tm) { tree attributes = NULL_TREE; while (true) @@ -5855,7 +5853,7 @@ c_parser_std_attribute_list (c_parser *parser, bool for_tm, c_parser_consume_token (parser); continue; } - tree attribute = c_parser_std_attribute (parser, for_tm, loose_scope_p); + tree attribute = c_parser_std_attribute (parser, for_tm); if (attribute != error_mark_node) { TREE_CHAIN (attribute) = attributes; @@ -5883,7 +5881,7 @@ c_parser_std_attribute_specifier (c_parser *parser, bool for_tm) { auto ext = disable_extension_diagnostics (); c_parser_consume_token (parser); - attributes = c_parser_std_attribute_list (parser, for_tm, true); + attributes = c_parser_std_attribute_list (parser, for_tm); restore_extension_diagnostics (ext); } else diff --git a/gcc/doc/extend.texi b/gcc/doc/extend.texi index 52b5a1f255e0..efd78014d1a8 100644 --- a/gcc/doc/extend.texi +++ b/gcc/doc/extend.texi @@ -12626,10 +12626,7 @@ In C, writing: @end smallexample suppresses warnings about using @samp{[[]]} attributes in C versions -that predate C23@. Since the scope token @samp{::} is not a single -lexing token in earlier versions of C, this construct also allows two colons -to be used in place of @code{::}. GCC does not check whether the two -colons are immediately adjacent. +that predate C23@. @end itemize @code{__extension__} has no effect aside from this. diff --git a/gcc/testsuite/gcc.dg/c23-attr-syntax-6.c b/gcc/testsuite/gcc.dg/c23-attr-syntax-6.c index ae1e7578c22f..f8c5b0facff9 100644 --- a/gcc/testsuite/gcc.dg/c23-attr-syntax-6.c +++ b/gcc/testsuite/gcc.dg/c23-attr-syntax-6.c @@ -9,19 +9,14 @@ typedef int [[__extension__ gnu::vector_size (4)]] g1; typedef int [[__extension__ gnu :: vector_size (4)]] g2; -typedef int [[__extension__ gnu : : vector_size (4)]] g3; -typedef int [[__extension__ gnu: :vector_size (4)]] g4; -typedef int [[__extension__ gnu FOO vector_size (4)]] g5; -typedef int [[__extension__ gnu BAR BAR vector_size (4)]] g6; -typedef int [[__extension__ gnu :/**/: vector_size (4)]] g7; -typedef int [[__extension__ gnu JOIN(:,:) vector_size (4)]] g8; -typedef int [[__extension__ gnu :: vector_size (sizeof (void (*)(...)))]] g10; -typedef int [[__extension__]] g11; -typedef int [[__extension__,]] g12; -typedef int [[__extension__, ,,,, ,, ,]] g13; -[[__extension__ deprecated]] int g14 (); -[[__extension__ nodiscard]] int g15 (); -[[__extension__ noreturn]] void g16 (); +typedef int [[__extension__ gnu FOO vector_size (4)]] g3; +typedef int [[__extension__ gnu :: vector_size (sizeof (void (*)(...)))]] g4; +typedef int [[__extension__]] g5; +typedef int [[__extension__,]] g6; +typedef int [[__extension__, ,,,, ,, ,]] g7; +[[__extension__ deprecated]] int g8 (); +[[__extension__ nodiscard]] int g9 (); +[[__extension__ noreturn]] void g10 (); int cases (int x) @@ -51,12 +46,42 @@ typedef int [[__extension__ unknown_attribute]] b3; /* { dg-error {'unknown_attr typedef int [[__extension__ gnu:vector_size(4)]] b4; /* { dg-error {expected '\]' before ':'} } */ /* { dg-error {'gnu' attribute ignored} "" { target *-*-* } .-1 } */ typedef int [[__extension__ gnu JOIN2(:,:) vector_size (4)]] b5; /* { dg-error {pasting ":" and ":" does not give a valid preprocessing token} } */ -typedef int [[gnu::vector_size(4)]] b6; /* { dg-error {expected '\]' before ':'} } */ +/* { dg-error {expected '\]' before ':'} "" { target *-*-* } .-1 } */ +/* { dg-error {'gnu' attribute ignored} "" { target *-*-* } .-2 } */ +typedef int [[__extension__ gnu : : vector_size (4)]] b6; /* { dg-error {expected '\]' before ':'} } */ +/* { dg-error {'gnu' attribute ignored} "" { target *-*-* } .-1 } */ +typedef int [[__extension__ gnu: :vector_size (4)]] b7; /* { dg-error {expected '\]' before ':'} } */ +/* { dg-error {'gnu' attribute ignored} "" { target *-*-* } .-1 } */ +typedef int [[__extension__ gnu BAR BAR vector_size (4)]] b8; /* { dg-error {expected '\]' before ':'} } */ +/* { dg-error {'gnu' attribute ignored} "" { target *-*-* } .-1 } */ +typedef int [[__extension__ gnu :/**/: vector_size (4)]] b9; /* { dg-error {expected '\]' before ':'} } */ +/* { dg-error {'gnu' attribute ignored} "" { target *-*-* } .-1 } */ +typedef int [[__extension__ gnu JOIN(:,:) vector_size (4)]] b10; /* { dg-error {expected '\]' before ':'} } */ +/* { dg-error {'gnu' attribute ignored} "" { target *-*-* } .-1 } */ +typedef int [[gnu::vector_size(4)]] b11; /* { dg-error {attributes before C23} } */ +typedef int [[gnu : : vector_size(4)]] b12; /* { dg-error {expected '\]' before ':'} } */ +/* { dg-error {'gnu' attribute ignored} "" { target *-*-* } .-1 } */ +/* { dg-error {attributes before C23} "" { target *-*-* } .-2 } */ +typedef int [[gnu : vector_size(4)]] b13; /* { dg-error {expected '\]' before ':'} } */ +/* { dg-error {'gnu' attribute ignored} "" { target *-*-* } .-1 } */ +/* { dg-error {attributes before C23} "" { target *-*-* } .-2 } */ +typedef int [[gnu: :vector_size (4)]] b14; /* { dg-error {expected '\]' before ':'} } */ +/* { dg-error {'gnu' attribute ignored} "" { target *-*-* } .-1 } */ +/* { dg-error {attributes before C23} "" { target *-*-* } .-2 } */ +typedef int [[gnu BAR BAR vector_size (4)]] b15; /* { dg-error {expected '\]' before ':'} } */ /* { dg-error {'gnu' attribute ignored} "" { target *-*-* } .-1 } */ /* { dg-error {attributes before C23} "" { target *-*-* } .-2 } */ -typedef int [[gnu : : vector_size(4)]] b7; /* { dg-error {expected '\]' before ':'} } */ +typedef int [[gnu :/**/: vector_size (4)]] b16; /* { dg-error {expected '\]' before ':'} } */ /* { dg-error {'gnu' attribute ignored} "" { target *-*-* } .-1 } */ /* { dg-error {attributes before C23} "" { target *-*-* } .-2 } */ -typedef int [[gnu : vector_size(4)]] b8; /* { dg-error {expected '\]' before ':'} } */ +typedef int [[gnu JOIN(:,:) vector_size (4)]] b17; /* { dg-error {expected '\]' before ':'} } */ /* { dg-error {'gnu' attribute ignored} "" { target *-*-* } .-1 } */ /* { dg-error {attributes before C23} "" { target *-*-* } .-2 } */ +typedef int [[gnu :: vector_size (4)]] b18; /* { dg-error {attributes before C23} } */ +typedef int [[gnu FOO vector_size (4)]] b19; /* { dg-error {attributes before C23} } */ +typedef int [[gnu :: vector_size (sizeof (void (*)(...)))]] b20; /* { dg-error {attributes before C23} } */ +/* { dg-error {requires a named argument before} "" { target *-*-* } .-1 } */ +typedef int [[gnu JOIN2(:,:) vector_size (4)]] b21; /* { dg-error {pasting ":" and ":" does not give a valid preprocessing token} } */ +/* { dg-error {expected '\]' before ':'} "" { target *-*-* } .-1 } */ +/* { dg-error {'gnu' attribute ignored} "" { target *-*-* } .-2 } */ +/* { dg-error {attributes before C23} "" { target *-*-* } .-3 } */ diff --git a/gcc/testsuite/gcc.dg/c23-attr-syntax-7.c b/gcc/testsuite/gcc.dg/c23-attr-syntax-7.c index cf3b1ff33e70..b34b73a5ce0b 100644 --- a/gcc/testsuite/gcc.dg/c23-attr-syntax-7.c +++ b/gcc/testsuite/gcc.dg/c23-attr-syntax-7.c @@ -9,19 +9,14 @@ typedef int [[__extension__ gnu::vector_size (4)]] g1; typedef int [[__extension__ gnu :: vector_size (4)]] g2; -typedef int [[__extension__ gnu : : vector_size (4)]] g3; -typedef int [[__extension__ gnu: :vector_size (4)]] g4; -typedef int [[__extension__ gnu FOO vector_size (4)]] g5; -typedef int [[__extension__ gnu BAR BAR vector_size (4)]] g6; -typedef int [[__extension__ gnu :/**/: vector_size (4)]] g7; -typedef int [[__extension__ gnu JOIN(:,:) vector_size (4)]] g8; -typedef int [[__extension__ gnu :: vector_size (sizeof (void (*)(...)))]] g10; -typedef int [[__extension__]] g11; -typedef int [[__extension__,]] g12; -typedef int [[__extension__, ,,,, ,, ,]] g13; -[[__extension__ deprecated]] int g14 (); -[[__extension__ nodiscard]] int g15 (); -[[__extension__ noreturn]] void g16 (); +typedef int [[__extension__ gnu FOO vector_size (4)]] g3; +typedef int [[__extension__ gnu :: vector_size (sizeof (void (*)(...)))]] g4; +typedef int [[__extension__]] g5; +typedef int [[__extension__,]] g6; +typedef int [[__extension__, ,,,, ,, ,]] g7; +[[__extension__ deprecated]] int g8 (); +[[__extension__ nodiscard]] int g9 (); +[[__extension__ noreturn]] void g10 (); int cases (int x) @@ -51,10 +46,37 @@ typedef int [[__extension__ unknown_attribute]] b3; /* { dg-error {'unknown_attr typedef int [[__extension__ gnu:vector_size(4)]] b4; /* { dg-error {expected '\]' before ':'} } */ /* { dg-error {'gnu' attribute ignored} "" { target *-*-* } .-1 } */ typedef int [[__extension__ gnu JOIN2(:,:) vector_size (4)]] b5; -typedef int [[gnu::vector_size(4)]] b6; /* { dg-warning {attributes before C23} } */ -typedef int [[gnu : : vector_size(4)]] b7; /* { dg-error {expected '\]' before ':'} } */ +typedef int [[__extension__ gnu : : vector_size (4)]] b6; /* { dg-error {expected '\]' before ':'} } */ +/* { dg-error {'gnu' attribute ignored} "" { target *-*-* } .-1 } */ +typedef int [[__extension__ gnu: :vector_size (4)]] b7; /* { dg-error {expected '\]' before ':'} } */ +/* { dg-error {'gnu' attribute ignored} "" { target *-*-* } .-1 } */ +typedef int [[__extension__ gnu BAR BAR vector_size (4)]] b8; /* { dg-error {expected '\]' before ':'} } */ +/* { dg-error {'gnu' attribute ignored} "" { target *-*-* } .-1 } */ +typedef int [[__extension__ gnu :/**/: vector_size (4)]] b9; /* { dg-error {expected '\]' before ':'} } */ +/* { dg-error {'gnu' attribute ignored} "" { target *-*-* } .-1 } */ +typedef int [[__extension__ gnu JOIN(:,:) vector_size (4)]] b10; /* { dg-error {expected '\]' before ':'} } */ +/* { dg-error {'gnu' attribute ignored} "" { target *-*-* } .-1 } */ +typedef int [[gnu::vector_size(4)]] b11; /* { dg-warning {attributes before C23} } */ +typedef int [[gnu : : vector_size(4)]] b12; /* { dg-error {expected '\]' before ':'} } */ +/* { dg-error {'gnu' attribute ignored} "" { target *-*-* } .-1 } */ +/* { dg-warning {attributes before C23} "" { target *-*-* } .-2 } */ +typedef int [[gnu : vector_size(4)]] b13; /* { dg-error {expected '\]' before ':'} } */ +/* { dg-error {'gnu' attribute ignored} "" { target *-*-* } .-1 } */ +/* { dg-warning {attributes before C23} "" { target *-*-* } .-2 } */ +typedef int [[gnu: :vector_size (4)]] b14; /* { dg-error {expected '\]' before ':'} } */ +/* { dg-error {'gnu' attribute ignored} "" { target *-*-* } .-1 } */ +/* { dg-warning {attributes before C23} "" { target *-*-* } .-2 } */ +typedef int [[gnu BAR BAR vector_size (4)]] b15; /* { dg-error {expected '\]' before ':'} } */ +/* { dg-error {'gnu' attribute ignored} "" { target *-*-* } .-1 } */ +/* { dg-warning {attributes before C23} "" { target *-*-* } .-2 } */ +typedef int [[gnu :/**/: vector_size (4)]] b16; /* { dg-error {expected '\]' before ':'} } */ /* { dg-error {'gnu' attribute ignored} "" { target *-*-* } .-1 } */ /* { dg-warning {attributes before C23} "" { target *-*-* } .-2 } */ -typedef int [[gnu : vector_size(4)]] b8; /* { dg-error {expected '\]' before ':'} } */ +typedef int [[gnu JOIN(:,:) vector_size (4)]] b17; /* { dg-error {expected '\]' before ':'} } */ /* { dg-error {'gnu' attribute ignored} "" { target *-*-* } .-1 } */ /* { dg-warning {attributes before C23} "" { target *-*-* } .-2 } */ +typedef int [[gnu :: vector_size (4)]] b18; /* { dg-warning {attributes before C23} } */ +typedef int [[gnu FOO vector_size (4)]] b19; /* { dg-warning {attributes before C23} } */ +typedef int [[gnu :: vector_size (sizeof (void (*)(...)))]] b20; /* { dg-warning {attributes before C23} } */ +/* { dg-warning {requires a named argument before} "" { target *-*-* } .-1 } */ +typedef int [[gnu JOIN2(:,:) vector_size (4)]] b21; /* { dg-warning {attributes before C23} } */ diff --git a/gcc/testsuite/gcc.dg/c23-attr-syntax-8.c b/gcc/testsuite/gcc.dg/c23-attr-syntax-8.c new file mode 100644 index 000000000000..6fff160dff03 --- /dev/null +++ b/gcc/testsuite/gcc.dg/c23-attr-syntax-8.c @@ -0,0 +1,12 @@ +/* PR c/114007 */ +/* { dg-do compile } */ +/* { dg-options "-std=c11" } */ + +#if __has_c_attribute (gnu::unused) +[[gnu::unused]] +#endif +int i; +#if __has_cpp_attribute (gnu::unused) +[[gnu::unused]] +#endif +int j; diff --git a/libcpp/include/cpplib.h b/libcpp/include/cpplib.h index 5746aac9ea42..c62374d31929 100644 --- a/libcpp/include/cpplib.h +++ b/libcpp/include/cpplib.h @@ -200,6 +200,7 @@ struct GTY(()) cpp_string { #define DECIMAL_INT (1 << 6) /* Decimal integer, set in c-lex.cc. */ #define PURE_ZERO (1 << 7) /* Single 0 digit, used by the C++ frontend, set in c-lex.cc. */ +#define COLON_SCOPE PURE_ZERO /* Adjacent colons in C < 23. */ #define SP_DIGRAPH (1 << 8) /* # or ## token was a digraph. */ #define SP_PREV_WHITE (1 << 9) /* If whitespace before a ## operator, or before this token diff --git a/libcpp/lex.cc b/libcpp/lex.cc index 5aa379980cf2..c9e44e6ccccf 100644 --- a/libcpp/lex.cc +++ b/libcpp/lex.cc @@ -4235,8 +4235,13 @@ _cpp_lex_direct (cpp_reader *pfile) case ':': result->type = CPP_COLON; - if (*buffer->cur == ':' && CPP_OPTION (pfile, scope)) - buffer->cur++, result->type = CPP_SCOPE; + if (*buffer->cur == ':') + { + if (CPP_OPTION (pfile, scope)) + buffer->cur++, result->type = CPP_SCOPE; + else + result->flags |= COLON_SCOPE; + } else if (*buffer->cur == '>' && CPP_OPTION (pfile, digraphs)) { buffer->cur++; -- GitLab