- Mar 04, 2025
-
-
GCC Administrator authored
-
- Mar 03, 2025
-
-
Joseph Myers authored
gcc/po/ * be.po, da.po, de.po, el.po, es.po, fi.po, fr.po, hr.po, id.po, ja.po, ka.po, nl.po, ru.po, sr.po, sv.po, tr.po, uk.po, vi.po, zh_CN.po, zh_TW.po: Update. libcpp/po/ * be.po, ca.po, da.po, de.po, el.po, eo.po, es.po, fi.po, fr.po, id.po, ja.po, ka.po, nl.po, pt_BR.po, ro.po, ru.po, sr.po, sv.po, tr.po, uk.po, vi.po, zh_CN.po, zh_TW.po: Update.
-
- Mar 01, 2025
-
-
GCC Administrator authored
-
- Feb 28, 2025
-
-
Jakub Jelinek authored
Now that the #embed paper has been voted in, the following patch removes the pedwarn for C++26 on it (and adjusts pedwarn warning for older C++ versions) and predefines __cpp_pp_embed FTM. Also, the patch changes cpp_error to cpp_pedwarning with for C++ -Wc++26-extensions guarding, and for C add -Wc11-c23-compat warning about #embed. I believe we otherwise implement everything in the paper already, except I'm really confused by the [Example: #embed <data.dat> limit(__has_include("a.h")) #if __has_embed(<data.dat> limit(__has_include("a.h"))) // ill-formed: __has_include [cpp.cond] cannot appear here #endif — end example] part. My reading of both C23 and C++ with the P1967R14 paper in is that the first case (#embed with __has_include or __has_embed in its clauses) is what is clearly invalid and so the ill-formed note should be for #embed. And the __has_include/__has_embed in __has_embed is actually questionable. Both C and C++ have something like "The identifiers __has_include, __has_embed, and __has_c_attribute shall not appear in any context not mentioned in this subclause." or "The identifiers __has_include and __has_cpp_attribute shall not appear in any context not mentioned in this subclause." (into which P1967R14 adds __has_embed) in the conditional inclusion subclause. #embed is defined in a different one, so using those in there is invalid (unless "using the rules specified for conditional inclusion" wording e.g. in limit clause overrides that). The reason why I think it is fuzzy for __has_embed is that __has_embed is actually defined in the Conditional inclusion subclause (so that would mean one can use __has_include, __has_embed and __has_*attribute in there) but its clauses are described in a different one. GCC currently accepts #embed __FILE__ limit (__has_include (<stdarg.h>)) #if __has_embed (__FILE__ limit (__has_include (<stdarg.h>))) #endif #embed __FILE__ limit (__has_embed (__FILE__)) #if __has_embed (__FILE__ limit (__has_embed (__FILE__))) #endif Note, it isn't just about limit clause, but also about prefix/suffix/if_empty, except that in those cases the "using the rules specified for conditional inclusion" doesn't apply. In any case, I'd hope that can be dealt with incrementally (and should be handled the same for both C and C++). 2025-02-28 Jakub Jelinek <jakub@redhat.com> libcpp/ * include/cpplib.h (enum cpp_warning_reason): Add CPP_W_CXX26_EXTENSIONS enumerator. * init.cc (lang_defaults): Set embed for GNUCXX26 and CXX26. * directives.cc (do_embed): Adjust pedwarn wording for embed in C++, use cpp_pedwarning instead of cpp_error and add CPP_W_C11_C23_COMPAT warning of cpp_pedwarning hasn't diagnosed anything. gcc/c-family/ * c.opt (Wc++26-extensions): Add CppReason(CPP_W_CXX26_EXTENSIONS). * c-cppbuiltin.cc (c_cpp_builtins): Predefine __cpp_pp_embed=202502 for C++26. gcc/testsuite/ * g++.dg/cpp/embed-1.C: Adjust for pedwarn wording change and don't expect any error for C++26. * g++.dg/cpp/embed-2.C: Adjust for pedwarn wording change and don't expect any warning for C++26. * g++.dg/cpp26/feat-cxx26.C: Test __cpp_pp_embed value. * gcc.dg/cpp/embed-17.c: New test.
-
- Feb 15, 2025
-
-
GCC Administrator authored
-
- Feb 14, 2025
-
-
Joseph Myers authored
gcc/po/ * gcc.pot: Regenerate. libcpp/po/ * cpplib.pot: Regenerate.
-
- Jan 02, 2025
-
-
Jakub Jelinek authored
-
Jakub Jelinek authored
-
Jakub Jelinek authored
2024 -> 2025
-
- Dec 25, 2024
-
-
GCC Administrator authored
-
- Dec 24, 2024
-
-
Lewis Hyatt authored
It seems that tokens_buff_new() has always been allocating the virtual location buffer 4 times larger than intended, and now that location_t is 64-bit, it is 8 times larger. Fixed. libcpp/ChangeLog: * macro.cc (tokens_buff_new): Fix length argument to XNEWVEC.
-
- Dec 17, 2024
-
-
GCC Administrator authored
-
- Dec 16, 2024
-
-
Joseph Myers authored
* sr.po: Update.
-
- Dec 09, 2024
-
-
GCC Administrator authored
-
- Dec 08, 2024
-
-
Lewis Hyatt authored
Change location_t to be a 64-bit integer instead of a 32-bit integer in libcpp. Also included in this change are the two other patches in the original series which depended on this one; I am committing them all at once in case it needs to be reverted later: -Support for 64-bit location_t: gimple parts The size of struct gimple increased by 8 bytes with the change in size of location_t from 32- to 64-bit; adjust the WORD markings in the comments accordingly. It seems that most of the WORD markings were off by one already, probably not having been updated after a previous reduction in the size of a gimple, so they have become retroactively correct again, and only a couple needed adjustment actually. Also add a comment that there is now 32 bits of unused padding available in struct gimple for 64-bit hosts. -Support for 64-bit location_t: Remove -flarge-source-files The option -flarge-source-files became unnecessary with 64-bit location_t and harms performance compared to the new default setting, so silently ignore it. libcpp/ChangeLog: * include/cpplib.h (struct cpp_token): Adjust comment about the struct size. * include/line-map.h (location_t): Change typedef from 32-bit to 64-bit integer. (LINE_MAP_MAX_COLUMN_NUMBER): Increase size to be appropriate for 64-bit location_t. (LINE_MAP_MAX_LOCATION_WITH_PACKED_RANGES): Likewise. (LINE_MAP_MAX_LOCATION_WITH_COLS): Likewise. (LINE_MAP_MAX_LOCATION): Likewise. (MAX_LOCATION_T): Likewise. (line_map_suggested_range_bits): Likewise. (struct line_map): Adjust comment about the struct size. (struct line_map_macro): Likewise. (struct line_map_ordinary): Likewise. Rearrange fields to optimize padding. gcc/testsuite/ChangeLog: * g++.dg/diagnostic/pr77949.C: Adapt the test for 64-bit location_t, when the previously expected failure doesn't actually happen. * g++.dg/modules/loc-prune-4.C: Adjust the expected output for the 64-bit location_t case. * gcc.dg/plugin/expensive_selftests_plugin.cc: Don't try to test the maximum supported column number in 64-bit location_t mode. * gcc.dg/plugin/location_overflow_plugin.cc: Adjust the base_location so it can effectively test 64-bit location_t. gcc/ChangeLog: * gimple.h (struct gphi): Update word marking comments to reflect the new size of location_t. (struct gimple): Likewise. Add a comment about padding. * common.opt: Mark -flarge-source-files as Ignored. * common.opt.urls: Regenerate. * doc/invoke.texi: Remove -flarge-source-files. * toplev.cc (process_options): Remove support for -flarge-source-files.
-
- Dec 07, 2024
-
-
GCC Administrator authored
-
- Dec 06, 2024
-
-
Jakub Jelinek authored
This patch adds similar optimizations to the C++ FE as have been implemented earlier in the C FE. The libcpp hunk enables use of CPP_EMBED token even for C++, not just C; the preprocessor guarantees there is always a CPP_NUMBER CPP_COMMA before CPP_EMBED and CPP_COMMA CPP_NUMBER after it which simplifies parsing (unless #embed is more than 2GB, in that case it could be CPP_NUMBER CPP_COMMA CPP_EMBED CPP_COMMA CPP_EMBED CPP_COMMA CPP_EMBED CPP_COMMA CPP_NUMBER etc. with each CPP_EMBED covering at most INT_MAX bytes). Similarly to the C patch, this patch parses it into RAW_DATA_CST tree in the braced initializers (and from there peels into INTEGER_CSTs unless it is an initializer of an std::byte array or integral array with CHAR_BIT element precision), parses CPP_EMBED in cp_parser_expression into just the last INTEGER_CST in it because I think users don't need millions of -Wunused-value warnings because they did useless int a = ( #embed "megabyte.dat" ); and so most of the inner INTEGER_CSTs would be there just for the warning, and in the rest of contexts like template argument list, function argument list, attribute argument list, ...) parse it into a sequence of INTEGER_CSTs (I wrote a range/iterator classes to simplify that). My dumb cat embed-11.c constexpr unsigned char a[] = { #embed "cc1plus" }; const unsigned char *b = a; testcase where cc1plus is 492329008 bytes long when configured --enable-checking=yes,rtl,extra against recent binutils with .base64 gas support results in: time ./xg++ -B ./ -S -O2 embed-11.c real 0m4.350s user 0m2.427s sys 0m0.830s time ./xg++ -B ./ -c -O2 embed-11.c real 0m6.932s user 0m6.034s sys 0m0.888s (compared to running out of memory or very long compilation). On a shorter inclusion, cat embed-12.c constexpr unsigned char a[] = { #embed "xg++" }; const unsigned char *b = a; where xg++ is 15225904 bytes long, this takes using GCC with the #embed patchset except for this patch: time ~/src/gcc/obj36/gcc/xg++ -B ~/src/gcc/obj36/gcc/ -S -O2 embed-12.c real 0m33.190s user 0m32.327s sys 0m0.790s and with this patch: time ./xg++ -B ./ -S -O2 embed-12.c real 0m0.118s user 0m0.090s sys 0m0.028s The patch doesn't change anything on what the first patch in the series introduces even for C++, namely that #embed is expanded (actually or as if) into a sequence of literals like 127,69,76,70,2,1,1,3,0,0,0,0,0,0,0,0,2,0,62,0,1,0,0,0,80,211,64,0,0,0,0,0,64,0,0,0,0,0,0,0,8,253 and so each element has int type. That is how I believe it is in C23, and the different versions of the C++ P1967 paper specified there some casts, P1967R12 in particular "Otherwise, the integral constant expression is the value of std::fgetc’s return is cast to unsigned char." but please see https://github.com/llvm/llvm-project/pull/97274#issuecomment-2230929277 comment and whether we really want the preprocessor to preprocess it for C++ as (or as-if) static_cast<unsigned char>(127),static_cast<unsigned char>(69),static_cast<unsigned char>(76),static_cast<unsigned char>(70),static_cast<unsigned char>(2),... i.e. 9 tokens per byte rather than 2, or (unsigned char)127,(unsigned char)69,... or ((unsigned char)127),((unsigned char)69),... etc. Without a literal suffix for unsigned char constant literals it is horrible, plus the incompatibility between C and C++. Sure, we could use the magic form more often for C++ to save the size and do the 9 or how many tokens form only for the boundary constants and use #embed "." __gnu__::__base64__("...") for what is in between if there are at least 2 tokens inside of it. E.g. (unsigned char)127 vs. static_cast<unsigned char>(127) behaves differently if there is constexpr long long p[] = { ... }; ... #embed __FILE__ [p] 2024-12-06 Jakub Jelinek <jakub@redhat.com> libcpp/ * files.cc (finish_embed): Use CPP_EMBED even for C++. gcc/ * tree.h (RAW_DATA_UCHAR_ELT, RAW_DATA_SCHAR_ELT): Define. gcc/cp/ChangeLog: * cp-tree.h (class raw_data_iterator): New type. (class raw_data_range): New type. * parser.cc (cp_parser_postfix_open_square_expression): Handle parsing of CPP_EMBED. (cp_parser_parenthesized_expression_list): Likewise. Use cp_lexer_next_token_is. (cp_parser_expression): Handle parsing of CPP_EMBED. (cp_parser_template_argument_list): Likewise. (cp_parser_initializer_list): Likewise. (cp_parser_oacc_clause_tile): Likewise. (cp_parser_omp_tile_sizes): Likewise. * pt.cc (tsubst_expr): Handle RAW_DATA_CST. * constexpr.cc (reduced_constant_expression_p): Likewise. (raw_data_cst_elt): New function. (find_array_ctor_elt): Handle RAW_DATA_CST. (cxx_eval_array_reference): Likewise. * typeck2.cc (digest_init_r): Emit -Wnarrowing and/or -Wconversion diagnostics. (process_init_constructor_array): Handle RAW_DATA_CST. * decl.cc (maybe_deduce_size_from_array_init): Likewise. (is_direct_enum_init): Fail for RAW_DATA_CST. (cp_maybe_split_raw_data): New function. (consume_init): New function. (reshape_init_array_1): Add VECTOR_P argument. Handle RAW_DATA_CST. (reshape_init_array): Adjust reshape_init_array_1 caller. (reshape_init_vector): Likewise. (reshape_init_class): Handle RAW_DATA_CST. (reshape_init_r): Likewise. gcc/testsuite/ * c-c++-common/cpp/embed-22.c: New test. * c-c++-common/cpp/embed-23.c: New test. * g++.dg/cpp/embed-4.C: New test. * g++.dg/cpp/embed-5.C: New test. * g++.dg/cpp/embed-6.C: New test. * g++.dg/cpp/embed-7.C: New test. * g++.dg/cpp/embed-8.C: New test. * g++.dg/cpp/embed-9.C: New test. * g++.dg/cpp/embed-10.C: New test. * g++.dg/cpp/embed-11.C: New test. * g++.dg/cpp/embed-12.C: New test. * g++.dg/cpp/embed-13.C: New test. * g++.dg/cpp/embed-14.C: New test.
-
- Dec 04, 2024
-
-
GCC Administrator authored
-
- Dec 03, 2024
-
-
Joseph Myers authored
As noted in bug 117162, C23 changed some rules on UCNs to match C++ (this was a late change agreed in the resolution to CD2 comment US-032, implementing changes from N3124), which we need to implement. Allow UCNs below 0xa0 outside identifiers for C, with a pedwarn-if-pedantic before C23 (and a warning with -Wc11-c23-compat) except for the always-allowed cases of UCNs for $ @ `. Also as part of that change, do not allow \u0024 in identifiers as equivalent to $ for C23. Bootstrapped with no regressions for x86_64-pc-linux-gnu. PR c/117162 libcpp/ * include/cpplib.h (struct cpp_options): Add low_ucns. * init.cc (struct lang_flags, lang_defaults): Add low_ucns. (cpp_set_lang): Set low_ucns * charset.cc (_cpp_valid_ucn): For C, allow UCNs below 0xa0 outside identifiers, with a pedwarn if pedantic before C23 or a warning with -Wc11-c23-compat. Do not allow \u0024 in identifiers for C23. gcc/testsuite/ * gcc.dg/cpp/c17-ucn-1.c, gcc.dg/cpp/c17-ucn-2.c, gcc.dg/cpp/c17-ucn-3.c, gcc.dg/cpp/c17-ucn-4.c, gcc.dg/cpp/c23-ucn-2.c, gcc.dg/cpp/c23-ucnid-2.c: New tests. * c-c++-common/cpp/delimited-escape-seq-3.c, c-c++-common/cpp/named-universal-char-escape-3.c, gcc.dg/cpp/c23-ucn-1.c, gcc.dg/cpp/c2y-delimited-escape-seq-3.c: Update expected messages * gcc.dg/cpp/ucs.c: Use -pedantic-errors. Update expected messages.
-
- Nov 29, 2024
-
-
GCC Administrator authored
-
- Nov 28, 2024
-
-
David Malcolm authored
No functional change intended. gcc/analyzer/ChangeLog: PR c/104896 * sm-malloc.cc: Replace "%<%s%>" with "%qs" in message wording. gcc/c-family/ChangeLog: PR c/104896 * c-lex.cc (c_common_lex_availability_macro): Replace "%<%s%>" with "%qs" in message wording. * c-opts.cc (c_common_handle_option): Likewise. * c-warn.cc (warn_parm_array_mismatch): Likewise. gcc/ChangeLog: PR c/104896 * common/config/ia64/ia64-common.cc (ia64_handle_option): Replace "%<%s%>" with "%qs" in message wording. * common/config/rs6000/rs6000-common.cc (rs6000_handle_option): Likewise. * config/aarch64/aarch64.cc (aarch64_validate_sls_mitigation): Likewise. (aarch64_override_options): Likewise. (aarch64_process_target_attr): Likewise. * config/arm/aarch-common.cc (aarch_validate_mbranch_protection): Likewise. * config/pru/pru.cc (pru_insert_attributes): Likewise. * config/riscv/riscv-target-attr.cc (riscv_target_attr_parser::parse_arch): Likewise. * omp-general.cc (oacc_verify_routine_clauses): Likewise. * tree-ssa-uninit.cc (maybe_warn_read_write_only): Likewise. (maybe_warn_pass_by_reference): Likewise. gcc/cp/ChangeLog: PR c/104896 * cvt.cc (maybe_warn_nodiscard): Replace "%<%s%>" with "%qs" in message wording. gcc/fortran/ChangeLog: PR c/104896 * resolve.cc (resolve_operator): Replace "%<%s%>" with "%qs" in message wording. gcc/go/ChangeLog: PR c/104896 * gofrontend/embed.cc (Gogo::initializer_for_embeds): Replace "%<%s%>" with "%qs" in message wording. * gofrontend/expressions.cc (Selector_expression::lower_method_expression): Likewise. * gofrontend/gogo.cc (Gogo::set_package_name): Likewise. (Named_object::export_named_object): Likewise. * gofrontend/parse.cc (Parse::struct_type): Likewise. (Parse::parameter_list): Likewise. gcc/rust/ChangeLog: PR c/104896 * backend/rust-compile-expr.cc (CompileExpr::compile_integer_literal): Replace "%<%s%>" with "%qs" in message wording. (CompileExpr::compile_float_literal): Likewise. * backend/rust-compile-intrinsic.cc (Intrinsics::compile): Likewise. * backend/rust-tree.cc (maybe_warn_nodiscard): Likewise. * checks/lints/rust-lint-scan-deadcode.h: Likewise. * lex/rust-lex.cc (Lexer::parse_partial_unicode_escape): Likewise. (Lexer::parse_raw_byte_string): Likewise. * lex/rust-token.cc (Token::get_str): Likewise. * metadata/rust-export-metadata.cc (PublicInterface::write_to_path): Likewise. * parse/rust-parse.cc (peculiar_fragment_match_compatible_fragment): Likewise. (peculiar_fragment_match_compatible): Likewise. * resolve/rust-ast-resolve-path.cc (ResolvePath::resolve_path): Likewise. * resolve/rust-ast-resolve-toplevel.h: Likewise. * resolve/rust-ast-resolve-type.cc (ResolveRelativeTypePath::go): Likewise. * rust-session-manager.cc (validate_crate_name): Likewise. (Session::load_extern_crate): Likewise. * typecheck/rust-hir-type-check-expr.cc (TypeCheckExpr::visit): Likewise. (TypeCheckExpr::resolve_fn_trait_call): Likewise. * typecheck/rust-hir-type-check-implitem.cc (TypeCheckImplItemWithTrait::visit): Likewise. * typecheck/rust-hir-type-check-item.cc (TypeCheckItem::validate_trait_impl_block): Likewise. * typecheck/rust-hir-type-check-struct.cc (TypeCheckStructExpr::visit): Likewise. * typecheck/rust-tyty-call.cc (TypeCheckCallExpr::visit): Likewise. * typecheck/rust-tyty.cc (BaseType::bounds_compatible): Likewise. * typecheck/rust-unify.cc (UnifyRules::emit_abi_mismatch): Likewise. * util/rust-attributes.cc (AttributeChecker::visit): Likewise. libcpp/ChangeLog: PR c/104896 * pch.cc (cpp_valid_state): Replace "%<%s%>" with "%qs" in message wording. Signed-off-by:
David Malcolm <dmalcolm@redhat.com>
-
GCC Administrator authored
-
- Nov 27, 2024
-
-
Jason Merrill authored
I enabled include translation to header units in r15-1104-ga29f481bbcaf2b, but it seems that patch wasn't sufficient, as any diagnostics in the main source file would show up as coming from the header instead. Fixed by setting buffer->file for leaving the file transition that my previous patch made us enter. And don't push a buffer of newlines, in this case that messes up line numbers instead of aligning them. libcpp/ChangeLog: * files.cc (_cpp_stack_file): Handle -include of header unit more specially. gcc/testsuite/ChangeLog: * g++.dg/modules/dashinclude-1_b.C: Add an #error. * g++.dg/modules/dashinclude-1_a.H: Remove dg-module-do run.
-
- Nov 24, 2024
-
-
GCC Administrator authored
-
- Nov 23, 2024
-
-
Lewis Hyatt authored
The PR shows that we ICE after lexing an invalid unterminated raw string, because lex_raw_string() pops the main buffer unexpectedly. Resolve by handling this case the same way as for other directives. libcpp/ChangeLog: PR preprocessor/117118 * lex.cc (lex_raw_string): Treat an unterminated raw string the same way for a deferred pragma as is done for other directives. gcc/testsuite/ChangeLog: PR preprocessor/117118 * c-c++-common/raw-string-directive-3.c: New test. * c-c++-common/raw-string-directive-4.c: New test.
-
Lewis Hyatt authored
libcpp makes use of the cpp_buffer pfile->a_buff to store things while it is handling macros. It uses it to store pointers (cpp_hashnode*, for macro arguments) and cpp_macro objects. This works fine because a cpp_hashnode* and a cpp_macro have the same alignment requirement on either 32-bit or 64-bit systems (namely, the same alignment as a pointer.) When 64-bit location_t is enabled on a 32-bit sytem, the alignment requirement may cease to be the same, because the alignment requirement of a cpp_macro object changes to that of a uint64_t, which be larger than that of a pointer. It's not the case for x86 32-bit, but for example, on sparc, a pointer has 4-byte alignment while a uint64_t has 8. In that case, intermixing the two within the same cpp_buffer leads to a misaligned access. The code path that triggers this is the one in _cpp_commit_buff in which a hash table with its own allocator (i.e. ggc) is not being used, so it doesn't happen within the compiler itself, but it happens in the other libcpp clients, such as genmatch. Fix that up by ensuring _cpp_commit_buff commits a fully aligned chunk of the buffer, so it's ready for anything it may be used for next. Also modify CPP_ALIGN so that it guarantees to return an alignment at least the size of location_t. Currently it returns the max of a pointer and a double. I am not aware of any platform where a double may have smaller alignment than a uint64_t, but it does not hurt to add location_t here to be sure. libcpp/ChangeLog: * lex.cc (_cpp_commit_buff): Make sure that the buffer is properly aligned for the next allocation. * internal.h (struct dummy): Make sure alignment is large enough for a location_t, just in case.
-
Lewis Hyatt authored
Prepare libcpp to support 64-bit location_t, without yet making any functional changes, by adding new typedefs that enable code to be written such that it works with any size location_t. Update the usage of line maps within libcpp accordingly. Subsequent patches will prepare the rest of the codebase similarly, and then afterwards, location_t will be changed to uint64_t. libcpp/ChangeLog: * include/line-map.h (line_map_uint_t): New typedef, the same type as location_t. (location_diff_t): New typedef. (line_map_suggested_range_bits): New constant. (struct maps_info_ordinary): Change member types from "unsigned int" to "line_map_uint_t". (struct maps_info_macro): Likewise. (struct location_adhoc_data_map): Likewise. (LINEMAPS_ALLOCATED): Change return type from "unsigned int" to "line_map_uint_t". (LINEMAPS_ORDINARY_ALLOCATED): Likewise. (LINEMAPS_MACRO_ALLOCATED): Likewise. (LINEMAPS_USED): Likewise. (LINEMAPS_ORDINARY_USED): Likewise. (LINEMAPS_MACRO_USED): Likewise. (linemap_lookup_macro_index): Likewise. (LINEMAPS_MAP_AT): Change argument type from "unsigned int" to "line_map_uint_t". (LINEMAPS_ORDINARY_MAP_AT): Likewise. (LINEMAPS_MACRO_MAP_AT): Likewise. (line_map_new_raw): Likewise. (linemap_module_restore): Likewise. (linemap_dump): Likewise. (line_table_dump): Likewise. (LINEMAPS_LAST_MAP): Add a linemap_assert() for safety. (SOURCE_COLUMN): Use a cast to ensure correctness if location_t becomes a 64-bit type. * line-map.cc (location_adhoc_data_hash): Don't truncate to 32-bit prematurely when hashing. (line_maps::get_or_create_combined_loc): Adapt types to support potentially 64-bit location_t. Use MAX_LOCATION_T rather than a hard-coded constant. (line_maps::get_range_from_loc): Adapt types and constants to support potentially 64-bit location_t. (line_maps::pure_location_p): Likewise. (line_maps::get_pure_location): Likewise. (line_map_new_raw): Likewise. (LAST_SOURCE_LINE_LOCATION): Likewise. (linemap_add): Likewise. (linemap_module_restore): Likewise. (linemap_line_start): Likewise. (linemap_position_for_column): Likewise. (linemap_position_for_line_and_column): Likewise. (linemap_position_for_loc_and_offset): Likewise. (linemap_ordinary_map_lookup): Likewise. (linemap_lookup_macro_index): Likewise. (linemap_dump): Likewise. (linemap_dump_location): Likewise. (linemap_get_file_highest_location): Likewise. (line_table_dump): Likewise. (linemap_compare_locations): Avoid signed int overflow in the result. * macro.cc (num_expanded_macros_counter): Change type of global variable from "unsigned int" to "line_map_uint_t". (num_macro_tokens_counter): Likewise.
-
- Nov 19, 2024
-
-
GCC Administrator authored
-
- Nov 18, 2024
-
-
Jason Merrill authored
The dependency output for header unit modules is based on the absolute pathname of the header file, but that's not something that a makefile can portably refer to. This patch adds a .c++-header-unit target based on the header name relative to an element of the include path. libcpp/ChangeLog: * internal.h (_cpp_get_file_dir): Declare. * files.cc (_cpp_get_file_dir): New fn. * mkdeps.cc (make_write): Use it. gcc/testsuite/ChangeLog: * g++.dg/modules/dep-4.H: New test.
-
GCC Administrator authored
-
- Nov 17, 2024
-
-
Jason Merrill authored
The C++ modules code has a -fmodule-header (or -x c++-{user,system}-header) option to specify looking up headers to compile to header units on the usual include paths. I'd like to have the same functionality for full C++20 modules such as module std, which I proposed to live on the include path at bits/std.cc. But this behavior doesn't seem necessarily connected to modules, so I'm proposing a general C/C++ option to specify the behavior of looking in the include path for the input files specified on the command line. Other ideas for the name of the option are very welcome. The libcpp change is to allow -fsearch-include-path{,=user} to find files in the current working directory, like -include. This can be handy for a quick compile of both std.cc and a file that imports it, e.g. g++ -std=c++20 -fmodules -fsearch-include-path bits/std.cc importer.cc gcc/ChangeLog: * doc/cppopts.texi: Document -fsearch-include-path. * doc/invoke.texi: Mention it for modules. gcc/c-family/ChangeLog: * c.opt: Add -fsearch-include-path. * c-opts.cc (c_common_post_options): Handle it. gcc/cp/ChangeLog: * module.cc (module_preprocess_options): Don't override it. libcpp/ChangeLog: * internal.h (search_path_head): Declare. * files.cc (search_path_head): No longer static. * init.cc (cpp_read_main_file): Use it.
-
- Nov 16, 2024
-
-
GCC Administrator authored
-
- Nov 15, 2024
-
-
Jakub Jelinek authored
The following patch adds _Decimal64x type support. Our dfp libraries (dpd & libbid) can only handle decimal32, decimal64 and decimal128 formats and I don't see that changing any time soon, so the following patch just hardcodes that _Decimal64x has the same mode as _Decimal128 (but is a distinct type). In the unlikely event some target would introduce something different that can be of course changed with target hooks but would be an ABI change. _Decimal128x is optional and we don't have a wider decimal type, so that type isn't added. 2024-11-15 Jakub Jelinek <jakub@redhat.com> gcc/ * tree-core.h (enum tree_index): Add TI_DFLOAT64X_TYPE. * tree.h (dfloat64x_type_node): Define. * tree.cc (build_common_tree_nodes): Initialize dfloat64x_type_node. * builtin-types.def (BT_DFLOAT64X): New DEF_PRIMITIVE_TYPE. (BT_FN_DFLOAT64X): New DEF_FUNCTION_TYPE_0. (BT_FN_DFLOAT64X_CONST_STRING, BT_FN_DFLOAT64X_DFLOAT64X): New DEF_FUNCTION_TYPE_1. * builtins.def (BUILT_IN_FABSD64X, BUILT_IN_INFD64X, BUILT_IN_NAND64X, BUILT_IN_NANSD64X): New builtins. * builtins.cc (expand_builtin): Handle BUILT_IN_FABSD64X. (fold_builtin_0): Handle BUILT_IN_INFD64X. (fold_builtin_1): Handle BUILT_IN_FABSD64X. * fold-const-call.cc (fold_const_call): Handle CFN_BUILT_IN_NAND64X and CFN_BUILT_IN_NANSD64X. * ginclude/float.h (DEC64X_MANT_DIG, DEC64X_MIN_EXP, DEC64X_MAX_EXP, DEC64X_MAX, DEC64X_EPSILON, DEC64X_MIN, DEC64X_TRUE_MIN, DEC64X_SNAN): Redefine. gcc/c-family/ * c-common.h (enum rid): Add RID_DFLOAT64X. * c-common.cc (c_global_trees): Fix comment typo. Add dfloat64x_type_node. (c_common_nodes_and_builtins): Handle RID_DFLOAT64X. * c-cppbuiltin.cc (c_cpp_builtins): Call builtin_define_decimal_float_constants also for dfloat64x_type_node if non-NULL. * c-lex.cc (interpret_float): Handle d64x suffixes. * c-pretty-print.cc (pp_c_floating_constant): Print d64x suffixes on dfloat64x_type_node typed constants. gcc/c/ * c-tree.h (enum c_typespec_keyword): Add cts_dfloat64x and adjust comment. * c-parser.cc (c_keyword_starts_typename, c_token_starts_declspecs, c_parser_declspecs, c_parser_gnu_attribute_any_word): Handle RID_DFLOAT64X. (c_parser_postfix_expression): Handle _Decimal64x arguments in __builtin_tgmath. (warn_for_abs): Handle BUILT_IN_FABSD64X. * c-decl.cc (declspecs_add_type): Handle cts_dfloat64x and RID_DFLOAT64X. (finish_declspecs): Handle cts_dfloat64x. * c-typeck.cc (c_common_type): Handle dfloat64x_type_node. gcc/testsuite/ * gcc.dg/dfp/c11-decimal64x-1.c: New test. * gcc.dg/dfp/c11-decimal64x-2.c: New test. * gcc.dg/dfp/c23-decimal64x-1.c: New test. * gcc.dg/dfp/c23-decimal64x-2.c: New test. * gcc.dg/dfp/c23-decimal64x-3.c: New test. * gcc.dg/dfp/c23-decimal64x-4.c: New test. libcpp/ * expr.cc (interpret_float_suffix): Handle d64x and D64x suffixes, adjust comment.
-
- Nov 14, 2024
-
-
GCC Administrator authored
-
- Nov 13, 2024
-
-
Jakub Jelinek authored
C23 roughly says that {d,D}{32,64,128} floating point constant suffixes are alternate spellings of {df,dd,dl} suffixes in annex H. So, the following patch allows that alternate spelling. Or is it intentional it isn't enabled and we need to do everything in there first before trying to define __STDC_IEC_60559_DFP__? Like add support for _Decimal32x and _Decimal64x types (including the d32x and d64x suffixes) etc. 2024-11-13 Jakub Jelinek <jakub@redhat.com> libcpp/ * expr.cc (interpret_float_suffix): Handle d32 and D32 suffixes for C like df, d64 and D64 like dd and d128 and D128 like dl. gcc/c-family/ * c-lex.cc (interpret_float): Subtract 3 or 4 from copylen rather than 2 if last character of CPP_N_DFLOAT is a digit. gcc/testsuite/ * gcc.dg/dfp/c11-constants-3.c: New test. * gcc.dg/dfp/c11-constants-4.c: New test. * gcc.dg/dfp/c23-constants-3.c: New test. * gcc.dg/dfp/c23-constants-4.c: New test.
-
Jakub Jelinek authored
The following patch implements the C2Y N3298 paper Introduce complex literals by providing different (or no) diagnostics on imaginary constants (except for integer ones). For _DecimalN constants we don't support _Complex _DecimalN and error on any i/j suffixes mixed with DD/DL/DF, so nothing changed there. 2024-11-13 Jakub Jelinek <jakub@redhat.com> PR c/117029 libcpp/ * include/cpplib.h (struct cpp_options): Add imaginary_constants member. * init.cc (struct lang_flags): Add imaginary_constants bitfield. (lang_defaults): Add column for imaginary_constants. (cpp_set_lang): Copy over imaginary_constants. * expr.cc (cpp_classify_number): Diagnose CPP_N_IMAGINARY non-CPP_N_FLOATING constants differently for C. gcc/testsuite/ * gcc.dg/cpp/pr7263-3.c: Adjust expected diagnostic wording. * gcc.dg/c23-imaginary-constants-1.c: New test. * gcc.dg/c23-imaginary-constants-2.c: New test. * gcc.dg/c23-imaginary-constants-3.c: New test. * gcc.dg/c23-imaginary-constants-4.c: New test. * gcc.dg/c23-imaginary-constants-5.c: New test. * gcc.dg/c23-imaginary-constants-6.c: New test. * gcc.dg/c23-imaginary-constants-7.c: New test. * gcc.dg/c23-imaginary-constants-8.c: New test. * gcc.dg/c23-imaginary-constants-9.c: New test. * gcc.dg/c23-imaginary-constants-10.c: New test. * gcc.dg/c2y-imaginary-constants-1.c: New test. * gcc.dg/c2y-imaginary-constants-2.c: New test. * gcc.dg/c2y-imaginary-constants-3.c: New test. * gcc.dg/c2y-imaginary-constants-4.c: New test. * gcc.dg/c2y-imaginary-constants-5.c: New test. * gcc.dg/c2y-imaginary-constants-6.c: New test. * gcc.dg/c2y-imaginary-constants-7.c: New test. * gcc.dg/c2y-imaginary-constants-8.c: New test. * gcc.dg/c2y-imaginary-constants-9.c: New test. * gcc.dg/c2y-imaginary-constants-10.c: New test. * gcc.dg/c2y-imaginary-constants-11.c: New test. * gcc.dg/c2y-imaginary-constants-12.c: New test.
-
- Nov 02, 2024
-
-
GCC Administrator authored
-
- Nov 01, 2024
-
-
Jakub Jelinek authored
This is an attempt to implement the https://wg21.link/p3034r1 paper, but I'm afraid the wording in the paper is bad for multiple reasons. I think I understand the intent, that the module name and partition if any shouldn't come from macros so that they can be scanned for without preprocessing, but on the other side doesn't want to disable macro expansion in pp-module altogether, because e.g. the optional attribute in module-declaration would be nice to come from macros as which exact attribute is needed might need to be decided based on preprocessor checks. The paper added https://eel.is/c++draft/cpp.module#2 which uses partly the wording from https://eel.is/c++draft/cpp.module#1 The first issue I see is that using that "defined as an object-like macro" from there means IMHO something very different in those 2 paragraphs. As per https://eel.is/c++draft/cpp.pre#7.sentence-1 preprocessing tokens in preprocessing directives aren't subject to macro expansion unless otherwise stated, and so the export and module tokens aren't expanded and so the requirement that they aren't defined as an object-like macro makes perfect sense. The problem with the new paragraph is that https://eel.is/c++draft/cpp.module#3.sentence-1 says that the rest of the tokens are macro expanded and after macro expansion none of the tokens can be defined as an object-like macro, if they would be, they'd be expanded to that. So, I think either the wording needs to change such that not all preprocessing tokens after module are macro expanded, only those which are after the pp-module-name and if any pp-module-partition tokens, or all tokens after module are macro expanded but none of the tokens in pp-module-name and pp-module-partition if any must come from macro expansion. The patch below implements it as if the former would be specified (but see later), so essentially scans the preprocessing tokens after module without expansion, if the first one is an identifier, it disables expansion for it and then if followed by . or : expects another such identifier (again with disabled expansion), but stops after second : is seen. Second issue is that while the global-module-fragment start is fine, matches the syntax of the new paragraph where the pp-tokens[opt] aren't present, there is also private-module-fragment in the syntax where module is followed by : private ; and in that case the colon doesn't match the pp-module-name grammar and appears now to be invalid. I think the https://eel.is/c++draft/cpp.module#2 paragraph needs to change so that it allows also that pp-tokens of a pp-module may also be : pp-tokens[opt] (and in that case, I think the colon shouldn't come from a macro and private and/or ; can). Third issue is that there are too many pp-tokens in https://eel.is/c++draft/cpp.module , one is all the tokens between module keyword and the semicolon and one is the optional extra tokens after pp-module-partition (if any, if missing, after pp-module). Perhaps introducing some other non-terminal would help talking about it? So in "where the pp-tokens (if any) shall not begin with a ( preprocessing token" it isn't obvious which pp-tokens it is talking about (my assumption is the latter) and also whether ( can't appear there just before macro expansion or also after expansion. The patch expects only before expansion, so #define F (); export module foo F would be valid during preprocessing but obviously invalid during compilation, but #define foo(n) n; export module foo (3) would be invalid already during preprocessing. The last issue applies only if the first issue is resolved to allow expansion of tokens after : if first token, or after pp-module-partition if present or after pp-module-name if present. When non-preprocessing scanner sees export module foo.bar:baz.qux; it knows nothing can come from preprocessing macros and is ok, but if it sees export module foo.bar:baz qux then it can't know whether it will be export module foo.bar:baz; or export module foo.bar:baz [[]]; or export module foo.bar:baz.freddy.garply; because qux could be validly a macro, which expands to ; or [[]]; or .freddy.garply; etc. So, either the non-preprocessing scanner would need to note it as possible export of foo.bar:baz* module partitions and preprocess if it needs to know the details or just compile, or if that is not ok, the wording would need to rule out that the expansion of (the second) pp-tokens if any can't start with . or : (colon would be only problematic if it isn't present in the tokens before it already). So, if e.g. defining qux above to . whatever is invalid, then the scanner can rely it sees the whole module name and partition. The patch below implements what is above described as the first variant of the first issue resolution, i.e. disables expansion of as many tokens as could be in the valid module name and module partition syntax, but as soon as it e.g. sees two adjacent identifiers, the second one can be macro expanded. If it is macro expanded though, the expansion can't start with . or :, and if it expands to nothing, tokens after it (whether they come from macro expansion or not) can't start with . or :. So, effectively: #define SEMI ; export module SEMI used to be valid and isn't anymore, #define FOO bar export module FOO; isn't valid, #define COLON : export module COLON private; isn't valid, #define BAR baz export module foo.bar:baz.qux.BAR; isn't valid, #define BAZ .qux export module foo BAZ; isn't valid, #define FREDDY :garply export module foo FREDDY; isn't valid, while #define QUX [[]] export module foo QUX; or #define GARPLY private module : GARPLY; etc. is. 2024-11-01 Jakub Jelinek <jakub@redhat.com> PR c++/114461 libcpp/ * include/cpplib.h: Implement C++26 P3034R1 - Module Declarations Shouldn’t be Macros (or more precisely its expected intent). (NO_DOT_COLON): Define. * internal.h (struct cpp_reader): Add diagnose_dot_colon_from_macro_p member. * lex.cc (cpp_maybe_module_directive): For pp-module, if module keyword is followed by CPP_NAME, ensure all CPP_NAME tokens possibly matching module name and module partition syntax aren't expanded and aren't defined as object-like macros. Verify first token after that doesn't start with open paren. If the next token after module name/partition is CPP_NAME defined as macro, set NO_DOT_COLON flag on it. * macro.cc (cpp_get_token_1): Set pfile->diagnose_dot_colon_from_macro_p if token to be expanded has NO_DOT_COLON bit set in flags. Before returning, if pfile->diagnose_dot_colon_from_macro_p is true and not returning CPP_PADDING or CPP_COMMENT and not during macro expansion preparation, set pfile->diagnose_dot_colon_from_macro_p to false and diagnose if returning CPP_DOT or CPP_COLON. gcc/testsuite/ * g++.dg/modules/cpp-7.C: New test. * g++.dg/modules/cpp-8.C: New test. * g++.dg/modules/cpp-9.C: New test. * g++.dg/modules/cpp-10.C: New test. * g++.dg/modules/cpp-11.C: New test. * g++.dg/modules/cpp-12.C: New test. * g++.dg/modules/cpp-13.C: New test. * g++.dg/modules/cpp-14.C: New test. * g++.dg/modules/cpp-15.C: New test. * g++.dg/modules/cpp-16.C: New test. * g++.dg/modules/cpp-17.C: New test. * g++.dg/modules/cpp-18.C: New test. * g++.dg/modules/cpp-19.C: New test. * g++.dg/modules/cpp-20.C: New test. * g++.dg/modules/pmp-4.C: New test. * g++.dg/modules/pmp-5.C: New test. * g++.dg/modules/pmp-6.C: New test. * g++.dg/modules/token-6.C: New test. * g++.dg/modules/token-7.C: New test. * g++.dg/modules/token-8.C: New test. * g++.dg/modules/token-9.C: New test. * g++.dg/modules/token-10.C: New test. * g++.dg/modules/token-11.C: New test. * g++.dg/modules/token-12.C: New test. * g++.dg/modules/token-13.C: New test. * g++.dg/modules/token-14.C: New test. * g++.dg/modules/token-15.C: New test. * g++.dg/modules/token-16.C: New test. * g++.dg/modules/dir-only-3.C: Expect an error. * g++.dg/modules/dir-only-4.C: Expect an error. * g++.dg/modules/dir-only-5.C: New test. * g++.dg/modules/atom-preamble-2_a.C: In export module malcolm; replace malcolm with kevin. Don't define malcolm macro. * g++.dg/modules/atom-preamble-4.C: Expect an error. * g++.dg/modules/atom-preamble-5.C: New test.
-
- Oct 26, 2024
-
-
GCC Administrator authored
-
- Oct 25, 2024
-
-
Jakub Jelinek authored
I've tried to build stage3 with -Wleading-whitespace=blanks -Wtrailing-whitespace=blank -Wno-error=leading-whitespace=blanks -Wno-error=trailing-whitespace=blank added to STRICT_WARN and that expectably resulted in about 2744 unique trailing whitespace warnings and 124837 leading whitespace warnings when excluding *.md files (which obviously is in big part a generator issue). Others from that are generator related, I think those need to be solved later. The following patch just fixes up the easy case (trailing whitespace), which could be easily automated: for i in `find . -name \*.h -o -name \*.cc -o -name \*.c | xargs grep -l '[ ]$' | grep -v testsuite/`; do sed -i -e 's/[ ]*$//' $i; done I've excluded files which I knew are obviously generated or go FE. Is there anything else we'd want to avoid the changes? Due to patch size, I've split it between gcc/ part and rest (include/, libiberty/, libgcc/, libcpp/, libstdc++-v3/; this part). 2024-10-24 Jakub Jelinek <jakub@redhat.com> include/ * dyn-string.h: Remove trailing whitespace. * libiberty.h: Likewise. * xregex.h: Likewise. * splay-tree.h: Likewise. * partition.h: Likewise. * plugin-api.h: Likewise. * demangle.h: Likewise. * vtv-change-permission.h: Likewise. * fibheap.h: Likewise. * hsa_ext_image.h: Likewise. * hashtab.h: Likewise. * libcollector.h: Likewise. * sort.h: Likewise. * symcat.h: Likewise. * hsa_ext_amd.h: Likewise. libcpp/ * directives.cc: Remove trailing whitespace. * mkdeps.cc: Likewise. * line-map.cc: Likewise. * internal.h: Likewise. * files.cc: Likewise. * init.cc: Likewise. * makeucnid.cc: Likewise. * system.h: Likewise. * include/line-map.h: Likewise. * include/symtab.h: Likewise. * include/cpplib.h: Likewise. * expr.cc: Likewise. * charset.cc: Likewise. * macro.cc: Likewise. * errors.cc: Likewise. * lex.cc: Likewise. * traditional.cc: Likewise. libgcc/ * crtstuff.c: Remove trailing whitespace. * libgcov.h: Likewise. * config/alpha/crtfastmath.c: Likewise. * config/alpha/vms-gcc_shell_handler.c: Likewise. * config/alpha/vms-unwind.h: Likewise. * config/pa/linux-atomic.c: Likewise. * config/pa/linux-unwind.h: Likewise. * config/pa/quadlib.c: Likewise. * config/pa/fptr.c: Likewise. * config/s390/32/_fixsfdi.c: Likewise. * config/s390/32/_fixunssfdi.c: Likewise. * config/s390/32/_fixunsdfdi.c: Likewise. * config/c6x/pr-support.c: Likewise. * config/lm32/_udivsi3.c: Likewise. * config/lm32/libgcc_lm32.h: Likewise. * config/lm32/_udivmodsi4.c: Likewise. * config/lm32/_mulsi3.c: Likewise. * config/lm32/_modsi3.c: Likewise. * config/lm32/_umodsi3.c: Likewise. * config/lm32/_divsi3.c: Likewise. * config/darwin-crt3.c: Likewise. * config/msp430/mpy.c: Likewise. * config/ia64/tf-signs.c: Likewise. * config/ia64/fde-vms.c: Likewise. * config/ia64/unwind-ia64.c: Likewise. * config/ia64/vms-unwind.h: Likewise. * config/ia64/sfp-exceptions.c: Likewise. * config/ia64/quadlib.c: Likewise. * config/ia64/unwind-ia64.h: Likewise. * config/rl78/vregs.h: Likewise. * config/arm/bpabi.c: Likewise. * config/arm/unwind-arm.c: Likewise. * config/arm/pr-support.c: Likewise. * config/arm/linux-atomic.c: Likewise. * config/arm/bpabi-lib.h: Likewise. * config/frv/frvend.c: Likewise. * config/frv/cmovw.c: Likewise. * config/frv/frvbegin.c: Likewise. * config/frv/cmovd.c: Likewise. * config/frv/cmovh.c: Likewise. * config/aarch64/cpuinfo.c: Likewise. * config/i386/crtfastmath.c: Likewise. * config/i386/cygming-crtend.c: Likewise. * config/i386/32/tf-signs.c: Likewise. * config/i386/crtprec.c: Likewise. * config/i386/sfp-exceptions.c: Likewise. * config/i386/w32-unwind.h: Likewise. * config/m32r/initfini.c: Likewise. * config/sparc/crtfastmath.c: Likewise. * config/gcn/amdgcn_veclib.h: Likewise. * config/nios2/linux-atomic.c: Likewise. * config/nios2/linux-unwind.h: Likewise. * config/nios2/lib2-mul.c: Likewise. * config/nios2/lib2-nios2.h: Likewise. * config/xtensa/unwind-dw2-xtensa.c: Likewise. * config/rs6000/darwin-fallback.c: Likewise. * config/rs6000/ibm-ldouble.c: Likewise. * config/rs6000/sfp-machine.h: Likewise. * config/rs6000/darwin-asm.h: Likewise. * config/rs6000/darwin-crt2.c: Likewise. * config/rs6000/aix-unwind.h: Likewise. * config/rs6000/sfp-exceptions.c: Likewise. * config/gthr-vxworks.c: Likewise. * config/riscv/atomic.c: Likewise. * config/visium/memcpy.c: Likewise. * config/darwin-crt-tm.c: Likewise. * config/stormy16/lib2funcs.c: Likewise. * config/arc/ieee-754/divtab-arc-sf.c: Likewise. * config/arc/ieee-754/divtab-arc-df.c: Likewise. * config/arc/initfini.c: Likewise. * config/sol2/gmon.c: Likewise. * config/microblaze/divsi3_table.c: Likewise. * config/m68k/fpgnulib.c: Likewise. * libgcov-driver.c: Likewise. * unwind-dw2.c: Likewise. * fp-bit.c: Likewise. * dfp-bit.h: Likewise. * dfp-bit.c: Likewise. * libgcov-driver-system.c: Likewise. libgcc/config/libbid/ * _le_td.c: Remove trailing whitespace. * bid128_compare.c: Likewise. * bid_div_macros.h: Likewise. * bid64_to_bid128.c: Likewise. * bid64_to_uint32.c: Likewise. * bid128_to_uint64.c: Likewise. * bid64_div.c: Likewise. * bid128_round_integral.c: Likewise. * bid_binarydecimal.c: Likewise. * bid128_string.c: Likewise. * bid_flag_operations.c: Likewise. * bid128_to_int64.c: Likewise. * _mul_sd.c: Likewise. * bid64_mul.c: Likewise. * bid128_noncomp.c: Likewise. * _gt_dd.c: Likewise. * bid64_add.c: Likewise. * bid64_string.c: Likewise. * bid_from_int.c: Likewise. * bid128.c: Likewise. * _ge_dd.c: Likewise. * _ne_sd.c: Likewise. * _dd_to_td.c: Likewise. * _unord_sd.c: Likewise. * bid64_to_uint64.c: Likewise. * _gt_sd.c: Likewise. * _sd_to_td.c: Likewise. * _addsub_td.c: Likewise. * _ne_td.c: Likewise. * bid_dpd.c: Likewise. * bid128_add.c: Likewise. * bid128_next.c: Likewise. * _lt_sd.c: Likewise. * bid64_next.c: Likewise. * bid128_mul.c: Likewise. * _lt_dd.c: Likewise. * _ge_td.c: Likewise. * _unord_dd.c: Likewise. * bid64_sqrt.c: Likewise. * bid_sqrt_macros.h: Likewise. * bid64_fma.c: Likewise. * _sd_to_dd.c: Likewise. * bid_conf.h: Likewise. * bid64_noncomp.c: Likewise. * bid_gcc_intrinsics.h: Likewise. * _gt_td.c: Likewise. * _ge_sd.c: Likewise. * bid128_minmax.c: Likewise. * bid128_quantize.c: Likewise. * bid32_to_bid64.c: Likewise. * bid_round.c: Likewise. * _td_to_sd.c: Likewise. * bid_inline_add.h: Likewise. * bid128_fma.c: Likewise. * _eq_td.c: Likewise. * bid32_to_bid128.c: Likewise. * bid64_rem.c: Likewise. * bid128_2_str_tables.c: Likewise. * _mul_dd.c: Likewise. * _dd_to_sd.c: Likewise. * bid128_div.c: Likewise. * _lt_td.c: Likewise. * bid64_compare.c: Likewise. * bid64_to_int32.c: Likewise. * _unord_td.c: Likewise. * bid128_rem.c: Likewise. * bid_internal.h: Likewise. * bid64_to_int64.c: Likewise. * _eq_dd.c: Likewise. * _td_to_dd.c: Likewise. * bid128_to_int32.c: Likewise. * bid128_to_uint32.c: Likewise. * _ne_dd.c: Likewise. * bid64_quantize.c: Likewise. * _le_dd.c: Likewise. * bid64_round_integral.c: Likewise. * _le_sd.c: Likewise. * bid64_minmax.c: Likewise. libgcc/config/avr/libf7/ * f7-renames.h: Remove trailing whitespace. libstdc++-v3/ * include/debug/debug.h: Remove trailing whitespace. * include/parallel/base.h: Likewise. * include/parallel/types.h: Likewise. * include/parallel/settings.h: Likewise. * include/parallel/multiseq_selection.h: Likewise. * include/parallel/partition.h: Likewise. * include/parallel/random_number.h: Likewise. * include/parallel/find_selectors.h: Likewise. * include/parallel/partial_sum.h: Likewise. * include/parallel/list_partition.h: Likewise. * include/parallel/search.h: Likewise. * include/parallel/algorithmfwd.h: Likewise. * include/parallel/random_shuffle.h: Likewise. * include/parallel/multiway_mergesort.h: Likewise. * include/parallel/sort.h: Likewise. * include/parallel/algobase.h: Likewise. * include/parallel/numericfwd.h: Likewise. * include/parallel/multiway_merge.h: Likewise. * include/parallel/losertree.h: Likewise. * include/bits/basic_ios.h: Likewise. * include/bits/stringfwd.h: Likewise. * include/bits/ostream_insert.h: Likewise. * include/bits/stl_heap.h: Likewise. * include/bits/unordered_map.h: Likewise. * include/bits/hashtable_policy.h: Likewise. * include/bits/stl_iterator_base_funcs.h: Likewise. * include/bits/valarray_before.h: Likewise. * include/bits/regex.h: Likewise. * include/bits/postypes.h: Likewise. * include/bits/stl_iterator.h: Likewise. * include/bits/localefwd.h: Likewise. * include/bits/stl_algo.h: Likewise. * include/bits/ios_base.h: Likewise. * include/bits/stl_function.h: Likewise. * include/bits/basic_string.h: Likewise. * include/bits/hashtable.h: Likewise. * include/bits/valarray_after.h: Likewise. * include/bits/char_traits.h: Likewise. * include/bits/gslice.h: Likewise. * include/bits/locale_facets_nonio.h: Likewise. * include/bits/mask_array.h: Likewise. * include/bits/specfun.h: Likewise. * include/bits/random.h: Likewise. * include/bits/slice_array.h: Likewise. * include/bits/valarray_array.h: Likewise. * include/tr1/float.h: Likewise. * include/tr1/functional_hash.h: Likewise. * include/tr1/math.h: Likewise. * include/tr1/hashtable_policy.h: Likewise. * include/tr1/stdio.h: Likewise. * include/tr1/complex.h: Likewise. * include/tr1/stdbool.h: Likewise. * include/tr1/stdarg.h: Likewise. * include/tr1/inttypes.h: Likewise. * include/tr1/fenv.h: Likewise. * include/tr1/stdlib.h: Likewise. * include/tr1/wchar.h: Likewise. * include/tr1/tgmath.h: Likewise. * include/tr1/limits.h: Likewise. * include/tr1/wctype.h: Likewise. * include/tr1/stdint.h: Likewise. * include/tr1/ctype.h: Likewise. * include/tr1/random.h: Likewise. * include/tr1/shared_ptr.h: Likewise. * include/ext/mt_allocator.h: Likewise. * include/ext/sso_string_base.h: Likewise. * include/ext/debug_allocator.h: Likewise. * include/ext/vstring_fwd.h: Likewise. * include/ext/pointer.h: Likewise. * include/ext/pod_char_traits.h: Likewise. * include/ext/malloc_allocator.h: Likewise. * include/ext/vstring.h: Likewise. * include/ext/bitmap_allocator.h: Likewise. * include/ext/pool_allocator.h: Likewise. * include/ext/type_traits.h: Likewise. * include/ext/ropeimpl.h: Likewise. * include/ext/codecvt_specializations.h: Likewise. * include/ext/throw_allocator.h: Likewise. * include/ext/extptr_allocator.h: Likewise. * include/ext/atomicity.h: Likewise. * include/ext/concurrence.h: Likewise. * include/c_compatibility/wchar.h: Likewise. * include/c_compatibility/stdint.h: Likewise. * include/backward/hash_fun.h: Likewise. * include/backward/binders.h: Likewise. * include/backward/hashtable.h: Likewise. * include/backward/auto_ptr.h: Likewise. * libsupc++/eh_arm.cc: Likewise. * libsupc++/unwind-cxx.h: Likewise. * libsupc++/si_class_type_info.cc: Likewise. * libsupc++/vec.cc: Likewise. * libsupc++/class_type_info.cc: Likewise. * libsupc++/vmi_class_type_info.cc: Likewise. * libsupc++/guard_error.cc: Likewise. * libsupc++/bad_typeid.cc: Likewise. * libsupc++/eh_personality.cc: Likewise. * libsupc++/atexit_arm.cc: Likewise. * libsupc++/pmem_type_info.cc: Likewise. * libsupc++/vterminate.cc: Likewise. * libsupc++/eh_terminate.cc: Likewise. * libsupc++/bad_cast.cc: Likewise. * libsupc++/exception_ptr.h: Likewise. * libsupc++/eh_throw.cc: Likewise. * libsupc++/bad_alloc.cc: Likewise. * libsupc++/nested_exception.cc: Likewise. * libsupc++/pointer_type_info.cc: Likewise. * libsupc++/pbase_type_info.cc: Likewise. * libsupc++/bad_array_new.cc: Likewise. * libsupc++/pure.cc: Likewise. * libsupc++/eh_exception.cc: Likewise. * libsupc++/bad_array_length.cc: Likewise. * libsupc++/cxxabi.h: Likewise. * libsupc++/guard.cc: Likewise. * libsupc++/eh_catch.cc: Likewise. * libsupc++/cxxabi_forced.h: Likewise. * libsupc++/tinfo.h: Likewise.
-