Skip to content
Snippets Groups Projects
  1. Jan 13, 2025
    • Paul-Antoine Arras's avatar
      Accept commas between clauses in OpenMP declare variant · 2ea4801c
      Paul-Antoine Arras authored
      Add support to the Fortran parser for the OpenMP syntax that allows a comma
      after the directive name and between clauses of declare variant. The C and C++
      parsers already support this syntax so only a new test is added.
      
      gcc/fortran/ChangeLog:
      
      	* openmp.cc (gfc_match_omp_declare_variant): Match comma after directive
      	name and between clauses. Emit more useful diagnostics.
      
      gcc/testsuite/ChangeLog:
      
      	* gfortran.dg/gomp/declare-variant-2.f90: Remove error test for a comma
      	after the directive name. Add tests for other invalid syntaxes (extra
      	comma and invalid clause).
      	* c-c++-common/gomp/adjust-args-5.c: New test.
      	* gfortran.dg/gomp/adjust-args-11.f90: New test.
      2ea4801c
    • Jin Ma's avatar
      RISC-V: Fix program logic errors caused by data truncation on 32-bit host for zbs, such as i386 · ecf688ed
      Jin Ma authored
      Correct logic on 64-bit host:
              ...
              bseti   a5,zero,38
              bseti   a5,a5,63
              addi    a5,a5,-1
              and     a4,a4,a5
      	...
      
      Wrong logic on 32-bit host:
      	...
              li      a5,64
              bseti   a5,a5,31
              addi    a5,a5,-1
              and     a4,a4,a5
      	...
      
      gcc/ChangeLog:
      
      	* config/riscv/riscv.cc (riscv_build_integer_1): Change
      	1UL/1ULL to HOST_WIDE_INT_1U.
      
      gcc/testsuite/ChangeLog:
      
      	* gcc.target/riscv/zbs-bug.c: New test.
      ecf688ed
    • Paul-Antoine Arras's avatar
      Add missing target directive in OpenMP dispatch Fortran runtime test · 655a8a02
      Paul-Antoine Arras authored
      Without the target directive, the test would run on the host but still try to
      use device pointers, which causes a segfault.
      
      libgomp/ChangeLog:
      
      	* testsuite/libgomp.fortran/dispatch-1.f90: Add missing target
      	directive.
      655a8a02
    • Gaius Mulley's avatar
      PR modula2/118453: Subranges types do not use virtual tokens during construction · 7cd4de65
      Gaius Mulley authored
      
      P2SymBuild.mod.BuildSubrange does not use a virtual token and therefore
      any error message containing a subrange type produces poor location carots.
      This patch rewrites BuildSubrange and the buildError4 procedure in
      M2Check.mod (which is only called when there is a formal/actual parameter
      mismatch).  buildError4 now issues a sub error for the formal and actual
      type declaration highlighing the type mismatch.
      
      gcc/m2/ChangeLog:
      
      	PR modula2/118453
      	* gm2-compiler/M2Check.mod (buildError4): Call MetaError1
      	for the actual and formal parameter type.
      	* gm2-compiler/P2Build.bnf (SubrangeType): Construct a virtual
      	token containing the subrange type declaration.
      	(PrefixedSubrangeType): Ditto.
      	* gm2-compiler/P2SymBuild.def (BuildSubrange): Add tok parameter.
      	* gm2-compiler/P2SymBuild.mod (BuildSubrange): Use tok parameter,
      	rather than the token at the start of the subrange.
      
      gcc/testsuite/ChangeLog:
      
      	PR modula2/118453
      	* gm2/pim/fail/badbecomes2.mod: New test.
      	* gm2/pim/fail/badparamset1.mod: New test.
      	* gm2/pim/fail/badparamset2.mod: New test.
      	* gm2/pim/fail/badsyntaxset1.mod: New test.
      
      Signed-off-by: default avatarGaius Mulley <gaiusmod2@gmail.com>
      7cd4de65
    • Jeff Law's avatar
      [PR rtl-optimization/107455] Eliminate unnecessary constant load · d23d338d
      Jeff Law authored
      This resurrects a patch from a bit over 2 years ago that I never wrapped up.
      IIRC, I ended up up catching covid, then in the hospital for an unrelated issue
      and it just got dropped on the floor in the insanity.
      
      The basic idea here is to help postreload-cse eliminate more const/copies by
      recording a small set of conditional equivalences (as Richi said in 2022,
      "Ick").
      
      It was originally to help eliminate an unnecessary constant load I saw in
      coremark, but as seen in BZ107455 the same issues show up in real code as well.
      
      Bootstrapped and regression tested on x86-64, also been through multiple spins
      in my tester.
      
      Changes since v2:
      
        - Simplified logic for blocks to examine
        - Remove redundant tests when filtering blocks to examine
        - Remove bogus check which only allowed reg->reg copies
      
      Changes since v1:
      
      Richard B and Richard S both had good comments last time around and their
      requests are reflected in this update:
      
        - Use rtx_equal_p rather than pointer equality
        - Restrict to register "destinations"
        - Restrict to integer modes
        - Adjust entry block handling
      
      My own wider scale testing resulted in a few more changes.
      
        - Robustify extracting the (set (pc) ... ), which then required ...
        - Handle if src/dst are clobbered by the conditional branch
        - Fix logic error causing too many equivalences to be recorded
      
      	PR rtl-optimization/107455
      gcc/
      	* postreload.cc (reload_cse_regs_1): Take advantage of conditional
      	equivalences.
      
      gcc/testsuite
      	* gcc.target/riscv/pr107455-1.c: New test.
      	* gcc.target/riscv/pr107455-2.c: New test.
      d23d338d
    • Alexandre Oliva's avatar
      [ifcombine] propagate signbit mask to XOR right-hand operand · 52e4ede0
      Alexandre Oliva authored
      If a single-bit bitfield takes up the sign bit of a storage unit,
      comparing the corresponding bitfield between two objects loads the
      storage units, XORs them, converts the result to signed char, and
      compares it with zero: ((signed char)(a.<byte> ^ c.<byte>) >= 0).
      
      fold_truth_andor_for_ifcombine recognizes the compare with zero as a
      sign bit test, then it decomposes the XOR into an equality test.
      
      The problem is that, after this decomposition, that figures out the
      width of the accessed fields, we apply the sign bit mask to the
      left-hand operand of the compare, but we failed to also apply it to
      the right-hand operand when both were taken from the same XOR.
      
      This patch fixes that.
      
      
      for  gcc/ChangeLog
      
      	PR tree-optimization/118409
      	* gimple-fold.cc (fold_truth_andor_for_ifcombine): Apply the
      	signbit mask to the right-hand XOR operand too.
      
      for  gcc/testsuite/ChangeLog
      
      	PR tree-optimization/118409
      	* gcc.dg/field-merge-20.c: New.
      52e4ede0
    • Jakub Jelinek's avatar
      expr: Fix up the divmod cost debugging note [PR115910] · 41a5a97d
      Jakub Jelinek authored
      Something I've noticed during working on the crc wrong-code fix.
      My first version of the patch failed because of no longer matching some
      expected strings in the assembly, so I had to add TDF_DETAILS debugging
      into the -fdump-rtl-expand-details dump which the crc tests can use.
      
      For PR115910 Andrew has added similar note for the division/modulo case
      if it is positive and we can choose either unsigned or signed
      division.  The problem is that unlike most other TDF_DETAILS diagnostics,
      this is not done before emitting the IL for the function, but during it.
      
      Other messages there are prefixed with ;;, both details on what it is doing
      and the GIMPLE IL for which it expands RTL, so the
      ;; Generating RTL for gimple basic block 4
      
      ;;
      
      (code_label 13 12 14 2 (nil) [0 uses])
      
      (note 14 13 0 NOTE_INSN_BASIC_BLOCK)
      positive division: unsigned cost: 30; signed cost: 28
      
      ;; return _4;
      
      message in between just looks weird and IMHO should be ;; prefixed.
      
      2025-01-13  Jakub Jelinek  <jakub@redhat.com>
      
      	PR target/115910
      	* expr.cc (expand_expr_divmod): Prefix the TDF_DETAILS note with
      	";; " and add a space before (needed tie breaker).  Formatting fixes.
      41a5a97d
    • Martin Jambor's avatar
      MAINTAINERS: Make contrib/check-MAINTAINERS.py happy · 539fc490
      Martin Jambor authored
      This commit makes the contrib/check-MAINTAINERS.py script happy about
      our MAINTAINERS file.  I hope that it knows best how things ought to
      be and so am committing this as obvious.
      
      ChangeLog:
      
      2025-01-13  Martin Jambor  <mjambor@suse.cz>
      
      	* MAINTAINERS: Fix the name order of the Write After Approval section.
      539fc490
    • Pascal Obry's avatar
      ada: Update gnatdll documentation (-b option removed) · 0cf06bf0
      Pascal Obry authored
      gcc/ada/ChangeLog:
      	* doc/gnat_ugn/platform_specific_information.rst: Update.
      	* gnat_ugn.texi: Regenerate.
      0cf06bf0
    • Javier Miranda's avatar
      ada: Cleanup preanalysis of static expressions (part 5) · 1a826571
      Javier Miranda authored
      Partially revert the fix for sem_ch13.adb as it does not comply
      with RM 13.14(7.2/5).
      
      gcc/ada/ChangeLog:
      
      	* sem_ch13.adb (Check_Aspect_At_End_Of_Declarations): Restore calls
      	to Preanalyze_Spec_Expression that were replaced by calls to
      	Preanalyze_And_Resolve. Add documentation.
      	(Check_Aspect_At_Freeze_Point): Ditto.
      1a826571
    • Pascal Obry's avatar
      ada: Fix relocatable DLL creation with gnatdll · 2e0b086f
      Pascal Obry authored
      gcc/ada/ChangeLog:
      
      	* mdll.adb: For the created DLL to be relocatable we do not want to use
      	the base file name when calling gnatdll.
      	* gnatdll.adb: Removes option -d which is not working anymore. And
      	when using a truly relocatable DLL the base-address has no real
      	meaning. Also reword the usage string for -d as we do not want to
      	specify relocatable as gnatdll can be used to create both
      	relocatable and non relocatable DLL.
      2e0b086f
    • Piotr Trojanek's avatar
      ada: Remove redundant parentheses inside unary operators (cont.) · 492aae16
      Piotr Trojanek authored
      GNAT already emits a style warning when redundant parentheses appear inside
      logical and short-circuit operators. A similar warning will be soon emitted for
      unary operators as well. This patch removes the redundant parentheses to avoid
      build errors.
      
      gcc/ada/ChangeLog:
      
      	* libgnat/a-strunb.ads: Remove redundant parentheses inside NOT
      	operators.
      492aae16
    • Javier Miranda's avatar
      ada: Cleanup preanalysis of static expressions (part 4) · 5fd925bf
      Javier Miranda authored
      Fix regression in the SPARK 2014 testsuite.
      
      gcc/ada/ChangeLog:
      
      	* sem_util.adb (Build_Actual_Subtype_Of_Component): No action
      	under preanalysis.
      	* sem_ch5.adb (Set_Assignment_Type): If the right-hand side contains
      	target names, expansion has been disabled to prevent expansion that
      	might move target names out of the context of the assignment statement.
      	Restore temporarily the current compilation mode so that the actual
      	subtype can be built.
      5fd925bf
    • Piotr Trojanek's avatar
      ada: Warn about redundant parentheses inside unary operators · 686bd4e0
      Piotr Trojanek authored
      GNAT already emits a style warning when redundant parentheses appear inside
      logical and short-circuit operators. A similar warning is now emitted for
      unary operators as well.
      
      gcc/ada/ChangeLog:
      
      	* par-ch4.adb (P_Factor): Warn when the operand of a unary operator
      	doesn't require parentheses.
      686bd4e0
    • Piotr Trojanek's avatar
      ada: Remove redundant parentheses inside unary operators in comments · 34943af1
      Piotr Trojanek authored
      GNAT already emits a style warning when redundant parentheses appear inside
      logical and short-circuit operators. A similar warning will be soon emitted for
      unary operators as well. This patch removes the redundant parentheses to avoid
      future build errors.
      
      gcc/ada/ChangeLog:
      
      	* libgnat/s-genbig.adb: Remove redundant parentheses in comments.
      34943af1
    • Piotr Trojanek's avatar
      ada: Remove redundant parentheses inside unary operators · 94a7543d
      Piotr Trojanek authored
      GNAT already emits a style warning when redundant parentheses appear inside
      logical and short-circuit operators. A similar warning will be soon emitted for
      unary operators as well. This patch removes the redundant parentheses to avoid
      future build errors.
      
      gcc/ada/ChangeLog:
      
      	* checks.adb, exp_dist.adb, exp_imgv.adb, exp_util.adb,
      	libgnarl/a-reatim.adb, libgnat/a-coinve.adb, libgnat/a-nbnbre.adb,
      	libgnat/a-ngcoty.adb, libgnat/a-ngelfu.adb, libgnat/a-ngrear.adb,
      	libgnat/a-strbou.ads, libgnat/a-strfix.ads, libgnat/a-strsea.adb,
      	libgnat/a-strsea.ads, libgnat/a-strsup.ads,
      	libgnat/a-strunb__shared.ads, libgnat/g-alleve.adb,
      	libgnat/g-spitbo.adb, libgnat/s-aridou.adb, libgnat/s-arit32.adb,
      	libgnat/s-dourea.ads, libgnat/s-genbig.adb, libgnat/s-imager.adb,
      	libgnat/s-statxd.adb, libgnat/s-widthi.adb, sem_attr.adb, sem_ch10.adb,
      	sem_ch3.adb, sem_ch6.adb, sem_ch7.adb, sem_dim.adb, sem_prag.adb,
      	sem_res.adb, uintp.adb: Remove redundant parentheses inside NOT and ABS
      	operators.
      94a7543d
    • Piotr Trojanek's avatar
      ada: Fix spurious warning about redundant parentheses in range bound · ef4448e0
      Piotr Trojanek authored
      Use the same logic for warning about redundant parentheses in lower and upper
      bounds of a discrete range. This fixes a spurious warning that, if followed,
      would render the code illegal.
      
      gcc/ada/ChangeLog:
      
      	* par-ch3.adb (P_Discrete_Range): Detect redundant parentheses in the
      	lower bound like in the upper bound.
      ef4448e0
    • Gary Dismukes's avatar
      ada: Unbounded recursion on character aggregates with predicated component subtype · c6989fbb
      Gary Dismukes authored
      The compiler was recursing endlessly when analyzing an aggregate of
      an array type whose component subtype has a static predicate and the
      component expressions are static, repeatedly transforming the aggregate
      first into a string literal and then back into an aggregate. This is fixed
      by suppressing the transformation to a string literal in the case where
      the component subtype has predicates.
      
      gcc/ada/ChangeLog:
      
      	* sem_aggr.adb (Resolve_Aggregate): Add another condition to prevent rewriting
      	an aggregate whose type is an array of characters, testing for the presence of
      	predicates on the component type.
      c6989fbb
    • Piotr Trojanek's avatar
      ada: Simplify expansion of negative membership operator · f9d22b7a
      Piotr Trojanek authored
      Code cleanup; semantics is unaffected.
      
      gcc/ada/ChangeLog:
      
      	* exp_ch4.adb: (Expand_N_Not_In): Preserve Alternatives in expanded
      	membership operator just like preserving Right_Opnd (though only
      	one of these fields is present at a time).
      	* par-ch4.adb (P_Membership_Test): Remove redundant setting of fields
      	to their default values.
      f9d22b7a
    • Piotr Trojanek's avatar
      ada: Warn about redundant parentheses in upper range bounds · 518fd9e9
      Piotr Trojanek authored
      Fix a glitch in condition that effectively caused detection of redundant
      parentheses in upper range bounds to be dead code.
      
      gcc/ada/ChangeLog:
      
      	* par-ch3.adb (P_Discrete_Range): Replace N_Subexpr, which was catching
      	all subexpressions, with kinds that catch nodes that require
      	parentheses to become "simple expressions".
      518fd9e9
    • Eric Botcazou's avatar
      ada: Add more commentary to System.Val_Real.Large_Powfive · d2e3635a
      Eric Botcazou authored
      gcc/ada/ChangeLog:
      
      	* libgnat/s-valrea.adb (Large_Powfive) [2 parameters]: Add a couple
      	of additional comments.
      d2e3635a
    • Piotr Trojanek's avatar
      ada: Fix parsing of raise expressions with no parens · 26b649b2
      Piotr Trojanek authored
      According to Ada grammar, raise expression is an expression, but requires
      parens to be a simple_expression. We wrongly classified raise expressions
      as expressions, because we mishandled a global state variable in the parser.
      
      This patch causes some illegal code to be rejected.
      
      gcc/ada/ChangeLog:
      
      	* par-ch4.adb (P_Relation): Prevent Expr_Form to be overwritten when
      	parsing the raise expression itself.
      	(P_Simple_Expression): Fix manipulation of Expr_Form.
      26b649b2
    • Richard Biener's avatar
      tree-optimization/117119 - ICE with int128 IV in dataref analysis · d3904a3a
      Richard Biener authored
      
      Here's another fix for a missing check that an IV value fits in a
      HIW.  It's originally from Stefan.
      
      	PR tree-optimization/117119
      	* tree-data-ref.cc (initialize_matrix_A): Check whether
      	an INTEGER_CST fits in HWI, otherwise return chrec_dont_know.
      
      	* gcc.dg/torture/pr117119.c: New testcase.
      
      Co-Authored-By: default avatarStefan Schulze Frielinghaus <stefansf@linux.ibm.com>
      d3904a3a
    • Thomas Schwinge's avatar
      Un-XFAIL 'dg-note's in 'gfortran.dg/goacc/routine-external-level-of-parallelism-2.f' · c0c47fc8
      Thomas Schwinge authored
      As of the recent commit 65286465
      "Fortran: Fix location_t in gfc_get_extern_function_decl; [...]" change:
      
          The declaration created by gfc_get_extern_function_decl used input_location
          as DECL_SOURCE_LOCATION, which gave rather odd results with 'declared here'
          diagnostic. - It is much more useful to use the gfc_symbol's declated_at,
          which this commit now does.
      
      ..., we're no longer using the 'dg-bogus' location informations, as pointed out
      for one class of additional notes of
      'gfortran.dg/goacc/routine-external-level-of-parallelism-2.f', once added in
      commit 03eb7791 "Add 'dg-note', 'dg-lto-note'".
      Therefore, un-XFAILed 'dg-note's rather than XFAILed 'dg-bogus'es.
      
      	gcc/testsuite/
      	* gfortran.dg/goacc/routine-external-level-of-parallelism-2.f:
      	Un-XFAIL 'dg-note's.
      c0c47fc8
    • Richard Biener's avatar
      Bump BASE-VER to 14.0.1 now that we are in stage4. · 017c45fa
      Richard Biener authored
      	* BASE-VER: Bump to 14.0.1.
      017c45fa
    • Michal Jires's avatar
      lto: Pass cache checksum by reference [PR118181] · 9100be57
      Michal Jires authored
      Bootstrapped/regtested on x86_64-linux. Committed as obvious.
      
      	PR lto/118181
      
      gcc/ChangeLog:
      
      	* lto-ltrans-cache.cc (ltrans_file_cache::create_item):
      	Pass checksum by reference.
      	* lto-ltrans-cache.h: Likewise.
      9100be57
    • Michal Jires's avatar
      lto: Fix empty fnctl.h build error with MinGW. · 89ebb88d
      Michal Jires authored
      MSYS2+MinGW contains headers without defining expected contents.
      This fix checks that the fcntl function is actually defined.
      
      Bootstrapped/regtested on x86_64-linux. Committed as obvious.
      
      gcc/ChangeLog:
      
      	* lockfile.cc (LOCKFILE_USE_FCNTL): New.
      	(lockfile::lock_write): Use LOCKFILE_USE_FCNTL.
      	(lockfile::try_lock_write): Use LOCKFILE_USE_FCNTL.
      	(lockfile::lock_read): Use LOCKFILE_USE_FCNTL.
      	(lockfile::unlock): Use LOCKFILE_USE_FCNTL.
      	(lockfile::lockfile_supported): Use LOCKFILE_USE_FCNTL.
      89ebb88d
    • liuhongt's avatar
      Refactor ix86_expand_vecop_qihi2. · 0e05b793
      liuhongt authored
      Since there's regression to use vpermq, and it's manually disabled by
      !TARGET_AVX512BW. I remove the codes related to vpermq and make
      ix86_expand_vecop_qihi2 only handle vpmovbw + op + vpmovwb case.
      
      gcc/ChangeLog:
      
      	* config/i386/i386-expand.cc (ix86_expand_vecop_qihi2):
      	Refactor to avoid redundant TARGET_AVX512BW in many places.
      0e05b793
    • Jakub Jelinek's avatar
      [PATCH] crc: Fix up some crc related wrong code issues [PR117997, PR118415] · 9c387a99
      Jakub Jelinek authored
      Hi!
      
      As mentioned in the second PR, using table names like
      crc_table_for_crc_8_polynomial_0x12
      in the user namespace is wrong, user could have defined such variables
      in their code and as can be seen on the last testcase, then it just
      misbehaves.
      At minimum such names should start with 2 underscores, moving it into
      implementation namespace, and if possible have some dot or dollar in the
      name if target supports it.
      I think assemble_crc_table right now always emits tables a local variables,
      I really don't see what would be setting TREE_PUBLIC flag on
      IDENTIFIER_NODEs.
      It might be nice to share the tables between TUs in the same binary or
      shared library, but it in that case should have hidden visibility if
      possible, so that it isn't exported from the libraries or binaries, we don't
      want the optimization to affect set of exported symbols from libraries.
      And, as can be seen in the first PR, building gen_rtx_SYMBOL_REF by hand
      is certainly unexpected on some targets, e.g. those which use
      -fsection-anchors, so we should instead use DECL_RTL of the VAR_DECL.
      For that we'd need to look it up if we haven't emitted it already, while
      IDENTIFIER_NODEs can be looked up easily, I guess for the VAR_DECLs we'd
      need custom hash table.
      
      Now, all of the above (except sharing between multiple TUs) is already
      implemented in output_constant_def, so I think it is much better to just
      use that function.
      
      And, if we want to share it between multiple TUs, we could extend the
      SHF_MERGE usage in gcc, currently we only use it for constant pool
      entries with same size as alignment, from 1 to 32 bytes, using .rodata.cstN
      sections.  We could just use say .rodata.cstM.N sections where M would be
      alignment and N would be the entity size.  We could use that for all
      constant pool entries say up to 2048 bytes.
      Though, as the current code doesn't share between multiple TUs, I think it
      can be done incrementally (either still for GCC 15, or GCC 16+).
      
      Bootstrapped/regtested on {x86_64,i686,aarch64,powerpc64le,s390x}-linux, on
      aarch64 it also fixes
      -FAIL: crypto/rsa
      -FAIL: hash
      ok for trunk?
      
      gcc/
      	PR tree-optimization/117997
      	PR middle-end/118415
      	* expr.cc (assemble_crc_table): Make static, remove id argument,
      	use output_constant_def.  Emit note if -fdump-rtl-expand-details
      	about which table has been emitted.
      	(generate_crc_table): Make static, adjust assemble_crc_table
      	caller, call it always.
      	(calculate_table_based_CRC): Make static.
      	* internal-fn.cc (expand_crc_optab_fn): Emit note if
      	-fdump-rtl-expand-details about using optab for crc.  Formatting fix.
      
      gcc/testsuite/
      	* gcc.dg/crc-builtin-target32.c: Add -fdump-rtl-expand-details
      	as dg-additional-options.  Scan expand dump rather than assembly,
      	adjust the regexps.
      	* gcc.dg/crc-builtin-target64.c: Likewise.
      	* gcc.dg/crc-builtin-rev-target32.c: Likewise.
      	* gcc.dg/crc-builtin-rev-target64.c: Likewise.
      	* gcc.dg/pr117997.c: New test.
      	* gcc.dg/pr118415.c: New test.
      9c387a99
    • GCC Administrator's avatar
      Daily bump. · 422c5884
      GCC Administrator authored
      422c5884
  2. Jan 12, 2025
    • Iain Buclaw's avatar
      d: Merge dmd, druntime c7902293d7, phobos 03aeafd20 · a2e540bf
      Iain Buclaw authored
      D front-end changes:
      
      	- Import dmd v2.110.0-rc.1.
      	- An error is now given for subtracting pointers of different
      	  types.
      
      D runtime changes:
      
      	- Import druntime v2.110.0-rc.1.
      
      Phobos changes:
      
      	- Import phobos v2.110.0-rc.1.
      
      gcc/d/ChangeLog:
      
      	* dmd/MERGE: Merge upstream dmd c7902293d7.
      	* dmd/VERSION: Bump version to v2.110.0-rc.1.
      
      libphobos/ChangeLog:
      
      	* libdruntime/MERGE: Merge upstream druntime c7902293d7.
      	* libdruntime/Makefile.am (DRUNTIME_DSOURCES): Rename
      	core/thread/fiber.d to core/thread/fiber/package.d.  Add
      	core/thread/fiber/base.d.
      	* libdruntime/Makefile.in: Regenerate.
      	* src/MERGE: Merge upstream phobos 63fdb282f.
      
      gcc/testsuite/ChangeLog:
      
      	* gdc.dg/asm3.d: Adjust test.
      	* gdc.dg/torture/pr96435.d: Adjust test.
      a2e540bf
    • Thomas Koenig's avatar
      Dump all symbol attributes in show_attr. · f4fa0b7d
      Thomas Koenig authored
      gcc/fortran/ChangeLog:
      
      	* dump-parse-tree.cc (show_attr): Dump all symbol attributes.
      f4fa0b7d
    • Iain Buclaw's avatar
      d: Merge upstream dmd, druntime c57da0cf59, phobos ad8ee5587 · 0dd21bce
      Iain Buclaw authored
      D front-end changes:
      
      	- Import latest fixes from dmd v2.110.0-beta.1.
      	- The `align' attribute now allows to specify `default'
      	  explicitly.
      	- Add primary expression of the form `__rvalue(expression)'
      	  which causes `expression' to be treated as an rvalue, even if
      	  it is an lvalue.
      	- Shortened method syntax can now be used in constructors.
      
      D runtime changes:
      
      	- Import latest fixes from druntime v2.110.0-beta.1.
      
      Phobos changes:
      
      	- Import latest fixes from phobos v2.110.0-beta.1.
      
      gcc/d/ChangeLog:
      
      	* dmd/MERGE: Merge upstream dmd c57da0cf59.
      	* d-codegen.cc (can_elide_copy_p): New.
      	(d_build_call): Use it.
      	* d-lang.cc (d_post_options): Update for new front-end interface.
      
      libphobos/ChangeLog:
      
      	* libdruntime/MERGE: Merge upstream druntime c57da0cf59.
      	* src/MERGE: Merge upstream phobos ad8ee5587.
      	* testsuite/libphobos.init_fini/custom_gc.d: Adjust test.
      
      gcc/testsuite/ChangeLog:
      
      	* gdc.dg/copy1.d: New test.
      0dd21bce
    • David Malcolm's avatar
      c: UX improvements to 'too {few,many} arguments' errors (v5) [PR118112] · a236f706
      David Malcolm authored
      
      Consider this case of a bad call to a callback function (perhaps
      due to C23 changing the meaning of () in function decls):
      
      struct p {
              int (*bar)();
      };
      
      void baz() {
          struct p q;
          q.bar(1);
      }
      
      Before this patch the C frontend emits:
      
      t.c: In function 'baz':
      t.c:7:5: error: too many arguments to function 'q.bar'
          7 |     q.bar(1);
            |     ^
      
      which doesn't give the user much help in terms of knowing what
      was expected, and where the relevant declaration is.
      
      With this patch the C frontend emits:
      
      t.c: In function 'baz':
      t.c:7:5: error: too many arguments to function 'q.bar'; expected 0, have 1
          7 |     q.bar(1);
            |     ^     ~
      t.c:2:15: note: declared here
          2 |         int (*bar)();
            |               ^~~
      
      (showing the expected vs actual counts, the pertinent field decl, and
      underlining the first extraneous argument at the callsite)
      
      Similarly, the patch also updates the "too few arguments" case to also
      show expected vs actual counts.  Doing so requires a tweak to the
      wording to say "at least" for the case of variadic fns where
      previously the C FE emitted e.g.:
      
      s.c: In function 'test':
      s.c:5:3: error: too few arguments to function 'callee'
          5 |   callee ();
            |   ^~~~~~
      s.c:1:6: note: declared here
          1 | void callee (const char *, ...);
            |      ^~~~~~
      
      with this patch it emits:
      
      s.c: In function 'test':
      s.c:5:3: error: too few arguments to function 'callee'; expected at least 1, have 0
          5 |   callee ();
            |   ^~~~~~
      s.c:1:6: note: declared here
          1 | void callee (const char *, ...);
            |      ^~~~~~
      
      gcc/c/ChangeLog:
      	PR c/118112
      	* c-typeck.cc (inform_declaration): Add "function_expr" param and
      	use it for cases where we couldn't show the function decl to show
      	field decls for callbacks.
      	(build_function_call_vec): Add missing auto_diagnostic_group.
      	Update for new param of inform_declaration.
      	(convert_arguments): Likewise.  For the "too many arguments" case
      	add the expected vs actual counts to the message, and if we have
      	it, add the location_t of the first surplus param as a secondary
      	location within the diagnostic.  For the "too few arguments" case,
      	determine the minimum number of arguments required and add the
      	expected vs actual counts to the message, tweaking it to "at least"
      	for variadic functions.
      
      gcc/testsuite/ChangeLog:
      	PR c/118112
      	* gcc.dg/too-few-arguments.c: New test.
      	* gcc.dg/too-many-arguments.c: New test.
      
      Signed-off-by: default avatarDavid Malcolm <dmalcolm@redhat.com>
      a236f706
    • Harald Anlauf's avatar
      Fortran: implement F2018 intrinsic OUT_OF_RANGE [PR115788] · f8eda60e
      Harald Anlauf authored
      Implementation of the Fortran 2018 standard intrinsic OUT_OF_RANGE, with
      the GNU Fortran extension to unsigned integers.
      
      Runtime code is fully inline expanded.
      
      	PR fortran/115788
      
      gcc/fortran/ChangeLog:
      
      	* check.cc (gfc_check_out_of_range): Check arguments to intrinsic.
      	* expr.cc (free_expr0): Fix a memleak with unsigned literals.
      	* gfortran.h (enum gfc_isym_id): Define GFC_ISYM_OUT_OF_RANGE.
      	* gfortran.texi: Add OUT_OF_RANGE to list of intrinsics supporting
      	UNSIGNED.
      	* intrinsic.cc (add_functions): Add Fortran prototype.  Break some
      	nearby lines with excessive length.
      	* intrinsic.h (gfc_check_out_of_range): Add prototypes.
      	* intrinsic.texi: Fortran documentation of OUT_OF_RANGE.
      	* simplify.cc (gfc_simplify_out_of_range): Compile-time simplification
      	of OUT_OF_RANGE.
      	* trans-intrinsic.cc (gfc_conv_intrinsic_out_of_range): Generate
      	inline expansion of runtime code for OUT_OF_RANGE.
      	(gfc_conv_intrinsic_function): Use it.
      
      gcc/testsuite/ChangeLog:
      
      	* gfortran.dg/ieee/out_of_range.f90: New test.
      	* gfortran.dg/out_of_range_1.f90: New test.
      	* gfortran.dg/out_of_range_2.f90: New test.
      	* gfortran.dg/out_of_range_3.f90: New test.
      f8eda60e
    • Maciej W. Rozycki's avatar
      Alpha: Fix a block move pessimisation with zero-extension after LDWU · ed8cd42d
      Maciej W. Rozycki authored
      For the BWX case we have a pessimisation in `alpha_expand_block_move'
      for HImode loads where we place the data loaded into a HImode register
      as well, therefore losing information that indeed the data loaded has
      already been zero-extended to the full DImode width of the register.
      Later on when we store this data in QImode quantities into an unaligned
      destination, we zero-extend it again for the purpose of right-shifting,
      such as with the test case included producing code at `-O2' as follows:
      
      	ldah $2,unaligned_src_hi($29)		!gprelhigh
      	lda $1,unaligned_src_hi($2)		!gprellow
      	ldwu $6,unaligned_src_hi($2)		!gprellow
      	ldwu $5,2($1)
      	ldwu $4,4($1)
      	bis $31,$31,$31
      	zapnot $6,3,$3				# Redundant!
      	ldbu $7,6($1)
      	zapnot $5,3,$2				# Redundant!
      	stb $6,0($16)
      	zapnot $4,3,$1				# Redundant!
      	stb $5,2($16)
      	srl $3,8,$3
      	stb $4,4($16)
      	srl $2,8,$2
      	stb $3,1($16)
      	srl $1,8,$1
      	stb $2,3($16)
      	stb $1,5($16)
      	stb $7,6($16)
      
      The non-BWX case is unaffected, because there we use byte insertion, so
      we don't care that data is held in a HImode register.
      
      Address this by making the holding RTX a HImode subreg of the original
      DImode register, which the RTL passes can then see through and eliminate
      the zero-extension where otherwise required, resulting in this shortened
      code:
      
      	ldah $2,unaligned_src_hi($29)		!gprelhigh
      	lda $1,unaligned_src_hi($2)		!gprellow
      	ldwu $4,unaligned_src_hi($2)		!gprellow
      	ldwu $3,2($1)
      	ldwu $2,4($1)
      	bis $31,$31,$31
      	srl $4,8,$6
      	ldbu $1,6($1)
      	srl $3,8,$5
      	stb $4,0($16)
      	stb $6,1($16)
      	srl $2,8,$4
      	stb $3,2($16)
      	stb $5,3($16)
      	stb $2,4($16)
      	stb $4,5($16)
      	stb $1,6($16)
      
      While at it reformat the enclosing do-while statement according to the
      GNU Coding Standards, observing that in this case it does not obfuscate
      the change owing to the odd original indentation.
      
      	gcc/
      	* config/alpha/alpha.cc (alpha_expand_block_move): Use a HImode
      	subreg of a DImode register to hold data from an aligned HImode
      	load.
      ed8cd42d
    • Maciej W. Rozycki's avatar
      Alpha: Optimize block moves coming from longword-aligned source · 4e557210
      Maciej W. Rozycki authored
      Now that we have proper alignment determination for block moves in place
      the case of copying a block of longword-aligned data has become real, so
      implement the merging of loaded data from pairs of SImode registers into
      single DImode registers for the purpose of using with unaligned stores
      efficiently, as suggested by a comment in `alpha_expand_block_move' and
      discard the comment.  Provide test cases accordingly.
      
      	gcc/
      	* config/alpha/alpha.cc (alpha_expand_block_move): Merge loaded
      	data from pairs of SImode registers into single DImode registers
      	if to be used with unaligned stores.
      
      	gcc/testsuite/
      	* gcc.target/alpha/memcpy-si-aligned.c: New file.
      	* gcc.target/alpha/memcpy-si-unaligned.c: New file.
      	* gcc.target/alpha/memcpy-si-unaligned-dst.c: New file.
      	* gcc.target/alpha/memcpy-si-unaligned-src.c: New file.
      	* gcc.target/alpha/memcpy-si-unaligned-src-bwx.c: New file.
      4e557210
    • Maciej W. Rozycki's avatar
      Alpha: Always respect -mbwx, -mcix, -mfix, -mmax, and their inverse · 19fdb9f3
      Maciej W. Rozycki authored
      Contrary to user documentation the `-mbwx', `-mcix', `-mfix', `-mmax'
      feature options and their inverse forms are ignored whenever `-mcpu='
      option is in effect, either by having been given explicitly or where
      configured as the default such as with the `alphaev56-linux-gnu' target.
      In the latter case there is no way to change the settings these options
      are supposed to tweak other than with `-mcpu=' and the settings cannot
      be individually controlled, making all the feature options permanently
      inactive.
      
      It seems a regression from commit 7816bea0 ("config.gcc: Reorganize
      --with-cpu logic.") back in 2003, which replaced the setting of the
      default feature mask with the setting of the default CPU across a few
      targets, and the complementing logic in the Alpha backend wasn't updated
      accordingly.
      
      Fix this by making the individual feature options take precedence over
      `-mcpu='.  Add test cases to verify this is the case, and to cover the
      defaults as well for the boundary cases.
      
      This has a drawback where the order of the options is ignored between
      `-mcpu=' and these individual options, so e.g. `-mno-bwx -mcpu=ev6' will
      keep the BWX feature disabled even though `-mcpu=ev6' comes later in the
      command line.  This may affect some scenarios involving user overrides
      such as with CFLAGS passed to `configure' and `make' invocations.  I do
      believe it has been our practice anyway for more finegrained options to
      override group options regardless of their relative order on the command
      line and in any case using `-mcpu=ev6 -mbwx' as the override will do the
      right thing if required, canceling any previous `-mno-bwx'.
      
      This has been spotted with `alphaev56-linux-gnu' target verification and
      a recently added test case:
      
      FAIL: gcc.target/alpha/stwx0.c   -O1   scan-assembler-times \\sldq_u\\s 2
      FAIL: gcc.target/alpha/stwx0.c   -O1   scan-assembler-times \\smskwh\\s 1
      FAIL: gcc.target/alpha/stwx0.c   -O1   scan-assembler-times \\smskwl\\s 1
      FAIL: gcc.target/alpha/stwx0.c   -O1   scan-assembler-times \\sstq_u\\s 2
      
      (and similarly for the remaining optimization levels covered) which this
      fix has addressed.
      
      	gcc/
      	* config/alpha/alpha.cc (alpha_option_override): Ignore CPU
      	flags corresponding to features the enabling or disabling of
      	which has been requested with an individual feature option.
      
      	gcc/testsuite/
      	* gcc.target/alpha/target-bwx-1.c: New file.
      	* gcc.target/alpha/target-bwx-2.c: New file.
      	* gcc.target/alpha/target-bwx-3.c: New file.
      	* gcc.target/alpha/target-bwx-4.c: New file.
      	* gcc.target/alpha/target-cix-1.c: New file.
      	* gcc.target/alpha/target-cix-2.c: New file.
      	* gcc.target/alpha/target-cix-3.c: New file.
      	* gcc.target/alpha/target-cix-4.c: New file.
      	* gcc.target/alpha/target-fix-1.c: New file.
      	* gcc.target/alpha/target-fix-2.c: New file.
      	* gcc.target/alpha/target-fix-3.c: New file.
      	* gcc.target/alpha/target-fix-4.c: New file.
      	* gcc.target/alpha/target-max-1.c: New file.
      	* gcc.target/alpha/target-max-2.c: New file.
      	* gcc.target/alpha/target-max-3.c: New file.
      	* gcc.target/alpha/target-max-4.c: New file.
      19fdb9f3
    • Maciej W. Rozycki's avatar
      Alpha: Restore frame pointer last in `builtin_longjmp' [PR64242] · 3cf0e6ab
      Maciej W. Rozycki authored
      Add similar arrangements to `builtin_longjmp' for Alpha as with commit
      71b14428 ("re PR middle-end/64242 (Longjmp expansion incorrect)")
      and commit 511ed59d ("Fix PR64242 - Longjmp expansion incorrect"),
      so as to restore the frame pointer last, so that accesses to a local
      buffer supplied can still be fulfilled with memory accesses via the
      original frame pointer, fixing:
      
      FAIL: gcc.c-torture/execute/pr64242.c   -O0  execution test
      FAIL: gcc.c-torture/execute/pr64242.c   -O1  execution test
      FAIL: gcc.c-torture/execute/pr64242.c   -O2  execution test
      FAIL: gcc.c-torture/execute/pr64242.c   -O3 -g  execution test
      FAIL: gcc.c-torture/execute/pr64242.c   -Os  execution test
      FAIL: gcc.c-torture/execute/pr64242.c   -O2 -flto -fno-use-linker-plugin -flto-partition=none  execution test
      FAIL: gcc.c-torture/execute/pr64242.c   -O2 -flto -fuse-linker-plugin -fno-fat-lto-objects  execution test
      
      and adding no regressions in `alpha-linux-gnu' testing.
      
      	gcc/
      	PR middle-end/64242
      	* config/alpha/alpha.md (`builtin_longjmp'): Restore frame
      	pointer last.  Add frame clobber and schedule blockage.
      3cf0e6ab
    • Maciej W. Rozycki's avatar
      Alpha: Add memory clobbers to `builtin_longjmp' expansion · 46861167
      Maciej W. Rozycki authored
      Add the same memory clobbers to `builtin_longjmp' for Alpha as with
      commit 41439bf6 ("builtins.c (expand_builtin_longjmp): Added two
      memory clobbers."), to prevent instructions that access memory via the
      frame or stack pointer from being moved across the write to the frame
      pointer.
      
      	gcc/
      	* config/alpha/alpha.md (builtin_longjmp): Add memory clobbers.
      46861167
Loading