Skip to content
Snippets Groups Projects
  1. Feb 28, 2023
    • Hans-Peter Nilsson's avatar
      testsuite: Add CRIS to targets not xfailing gcc.dg/attr-alloc_size-11.c:50,51 · 2f2c0bc5
      Hans-Peter Nilsson authored
      Reacting to a long-standing XPASS for CRIS.  Maybe better do
      as https://gcc.gnu.org/PR79356#c11 suggests: xfail it for
      x86 only ...except I see m68k also does not xpass.
      
      testsuite:
      	PR testsuite/79356
      	* gcc.dg/attr-alloc_size-11.c: Add CRIS to the list
      	of targets excluding xfail on lines 50 and 51.
      2f2c0bc5
    • Hans-Peter Nilsson's avatar
      testsuite: Add -fno-ivopts to gcc.dg/Wuse-after-free-2.c, PR108828 · 8c58f4b7
      Hans-Peter Nilsson authored
      For cris-elf before this patch, ever since it was added,
      this test gets:
      
      Running /x/gcc/testsuite/gcc.dg/dg.exp ...
      FAIL: gcc.dg/Wuse-after-free-2.c  (test for warnings, line 115)
      FAIL: gcc.dg/Wuse-after-free-2.c  (test for warnings, line 116)
      
      and comparing tree dumps with a native x86_64-pc-linux-gnu
      run shows a suspicious difference in the "180t.ivopts" dump.
      Indeed -fno-ivopts makes the warning appear for cris-elf
      too.  It was suggested to simply add -fno-ivopts to the
      test-flags, like before -fno-tree-loop-distribute-patterns
      was added; thus.
      
      	PR tree-optimization/108828
      	* gcc.dg/Wuse-after-free-2.c: Add -fno-ivopts.
      8c58f4b7
    • GCC Administrator's avatar
      Daily bump. · bf0e0fc0
      GCC Administrator authored
      bf0e0fc0
  2. Feb 27, 2023
    • Harald Anlauf's avatar
      Fortran: fix corner case of IBITS intrinsic [PR108937] · 6cce953e
      Harald Anlauf authored
      gcc/fortran/ChangeLog:
      
      	PR fortran/108937
      	* trans-intrinsic.cc (gfc_conv_intrinsic_ibits): Handle corner case
      	LEN argument of IBITS equal to BITSIZE(I).
      
      gcc/testsuite/ChangeLog:
      
      	PR fortran/108937
      	* gfortran.dg/ibits_2.f90: New test.
      6cce953e
    • Uros Bizjak's avatar
      i386: Do not constrain fmod and remainder patterns with flag_finite_math_only [PR108922] · 8020c9c4
      Uros Bizjak authored
      According to Intel ISA manual, fprem and fprem1 return NaN when invalid
      arithmetic exception is generated. This is documented in Table 8-10 of the
      ISA manual and makes these two instructions fully IEEE compatible.
      
      The reverted patch was based on the data from table 3-30 and 3-31 of the
      Intel ISA manual, where results in case of st(0) being infinity or
      st(1) being 0 are not specified.
      
      2023-02-27  Uroš Bizjak  <ubizjak@gmail.com>
      
      gcc/ChangeLog:
      
      	PR target/108922
      	Revert:
      	* config/i386/i386.md (fmodxf3): Enable for flag_finite_math_only only.
      	(fmod<mode>3): Ditto.
      	(fpremxf4_i387): Ditto.
      	(reminderxf3): Ditto.
      	(reminder<mode>3): Ditto.
      	(fprem1xf4_i387): Ditto.
      8020c9c4
    • Roger Sayle's avatar
      Fix RTL simplifications of FFS, POPCOUNT and PARITY. · ab76d711
      Roger Sayle authored
      In 2011, the rtl.texi documentation was updated to reflect that the
      modes of the RTX unary operations FFS, POPCOUNT and PARITY should
      match those of their operands.  Unfortunately, some of the transformations
      in simplify-rtx.cc predate this tightening of RTL semantics, and have
      not (until now) been updated/fixed.  i.e. The POPCOUNT and PARITY
      optimizations were "correct" when I added them back in 2007.
      
      2023-02-27  Roger Sayle  <roger@nextmovesoftware.com>
      
      gcc/ChangeLog
      	* simplify-rtx.cc (simplify_unary_operation_1) <case FFS>: Avoid
      	generating FFS with mismatched operand and result modes, by using
      	an explicit SIGN_EXTEND/ZERO_EXTEND.
      	<case POPCOUNT>: Likewise, for POPCOUNT of ZERO_EXTEND.
      	<case PARITY>: Likewise, for PARITY of {ZERO,SIGN}_EXTEND.
      ab76d711
    • Gaius Mulley's avatar
      libgm2/libm2pim/sckt.cc:254:3: warning: memset() called to fill 0 bytes [PR108944] · e5fcf084
      Gaius Mulley authored
      
      The pattern parameter to memset is second.  Correct an obvious mistake
      in libm2pim/sckt.cc.
      
      libgm2/ChangeLog:
      
      	PR modula2/108944
      	* libm2pim/sckt.cc (getLocalIP): Correct parameter order.
      
      Signed-off-by: default avatarGaius Mulley <gaiusmod2@gmail.com>
      e5fcf084
    • Patrick Palka's avatar
      don't declare header-defined functions both static and inline, cont. · b800f80b
      Patrick Palka authored
      This fixes some header-defined functions that are undesirably declared
      static and weren't caught by the "^static inline" pattern used for the
      main patch r13-6096-gcb3e0eac262e55.
      
      gcc/ChangeLog:
      
      	* hash-table.h (gt_pch_nx(hash_table<D>)): Remove static.
      	* lra-int.h (lra_change_class): Likewise.
      	* recog.h (which_op_alt): Likewise.
      	* sel-sched-ir.h (sel_bb_empty_or_nop_p): Declare inline
      	instead of static.
      b800f80b
    • Jonathan Wakely's avatar
      libstdc++: Add Doxygen comment for string::resize_and_overwite · dfa85bee
      Jonathan Wakely authored
      This is a complicated API that should be clearly documented.
      
      Also improve the comment on basic_ios::_M_setstate.
      
      libstdc++-v3/ChangeLog:
      
      	* include/bits/basic_ios.h (basic_ios::_M_setstate): Add
      	caveat to comment.
      	* include/bits/basic_string.h (resize_and_overwrite): Add
      	doxygen comment.
      dfa85bee
    • Takayuki 'January June' Suwa's avatar
      xtensa: Make use of CLAMPS instruction if configured · ce83c3e4
      Takayuki 'January June' Suwa authored
      This patch introduces the use of CLAMPS instruction when the instruction
      is configured.
      
          /* example */
          int test(int a) {
            if (a < -512)
              return -512;
            if (a > 511)
              return 511;
            return a;
          }
      
          ;; prereq: TARGET_CLAMPS
          test:
      	clamps	a2, a2, 9
      	ret.n
      
      gcc/ChangeLog:
      
      	* config/xtensa/xtensa-protos.h (xtensa_match_CLAMPS_imms_p):
      	New prototype.
      	* config/xtensa/xtensa.cc (xtensa_match_CLAMPS_imms_p):
      	New function.
      	* config/xtensa/xtensa.h (TARGET_CLAMPS): New macro definition.
      	* config/xtensa/xtensa.md (*xtensa_clamps): New insn pattern.
      ce83c3e4
    • Max Filippov's avatar
      gcc: xtensa: add XCHAL_HAVE_{CLAMPS,DEPBITS,EXCLUSIVE,XEA3} to dynconfig · 999b7aab
      Max Filippov authored
      gcc/
      	* config/xtensa/xtensa-dynconfig.cc (xtensa_get_config_v2)
      	(xtensa_get_config_v3): New functions.
      
      include/
      	* xtensa-dynconfig.h (xtensa_config_v3): New struct.
      	(xtensa_get_config_v3): New declaration.
      	(XCHAL_HAVE_CLAMPS, XCHAL_HAVE_DEPBITS, XCHAL_HAVE_EXCLUSIVE)
      	(XCHAL_HAVE_XEA3, XTENSA_CONFIG_V3_ENTRY_LIST): New definitions.
      	(XTENSA_CONFIG_INSTANCE_LIST): Add xtensa_config_v3 instance.
      	(XTENSA_CONFIG_ENTRY_LIST): Add XTENSA_CONFIG_V3_ENTRY_LIST.
      999b7aab
    • Kyrylo Tkachov's avatar
      aarch64: Fix typo in comment for aarch64_abs<mode> · 16cfd803
      Kyrylo Tkachov authored
      gcc/ChangeLog:
      
      	* config/aarch64/aarch64-simd.md (aarch64_abs<mode>): Fix typo in comment.
      16cfd803
    • Lulu Cheng's avatar
      LoongArch: Change the value of macro TRY_EMPTY_VM_SPACE from 0x8000000000 to 0x1000000000. · 529e03b9
      Lulu Cheng authored
      The PCH mechanism first tries to map the .gch file to the virtual memory
      space pointed to by TRY_EMPTY_VM_SPACE during the compilation process.
      
      The original value of TRY_EMPTY_VM_SPACE macro is 0x8000000000,
      but like la464 only has 40 bits of virtual address space, this value
      just exceeds the address range.
      
      If we want to support chips with less than 40 bits virtual addresses,
      then the value of this macro needs to be set small. I think setting
      this value small will increase the probability of virtual address
      mapping failure. And the purpose of pch is to make compilation faster,
      but I think we rarely compile on embedded systems. So this situation
      may not be within our consideration.
      
      So change the value of this macro to 0x1000000000.
      
      gcc/ChangeLog:
      
      	* config/host-linux.cc (TRY_EMPTY_VM_SPACE): Modify the value of
      	the macro to 0x1000000000.
      529e03b9
    • GCC Administrator's avatar
      Daily bump. · 2cd665b1
      GCC Administrator authored
      2cd665b1
  3. Feb 26, 2023
  4. Feb 25, 2023
    • Gaius Mulley's avatar
      Disable tower socket runtest (gm2-simple-execute). · 3dd348d0
      Gaius Mulley authored
      
      The projects-pim-run-pass-tower.exp test blocks indefinitely
      on some platforms.  This patch disables it for now - it should
      be enabled once a cross platform fix for RTint.mod is found.
      Even disable the trivial execution test.
      
      gcc/testsuite/ChangeLog:
      
      	* gm2/projects/pim/run/pass/tower/projects-pim-run-pass-tower.exp:
      	Also add conditional to gm2-simple-execute.
      
      Signed-off-by: default avatarGaius Mulley <gaiusmod2@gmail.com>
      3dd348d0
    • Gaius Mulley's avatar
      Disable tower socket runtest · a553fc87
      Gaius Mulley authored
      
      The projects-pim-run-pass-tower.exp test blocks indefinitely
      on some platforms.  This patch disables it for now - it should
      be enabled once a cross platform fix for RTint.mod is found.
      
      gcc/testsuite/ChangeLog:
      
      	* gm2/projects/pim/run/pass/tower/projects-pim-run-pass-tower.exp
      	(gm2_run_tower_test): New global variable.  Add conditional
      	before invoking gm2-local-exec.
      
      Signed-off-by: default avatarGaius Mulley <gaiusmod2@gmail.com>
      a553fc87
    • Mikael Morin's avatar
      fortran: Reuse associated_dummy memory if previously allocated [PR108923] · 5c638095
      Mikael Morin authored
      This avoids making the associted_dummy field point to a new memory chunk
      if it's already pointing somewhere, in which case doing so would leak the
      previously allocated chunk.
      
      	PR fortran/108923
      
      gcc/fortran/ChangeLog:
      
      	* intrinsic.cc (get_intrinsic_dummy_arg,
      	set_intrinsic_dummy_arg): Rename the former to the latter.
      	Remove the return value, add a reference to the lhs as argument,
      	and do the pointer assignment inside the function.  Don't do
      	it if the pointer is already non-NULL.
      	(sort_actual): Update caller.
      5c638095
    • Hans-Peter Nilsson's avatar
      testsuite: Don't include multiline patterns in the the pass/fail log · a24b2720
      Hans-Peter Nilsson authored
      I see overlong lines in the output when a test fails, for
      example for a bug exposed for cris-elf and pru-elf in
      gcc.dg/analyzer/allocation-size-multiline-3.c:
      
      Running /x/gcc/testsuite/gcc.dg/analyzer/analyzer.exp ...
      FAIL: gcc.dg/analyzer/allocation-size-multiline-3.c expected multiline pattern lines 16-25 not found: "\s*int32_t \*ptr = alloca \(99\);[^\n\r]*\n                  \^~~~~~\n  'test_constant_99': events 1-2[^\n\r]*\n    \|[^\n\r]*\n    \|   int32_t \*ptr = alloca \(99\);[^\n\r]*\n    \|                  \^~~~~~\n    \|                  \|[^\n\r]*\n    \|                  \(1\) allocated 99 bytes here[^\n\r]*\n    \|                  \(2\) assigned to 'int32_t \*' \{aka 'int \*'\} here; 'sizeof \(int32_t \{aka int\}\)' is '4'[^\n\r]*\n    \|[^\n\r]*\n"
      FAIL: gcc.dg/analyzer/allocation-size-multiline-3.c expected multiline pattern lines 34-43 not found: "   int32_t \*ptr = alloca \(n \* 2\);[^\n\r]*\n                  \^~~~~~\n  'test_symbolic': events 1-2[^\n\r]*\n    \|[^\n\r]*\n    \|   int32_t \*ptr = alloca \(n \* 2\);[^\n\r]*\n    \|                  \^~~~~~\n    \|                  \|[^\n\r]*\n    \|                  \(1\) allocated 'n \* 2' bytes here[^\n\r]*\n    \|                  \(2\) assigned to 'int32_t \*' \{aka 'int \*'\} here; 'sizeof \(int32_t \{aka int\}\)' is '4'[^\n\r]*\n    \|[^\n\r]*\n"
      FAIL: gcc.dg/analyzer/allocation-size-multiline-3.c (test for excess errors)
      
      That multiline-pattern-quoted-on-a-single-line is redundant
      when also outputting "lines 16-25" and "lines 34-43".  It's
      also so noisy that it can be mistaken for a testsuite error.
      If there's a need to inspect it, it can be seen at
      verbose-level 4, i.e. persons interested in seeing it
      without editing sources can just add "-v -v -v -v".
      
      Let's "prune" the pattern from regular output, instead producing:
      Running /x/gcc/testsuite/gcc.dg/analyzer/analyzer.exp ...
      FAIL: gcc.dg/analyzer/allocation-size-multiline-3.c expected multiline pattern lines 16-25 not found
      FAIL: gcc.dg/analyzer/allocation-size-multiline-3.c expected multiline pattern lines 34-43 not found
      FAIL: gcc.dg/analyzer/allocation-size-multiline-3.c (test for excess errors)
      
      	* lib/multiline.exp (handle-multiline-outputs): Don't include the
      	quoted multiline pattern in the pass/fail output.
      a24b2720
    • Harald Anlauf's avatar
      Fortran: fix memory leak with real to integer conversion warning · 03c60e52
      Harald Anlauf authored
      gcc/fortran/ChangeLog:
      
      	* arith.cc (gfc_real2int): Clear mpfr variable after use.
      03c60e52
    • Gaius Mulley's avatar
      modula-2 module registration process seems to fail with shared libraries [PR108261] · 05652ac4
      Gaius Mulley authored
      
      The commit adds pathnames to modula-2 which in turn appears in any
      external symbol.  This is necessary to allow different dialects of
      libraries to coexist (different implementations of SYSTEM and Storage
      for example in libm2pim and libm2iso).  It also makes it easier to
      debug as the library name forms part of the external mangled name.
      By default pathnames are not user facing.  This commit fixes
      PR108261.
      
      gcc/ChangeLog:
      
      	PR modula2/108261
      	* doc/gm2.texi (-fm2-pathname): New option documented.
      	(-fm2-pathnameI): New option documented.
      	(-fm2-prefix=): New option documented.
      	(-fruntime-modules=): Update default module list.
      
      gcc/m2/ChangeLog:
      
      	PR modula2/108261
      	* Make-lang.in (GM2-COMP-BOOT-DEFS): DynamicStringPath.def
      	remove.  DynamicPath.def add.
      	(GM2-COMP-BOOT-MODS): DynamicStringPath.mod remove.
      	DynamicPath.mod add.
      	* Make-maintainer.in (BUILD-BOOT-PPG-H): New dependency.
      	(m2/gm2-ppg-boot/$(SRC_PREFIX)%.o): $(BUILD-BOOT-PPG-H) Add
      	dependency.
      	(PGE-DEF): New definition.
      	(BUILD-BOOT-PG-H): New dependency.
      	(m2/gm2-pg-boot/$(SRC_PREFIX)%.o): $(BUILD-BOOT-PG-H) Add
      	dependency.
      	(BUILD-BOOT-PGE-H): New dependency.
      	(m2/gm2-pge-boot/$(SRC_PREFIX)%.o): $(BUILD-BOOT-PGE-H) Add
      	dependency.
      	(GM2PATH): Add pathname entries.
      	(m2/boot-bin/mc-devel$(exeext)): Add m2/mc-boot-ch/Gm2rtsdummy.o
      	dependency.
      	(m2/boot-bin/mc-opt$(exeext)): Fix -I path.
      	* gm2-compiler/DynamicStringPath.def: Renamed module to
      	DynamicPath.
      	(GetUserPath): Remove.
      	(GetSystemPath): Remove.
      	(SetUserPath): Remove.
      	(SetSystemPath): Remove.
      	(DumpPath): New procedure definition.
      	* gm2-compiler/DynamicStringPath.mod: Renamed module to
      	DynamicPath.
      	(GetUserPath): Remove.
      	(GetSystemPath): Remove.
      	(SetUserPath): Remove.
      	(SetSystemPath): Remove.
      	(DumpPath): Remove Debugging conditional.
      	* gm2-compiler/M2AsmUtil.mod: Import EqualArray, NulName and
      	GetLibName.
      	(Debugging): New declaration.
      	(GetFullSymName): Re-implemented to prefix (mange) libname
      	to any extern variable/procedure which is IsExportQualified.
      	* gm2-compiler/M2Comp.mod (qprintLibName): New procedure.
      	* gm2-compiler/M2Graph.mod (resolveImports): Add libname.
      	* gm2-compiler/M2Options.def (SetM2Prefix): New procedure.
      	(GetM2Prefix): New procedure function.
      	(SetM2PathName): New procedure.
      	(GetM2PathName): New procedure function.
      	* gm2-compiler/M2Options.mod: (SetM2Prefix): New procedure implemented.
      	(GetM2Prefix): New procedure function implemented.
      	(SetM2PathName): New procedure implemented.
      	(GetM2PathName): New procedure function implemented.
      	(RuntimeModuleOverride): Set to DefaultRuntimeModuleOverride.
      	* gm2-compiler/M2Quads.mod: Import GetLibName.
      	(SafeRequestSym) Pass result of GetLibName to RequestDependant.
      	(callRequestDependant): Add libname as a parameter.
      	(BuildM2InitFunction): Add libname as a parameter.
      	(BuildM2FiniFunction): Add libname as a parameter.
      	(BuildM2CtorFunction): Add libname as a parameter.
      	* gm2-compiler/M2Scaffold.mod (LookupModuleSym): Set LibName
      	if a definition source was found.
      	* gm2-compiler/M2Search.def (FindSourceFile): Add named library parameter.
      	(FindSourceDefFile): Add named library parameter.
      	(FindSourceModFile): Add named library parameter.
      	* gm2-compiler/M2Search.mod (FindSourceFile): Reimplement.
      	(FindSourceDefFile): Add named library parameter.
      	(FindSourceModFile): Add named library parameter.
      	* gm2-compiler/SymbolTable.def (MakeProcedureCtorExtern): Add
      	libname parameter.
      	(PutLibName): New procedure.
      	(GetLibName): New procedure function.
      	* gm2-compiler/SymbolTable.mod (MakeProcedureCtorExtern): Add
      	libname parameter.
      	(GenName): Add libname parameter.
      	(InitCtorFields): Add moduleSym as a parameter.
      	(PutCtorExtern): Add libname parameter to GenName.
      	* gm2-gcc/init.cc (_M2_DynamicStringPath_init): Rename function...
      	(_M2_DynamicPath_init): ...to this.
      	(_M2_PathName_init): Added.
      	* gm2-gcc/m2decl.cc (m2decl_DeclareM2linkStaticInitialization):
      	Add m2pim as the manged component of the exported symbol.
      	(m2decl_DeclareM2linkForcedModuleInitOrder): Add m2pim mangle prefix.
      	* gm2-gcc/m2options.h (M2Options_SetM2Prefix): New function.
      	(M2Options_GetM2Prefix): New function.
      	(M2Options_SetM2PathName): New function.
      	(M2Options_GetM2PathName): New function.
      	* gm2-lang.cc (push_back_Ipath): New function.
      	(add_one_import_path): New function.
      	(gm2_langhook_handle_option): Record -I component.  Call
      	SetM2PathName when -fm2-pathname= is seen.  Record -fm2-pathnameI
      	component.  Call SetM2Prefix when -fm2-prefix= is seen.
      	(gm2_langhook_post_options): Iterative over pathname entries
      	and call SetM2PathName, SetSearchPath as appropriate.
      	* gm2-libs-iso/M2RTS.def (ConstructModules): Add libname parameter.
      	(DeconstructModules): Add libname parameter.
      	(RegisterModule): Add libname parameter.
      	(RequestDependant): Add libname parameter.
      	* gm2-libs-iso/M2RTS.mod (ConstructModules): Add libname parameter.
      	(DeconstructModules): Add libname parameter.
      	(RegisterModule): Add libname parameter.
      	(RequestDependant): Add libname parameter.
      	* gm2-libs-min/M2RTS.def (ConstructModules): Add libname parameter.
      	(DeconstructModules): Add libname parameter.
      	(RegisterModule): Add libname parameter.
      	(RequestDependant): Add libname parameter.
      	* gm2-libs-min/M2RTS.mod (ConstructModules): Add libname parameter.
      	(DeconstructModules): Add libname parameter.
      	(RegisterModule): Add libname parameter.
      	(RequestDependant): Add libname parameter.
      	* gm2-libs/M2Dependent.def (ConstructModules): Add libname parameter.
      	(DeconstructModules): Add libname parameter.
      	(RegisterModule): Add libname parameter.
      	(RequestDependant): Add libname parameter.
      	* gm2-libs/M2Dependent.mod (ConstructModules): Add libname parameter.
      	(DeconstructModules): Add libname parameter.
      	(RegisterModule): Add libname parameter.
      	(RequestDependant): Add libname parameter.
      	* gm2-libs/M2RTS.def (ConstructModules): Add libname parameter.
      	(DeconstructModules): Add libname parameter.
      	(RegisterModule): Add libname parameter.
      	(RequestDependant): Add libname parameter.
      	* gm2-libs/M2RTS.mod (ConstructModules): Add libname parameter.
      	(DeconstructModules): Add libname parameter.
      	(RegisterModule): Add libname parameter.
      	(RequestDependant): Add libname parameter.
      	* gm2-libs/RTint.mod (FindVector): Rename variables.
      	(initInputVector): Rename variables.
      	(initOutputVector): Rename variables.
      	(InitTimeVector): Rename variables.
      	(FindVectorNo): Rename variables.
      	(FindPendingVector): Rename variables.
      	(ReArmTimeVector): Rename variables.
      	(GetTimeVector): Rename variables.
      	(AttachVector): Rename variables.
      	(AttachVector): Rename variables.
      	(IncludeVector): Rename variables.
      	(ExcludeVector): Rename variables.
      	(AddFd): Rename variables.
      	(AddFd): Rename variables.
      	(DumpPendingQueue): Rename variables.
      	(stop): Remove.
      	(activatePending): Rename variables.
      	(Listen): Rename variables.
      	* gm2-libs/libc.def (snprintf): New function.
      	* gm2-libs/sckt.def: Change all exported identifiers to be
      	export qualified.
      	* gm2spec.cc (push_back_Ipath): New function.
      	(add_m2_I_path): New function.
      	(lang_specific_driver): Skip -fm2-pathname= and remember pathname.
      	Skip -I and record the path and current pathname.  Call add_m2_I_path.
      	* lang-specs.h: Replace %{I*} with %{fm2-pathname*}.
      	* lang.opt (-fm2-pathname=): New entry.
      	(-fm2-pathname): New entry.
      	(-fm2-prefix=): New entry.
      	* mc-boot-ch/GUnixArgs.cc (_M2_UnixArgs_dep): New function.
      	(_M2_UnixArgs_ctor::_M2_UnixArgs_ctor): New method.
      	* mc-boot-ch/Glibc.c (libc_snprintf): New function.
      	* mc-boot-ch/m2rts.h (M2RTS_RequestDependant): Changed prototype.
      	(M2RTS_RegisterModule): Changed prototype.
      	* mc-boot/GDynamicStrings.c: Rebuild.
      	* mc-boot/GFIO.c: Rebuild.
      	* mc-boot/GIndexing.c: Rebuild.
      	* mc-boot/GM2Dependent.c: Rebuild.
      	* mc-boot/GM2Dependent.h: Rebuild.
      	* mc-boot/GM2EXCEPTION.c: Rebuild.
      	* mc-boot/GM2RTS.c: Rebuild.
      	* mc-boot/GM2RTS.h: Rebuild.
      	* mc-boot/GPushBackInput.c: Rebuild.
      	* mc-boot/GRTExceptions.c: Rebuild.
      	* mc-boot/GRTint.c: Rebuild.
      	* mc-boot/GStdIO.c: Rebuild.
      	* mc-boot/GStringConvert.c: Rebuild.
      	* mc-boot/GSysStorage.c: Rebuild.
      	* mc-boot/Gdecl.c: Rebuild.
      	* mc-boot/Gkeyc.c: Rebuild.
      	* mc-boot/Glibc.h: Rebuild.
      	* mc-boot/GmcComment.c: Rebuild.
      	* mc-boot/GmcComp.c: Rebuild.
      	* mc-boot/GmcDebug.c: Rebuild.
      	* mc-boot/GmcMetaError.c: Rebuild.
      	* mc-boot/GmcStack.c: Rebuild.
      	* mc-boot/GnameKey.c: Rebuild.
      	* mc-boot/GsymbolKey.c: Rebuild.
      	* pge-boot/GASCII.c: Rebuild.
      	* pge-boot/GArgs.c: Rebuild.
      	* pge-boot/GAssertion.c: Rebuild.
      	* pge-boot/GDebug.c: Rebuild.
      	* pge-boot/GDynamicStrings.c: Rebuild.
      	* pge-boot/GFIO.c: Rebuild.
      	* pge-boot/GIO.c: Rebuild.
      	* pge-boot/GIndexing.c: Rebuild.
      	* pge-boot/GLists.c: Rebuild.
      	* pge-boot/GM2Dependent.c: Rebuild.
      	* pge-boot/GM2Dependent.h: Rebuild.
      	* pge-boot/GM2EXCEPTION.c: Rebuild.
      	* pge-boot/GM2RTS.c: Rebuild.
      	* pge-boot/GM2RTS.h: Rebuild.
      	* pge-boot/GNameKey.c: Rebuild.
      	* pge-boot/GNumberIO.c: Rebuild.
      	* pge-boot/GOutput.c: Rebuild.
      	* pge-boot/GPushBackInput.c: Rebuild.
      	* pge-boot/GRTExceptions.c: Rebuild.
      	* pge-boot/GSFIO.c: Rebuild.
      	* pge-boot/GStdIO.c: Rebuild.
      	* pge-boot/GStorage.c: Rebuild.
      	* pge-boot/GStrCase.c: Rebuild.
      	* pge-boot/GStrIO.c: Rebuild.
      	* pge-boot/GStrLib.c: Rebuild.
      	* pge-boot/GSymbolKey.c: Rebuild.
      	* pge-boot/GSysExceptions.c (_M2_SysExceptions_finish): Rename this...
      	(_M2_SysExceptions_fini): ... to this.
      	* pge-boot/GSysStorage.c: Rebuild.
      	(_M2_SysStorage_finish): Rename this...
      	(_M2_SysStorage_fini): ... to this.
      	* pge-boot/GUnixArgs.cc: New file.
      	* pge-boot/Gbnflex.c (_M2_bnflex_finish): Rename this...
      	(_M2_bnflex_fini): ... to this.
      	* pge-boot/Gerrno.c (_M2_errno_finish): Rename this...
      	(_M2_errno_fini): ... to this.
      	* pge-boot/Glibc.c (libc_snprintf): New function.
      	* pge-boot/Glibc.h (libc_snprintf): New prototype.
      	* pge-boot/Gpge.c (_M2_pge_finish): Rename this...
      	(_M2_pge_fini): ... to this.
      	* pge-boot/Gtermios.cc (_M2_termios_finish): Rename this...
      	(_M2_termios_fini): ... to this.
      	* pge-boot/main.c (_M2_RTExceptions_finish): Rename this...
      	(_M2_RTExceptions_fini): ... to this.
      	(_M2_M2EXCEPTION_finish): Rename this...
      	(_M2_M2EXCEPTION_fini): ... to this.
      	(_M2_M2RTS_finish): Rename this...
      	(_M2_M2RTS_fini): ... to this.
      	(_M2_SysExceptions_finish): Rename this...
      	(_M2_SysExceptions_fini): ... to this.
      	(_M2_StrLib_finish): Rename this...
      	(_M2_StrLib_fini): ... to this.
      	(_M2_errno_finish): Rename this...
      	(_M2_errno_fini): ... to this.
      	(_M2_termios_finish): Rename this...
      	(_M2_termios_fini): ... to this.
      	(_M2_IO_finish): Rename this...
      	(_M2_IO_fini): ... to this.
      	(_M2_StdIO_finish): Rename this...
      	(_M2_StdIO_fini): ... to this.
      	(_M2_Debug_finish): Rename this...
      	(_M2_Debug_fini): ... to this.
      	(_M2_SysStorage_finish): Rename this...
      	(_M2_SysStorage_fini): ... to this.
      	(_M2_Storage_finish): Rename this...
      	(_M2_Storage_fini): ... to this.
      	(_M2_StrIO_finish): Rename this...
      	(_M2_StrIO_fini): ... to this.
      	(_M2_DynamicStrings_finish): Rename this...
      	(_M2_DynamicStrings_fini): ... to this.
      	(_M2_Assertion_finish): Rename this...
      	(_M2_Assertion_fini): ... to this.
      	(_M2_Indexing_finish): Rename this...
      	(_M2_Indexing_fini): ... to this.
      	(_M2_NameKey_finish): Rename this...
      	(_M2_NameKey_fini): ... to this.
      	(_M2_NumberIO_finish): Rename this...
      	(_M2_NumberIO_fini): ... to this.
      	(_M2_PushBackInput_finish): Rename this...
      	(_M2_PushBackInput_fini): ... to this.
      	(_M2_SymbolKey_finish): Rename this...
      	(_M2_SymbolKey_fini): ... to this.
      	(_M2_UnixArgs_finish): Rename this...
      	(_M2_UnixArgs_fini): ... to this.
      	(_M2_FIO_finish): Rename this...
      	(_M2_FIO_fini): ... to this.
      	(_M2_SFIO_finish): Rename this...
      	(_M2_SFIO_fini): ... to this.
      	(_M2_StrCase_finish): Rename this...
      	(_M2_StrCase_fini): ... to this.
      	(_M2_bnflex_finish): Rename this...
      	(_M2_bnflex_fini): ... to this.
      	(_M2_Lists_finish): Rename this...
      	(_M2_Lists_fini): ... to this.
      	(_M2_Args_finish): Rename this...
      	(_M2_Args_fini): ... to this.
      	(_M2_Output_finish): Rename this...
      	(_M2_Output_fini): ... to this.
      	(_M2_pge_finish): Rename this...
      	(_M2_pge_fini): ... to this.
      	* plugin/m2rte.cc (m2_runtime_error_calls): Change all runtime
      	procedure names to their name mangled counterparts.
      	* gm2-libs-iso/wrapsock.c: Removed.
      	* gm2-libs-iso/wraptime.c: Removed.
      	* mc-boot/Gpth.h: Removed.
      	* gm2-compiler/PathName.def: New file.
      	* gm2-compiler/PathName.mod: New file.
      
      libgm2/ChangeLog:
      
      	PR modula2/108261
      	* libm2cor/KeyBoardLEDs.cc (EXPORT): New define.
      	(M2EXPORT): New define.
      	(M2LIBNAME): New define.
      	(KeyBoardLEDs_SwitchScroll): EXPORT.
      	(KeyBoardLEDs_SwitchNum): EXPORT.
      	(KeyBoardLEDs_SwitchCaps): EXPORT.
      	(KeyBoardLEDs_SwitchLeds): EXPORT.
      	(_M2_KeyBoardLEDs_init): M2EXPORT.
      	(_M2_KeyBoardLEDs_finish): M2EXPORT.
      	(_M2_KeyBoardLEDs_dep): M2EXPORT.
      	* libm2cor/Makefile.am (libm2cor_la_M2FLAGS): Define
      	path names.
      	* libm2cor/Makefile.in: Rebuild.
      	* libm2iso/ErrnoCategory.cc (EXPORT): New define.
      	(M2EXPORT): New define.
      	(M2LIBNAME): New define.
      	(ErrnoCategory_IsErrnoHard): EXPORT.
      	(ErrnoCategory_IsErrnoSoft): EXPORT.
      	(ErrnoCategory_UnAvailable): EXPORT.
      	(ErrnoCategory_GetOpenResults): EXPORT.
      	(_M2_ErrnoCategory_init): M2EXPORT.
      	(_M2_ErrnoCategory_fini): M2EXPORT.
      	(_M2_ErrnoCategory_dep): M2EXPORT.
      	(_M2_ErrnoCategory_ctor): M2EXPORT.
      	* libm2iso/Makefile.am (libm2iso_la_M2FLAGS): Define
      	path names.
      	* libm2iso/Makefile.in: Rebuild.
      	* libm2iso/RTco.cc (EXPORT): New define.
      	(M2EXPORT): New define.
      	(M2LIBNAME): New define.
      	(newSem): Add module libname prefix to HaltC.
      	(currentThread): Remove variable and replace with a function.
      	(never): Add module libname prefix to HaltC.
      	(initThread): Add module libname prefix to HaltC.
      	* libm2iso/m2rts.h (str): New define.
      	(M2RTS_RequestDependant): Change to the mangled name equivalent.
      	(M2RTS_RegisterModule): Change to the mangled name equivalent.
      	(m2iso_M2RTS_RequestDependant): Add libname parameter.
      	(m2iso_M2RTS_RegisterModule): Add libname parameter.
      	(m2pim_M2RTS_RegisterModule): Add libname parameter.
      	(_M2_M2RTS_init): Rename this...
      	(m2iso_M2_M2RTS_init): ...to this.
      	(M2RTS_ConstructModules): Change to the mangled name equivalent.
      	(M2RTS_Terminate): Change to the mangled name equivalent.
      	(M2RTS_DeconstructModules): Change to the mangled name equivalent.
      	(m2iso_M2RTS_ConstructModules): Add libname parameter.
      	(m2iso_M2RTS_Terminate): Add libname parameter.
      	(m2iso_M2RTS_DeconstructModules): Add libname parameter.
      	(M2RTS_HaltC): Rename this...
      	(m2iso_M2RTS_HaltC): ...to this.
      	* libm2iso/wrapsock.c (EXPORT): New define.
      	(IMPORT): New define.
      	(M2EXPORT): New define.
      	(M2LIBNAME): New define.
      	(m2iso_M2RTS_RequestDependant): Add prototype.
      	(wrapsock_clientOpen): EXPORT.
      	(wrapsock_clientOpenIP): EXPORT.
      	(wrapsock_getClientPortNo): EXPORT.
      	(wrapsock_getClientHostname): EXPORT.
      	(wrapsock_getClientSocketFd): EXPORT.
      	(wrapsock_getClientIP): EXPORT.
      	(wrapsock_getPushBackChar): EXPORT.
      	(wrapsock_setPushBackChar): EXPORT.
      	(wrapsock_getSizeOfClientInfo): EXPORT.
      	(_M2_wrapsock_init): M2EXPORT.
      	(_M2_wrapsock_fini): M2EXPORT.
      	(ctor): M2EXPORT.  New function.
      	* libm2iso/wraptime.c: Rename to...
      	* libm2iso/wraptime.cc: ...this.
      	(EXPORT): New define.
      	(M2EXPORT): New define.
      	(M2LIBNAME): New define.
      	(wraptime_InitTimeval): EXPORT.
      	(wraptime_KillTimeval): EXPORT.
      	(wraptime_InitTimezone): EXPORT.
      	(wraptime_KillTimezone): EXPORT.
      	(wraptime_InitTM): EXPORT.
      	(wraptime_KillTM): EXPORT.
      	(wraptime_gettimeofday): EXPORT.
      	(wraptime_settimeofday): EXPORT.
      	(wraptime_GetFractions): EXPORT.
      	(wraptime_localtime_r): EXPORT.
      	(wraptime_GetYear): EXPORT.
      	(wraptime_GetMonth): EXPORT.
      	(wraptime_GetDay): EXPORT.
      	(wraptime_GetHour): EXPORT.
      	(wraptime_GetMinute): EXPORT.
      	(wraptime_GetSecond): EXPORT.
      	(wraptime_GetSummerTime): EXPORT.
      	(wraptime_GetDST): EXPORT.
      	(wraptime_SetTimezone): EXPORT.
      	(wraptime_SetTimeval): EXPORT.
      	(_M2_wraptime_init): M2EXPORT.
      	(_M2_wraptime_fini): M2EXPORT.
      	(ctor): M2EXPORT.  New function.
      	* libm2log/Makefile.am (libm2log_la_M2FLAGS): Define
      	path names.
      	* libm2log/Makefile.in:
      	* libm2min/Makefile.am (libm2min_la_M2FLAGS): Define
      	path names.
      	* libm2min/Makefile.in:
      	* libm2pim/Makefile.am (libm2pim_la_M2FLAGS): Define
      	path names.
      	* libm2pim/Makefile.in:
      	* libm2pim/Selective.cc (EXPORT): New define.
      	(M2EXPORT): New define.
      	(M2LIBNAME): New define.
      	(Selective_Select): EXPORT.
      	(Selective_InitTime): EXPORT.
      	(Selective_GetTime): EXPORT.
      	(Selective_SetTime): EXPORT.
      	(Selective_KillTime): EXPORT.
      	(Selective_InitSet): EXPORT.
      	(Selective_KillSet): EXPORT.
      	(Selective_FdZero): EXPORT.
      	(Selective_FdSet): EXPORT.
      	(Selective_FdClr): EXPORT.
      	(Selective_FdIsSet): EXPORT.
      	(Selective_GetTimeOfDay): EXPORT.
      	(Selective_MaxFdsPlusOne): EXPORT.
      	(Selective_WriteCharRaw): EXPORT.
      	(Selective_ReadCharRaw): EXPORT.
      	(_M2_Selective_init): M2EXPORT.
      	(_M2_Selective_fini): M2EXPORT.
      	(_M2_Selective_dep): M2EXPORT.
      	(_M2_Selective_ctor): M2EXPORT.
      	* libm2pim/SysExceptions.cc (EXPORT): New define.
      	(M2EXPORT): New define.
      	(M2LIBNAME): New define.
      	(SysExceptions_InitExceptionHandlers): EXPORT.
      	(_M2_SysExceptions_init): M2EXPORT.
      	(_M2_SysExceptions_fini): M2EXPORT.
      	(_M2_SysExceptions_dep): M2EXPORT.
      	(_M2_SysExceptions_ctor): M2EXPORT.
      	* libm2pim/UnixArgs.cc (EXPORT): New define.
      	(M2EXPORT): New define.
      	(M2LIBNAME): New define.
      	(UnixArgs_GetArgC): EXPORT.
      	(UnixArgs_GetArgV): EXPORT.
      	(UnixArgs_GetEnvV): EXPORT.
      	(_M2_UnixArgs_init): M2EXPORT.
      	(_M2_UnixArgs_fini): M2EXPORT.
      	(_M2_UnixArgs_dep): M2EXPORT.
      	(_M2_UnixArgs_ctor): M2EXPORT.
      	* libm2pim/cgetopt.cc (EXPORT): New define.
      	(M2EXPORT): New define.
      	(M2LIBNAME): New define.
      	(cgetopt_getopt): EXPORT.
      	(cgetopt_getopt_long): EXPORT.
      	(cgetopt_getopt_long_only): EXPORT.
      	(cgetopt_InitOptions): EXPORT.
      	(cgetopt_KillOptions): EXPORT.
      	(cgetopt_SetOption): EXPORT.
      	(cgetopt_GetLongOptionArray): EXPORT.
      	(_M2_cgetopt_init): M2EXPORT.
      	(_M2_cgetopt_fini): M2EXPORT.
      	(_M2_cgetopt_dep): M2EXPORT.
      	(_M2_cgetopt_ctor): M2EXPORT.
      	* libm2pim/dtoa.cc (EXPORT): New define.
      	(M2EXPORT): New define.
      	(M2LIBNAME): New define.
      	(dtoa_strtod): EXPORT.
      	(dtoa_calcmaxsig): EXPORT.
      	(dtoa_calcdecimal): EXPORT.
      	(dtoa_calcsign): EXPORT.
      	(dtoa_dtoa): EXPORT.
      	(_M2_dtoa_init): M2EXPORT.
      	(_M2_dtoa_fini): M2EXPORT.
      	(_M2_dtoa_dep): M2EXPORT.
      	(_M2_dtoa_ctor): M2EXPORT.
      	* libm2pim/errno.cc (EXPORT): New define.
      	(M2EXPORT): New define.
      	(M2LIBNAME): New define.
      	(errno_geterrno): EXPORT.
      	(_M2_errno_init): M2EXPORT.
      	(_M2_errno_fini): M2EXPORT.
      	(_M2_errno_dep): M2EXPORT.
      	(_M2_errno_ctor): M2EXPORT.
      	* libm2pim/ldtoa.cc (EXPORT): New define.
      	(IMPORT): New define.
      	(M2EXPORT): New define.
      	(M2LIBNAME): New define.
      	(dtoa_calcmaxsig): EXPORT.
      	(dtoa_calcdecimal): EXPORT.
      	(dtoa_calcsign): EXPORT.
      	(ldtoa_strtold): EXPORT.
      	(ldtoa_ldtoa): EXPORT.
      	(_M2_ldtoa_init): M2EXPORT.
      	(_M2_ldtoa_fini): M2EXPORT.
      	(_M2_ldtoa_dep): M2EXPORT.
      	(_M2_ldtoa_ctor): M2EXPORT.
      	* libm2pim/sckt.cc (EXPORT): New define.
      	(M2EXPORT): New define.
      	(M2LIBNAME): New define.
      	(tcpServerEstablishPort): EXPORT.
      	(tcpServerEstablish): EXPORT.
      	(tcpServerAccept): EXPORT.
      	(tcpServerPortNo): EXPORT.
      	(tcpServerSocketFd): EXPORT.
      	(getLocalIP): EXPORT.
      	(tcpServerIP): EXPORT.
      	(tcpServerClientIP): EXPORT.
      	(tcpServerClientPortNo): EXPORT.
      	(tcpClientSocket): EXPORT.
      	(tcpClientSocketIP): EXPORT.
      	(tcpClientConnect): EXPORT.
      	(tcpClientPortNo): EXPORT.
      	(tcpClientSocketFd): EXPORT.
      	(tcpClientIP): EXPORT.
      	(_M2_sckt_init): M2EXPORT.
      	(_M2_sckt_finish): M2EXPORT.
      	(_M2_sckt_dep): M2EXPORT.
      	(_M2_sckt_ctor): M2EXPORT.
      	* libm2pim/termios.cc (EXPORT): New define.
      	(M2EXPORT): New define.
      	(M2LIBNAME): New define.
      	(_M2_termios_init): M2EXPORT.
      	(_M2_termios_fini): M2EXPORT.
      	(_M2_termios_dep): M2EXPORT.
      	(_M2_termios_ctor): M2EXPORT.
      	* libm2pim/wrapc.c (EXPORT): New define.
      	(M2EXPORT): New define.
      	(M2LIBNAME): New define.
      	(wrapc_strtime): EXPORT.
      	(wrapc_filesize): EXPORT.
      	(wrapc_filemtime): EXPORT.
      	(wrapc_fileinode): EXPORT.
      	(wrapc_getrand): EXPORT.
      	(wrapc_getusername): EXPORT.
      	(wrapc_getnameuidgid): EXPORT.
      	(wrapc_signbit): EXPORT.
      	(wrapc_signbitl): EXPORT.
      	(wrapc_signbitf): EXPORT.
      	(wrapc_isfinite): EXPORT.
      	(wrapc_isfinitel): EXPORT.
      	(wrapc_isfinitef): EXPORT.
      	(_M2_wrapc_init): M2EXPORT.
      	(_M2_wrapc_fini): M2EXPORT.
      	(_M2_wrapc_ctor): M2EXPORT.
      
      gcc/testsuite/ChangeLog:
      
      	PR modula2/108261
      	* gm2/examples/callingC/pass/examples-callingC-pass.exp: Tidy up
      	variable access.
      	* gm2/examples/callingC/run/pass/examples-callingC-run-pass.exp: Tidy up
      	variable access.
      	* gm2/examples/cpp/pass/examples-cpp-pass.exp: Tidy up
      	variable access.
      	* gm2/examples/cppDef/pass/examples-cppDef-pass.exp: Tidy up
      	variable access.
      	* gm2/examples/hello/pass/examples-hello-pass.exp: Tidy up
      	variable access.
      	* gm2/examples/map/pass/examples-map-pass.exp: Tidy up
      	variable access.
      	* gm2/iso/check/fail/iso-check-fail.exp: Add pathname.
      	* gm2/link/externalscaffold/pass/link-externalscaffold-pass.exp:
      	Add pathname.
      	* gm2/link/externalscaffold/pass/scaffold.c: Add mangled export name.
      	* gm2/pimlib/base/run/pass/FIO.mod: Updated test code.
      	* gm2/pimlib/base/run/pass/StrLib.mod: Updated test code.
      	* gm2/pimlib/base/run/pass/pimlib-base-run-pass.exp: Remove path.
      	* gm2/projects/pim/run/pass/random/projects-pim-run-pass-random.exp:
      	Tidy up variable access.
      	* gm2/switches/auto-init/fail/switches-auto-init-fail.exp: Add pathname.
      	* gm2/switches/check-all/pim2/fail/switches-check-all-pim2-fail.exp:
      	Add pathname.
      	* gm2/switches/makeall/fail/switches-makeall-fail.exp: Remove -fmakeall.
      	* gm2/switches/makeall/pass/switches-makeall-pass.exp: Remove -fmakeall.
      	* lib/gm2-simple.exp (gm2_keep_executable): New global variable.
      	(gm2_simple_execute): Keep executable if global is true.
      	* lib/gm2-torture.exp: Add ; after global variable access.
      	* lib/gm2.exp: Set up pathnames.
      	* gm2/projects/pim/run/pass/tower/AdvCmd.def: New test.
      	* gm2/projects/pim/run/pass/tower/AdvCmd.mod: New test.
      	* gm2/projects/pim/run/pass/tower/AdvIntroduction.def: New test.
      	* gm2/projects/pim/run/pass/tower/AdvIntroduction.mod: New test.
      	* gm2/projects/pim/run/pass/tower/AdvMap.def: New test.
      	* gm2/projects/pim/run/pass/tower/AdvMap.mod: New test.
      	* gm2/projects/pim/run/pass/tower/AdvMath.def: New test.
      	* gm2/projects/pim/run/pass/tower/AdvMath.mod: New test.
      	* gm2/projects/pim/run/pass/tower/AdvParse.bnf: New test.
      	* gm2/projects/pim/run/pass/tower/AdvParse.def: New test.
      	* gm2/projects/pim/run/pass/tower/AdvParse.mod: New test.
      	* gm2/projects/pim/run/pass/tower/AdvSound.def: New test.
      	* gm2/projects/pim/run/pass/tower/AdvSound.mod: New test.
      	* gm2/projects/pim/run/pass/tower/AdvSystem.def: New test.
      	* gm2/projects/pim/run/pass/tower/AdvSystem.mod: New test.
      	* gm2/projects/pim/run/pass/tower/AdvTreasure.def: New test.
      	* gm2/projects/pim/run/pass/tower/AdvTreasure.mod: New test.
      	* gm2/projects/pim/run/pass/tower/AdvUtil.def: New test.
      	* gm2/projects/pim/run/pass/tower/AdvUtil.mod: New test.
      	* gm2/projects/pim/run/pass/tower/DrawG.def: New test.
      	* gm2/projects/pim/run/pass/tower/DrawG.mod: New test.
      	* gm2/projects/pim/run/pass/tower/DrawL.def: New test.
      	* gm2/projects/pim/run/pass/tower/DrawL.mod: New test.
      	* gm2/projects/pim/run/pass/tower/Dungeon.mod: New test.
      	* gm2/projects/pim/run/pass/tower/Lock.def: New test.
      	* gm2/projects/pim/run/pass/tower/Lock.mod: New test.
      	* gm2/projects/pim/run/pass/tower/ProcArgs.def: New test.
      	* gm2/projects/pim/run/pass/tower/ProcArgs.mod: New test.
      	* gm2/projects/pim/run/pass/tower/Screen.def: New test.
      	* gm2/projects/pim/run/pass/tower/Screen.mod: New test.
      	* gm2/projects/pim/run/pass/tower/SocketControl.c: New test.
      	* gm2/projects/pim/run/pass/tower/SocketControl.def: New test.
      	* gm2/projects/pim/run/pass/tower/Window.def: New test.
      	* gm2/projects/pim/run/pass/tower/Window.mod: New test.
      	* gm2/projects/pim/run/pass/tower/adv.flex: New test.
      	* gm2/projects/pim/run/pass/tower/advflex.c: New test.
      	* gm2/projects/pim/run/pass/tower/advflex.def: New test.
      	* gm2/projects/pim/run/pass/tower/projects-pim-run-pass-tower.exp:
      	New test.
      	* gm2/projects/pim/run/pass/tower/star: New test.
      
      Signed-off-by: default avatarGaius Mulley <gaiusmod2@gmail.com>
      05652ac4
    • Max Filippov's avatar
      gcc: xtensa: fix PR target/108919 · 461d3c84
      Max Filippov authored
      gcc/
      	PR target/108919
      
      	* config/xtensa/xtensa-protos.h
      	(xtensa_prepare_expand_call): Rename to xtensa_expand_call.
      	* config/xtensa/xtensa.cc (xtensa_prepare_expand_call): Rename
      	to xtensa_expand_call.
      	(xtensa_expand_call): Emit the call and add a clobber expression
      	for the static chain to it in case of windowed ABI.
      	* config/xtensa/xtensa.md (call, call_value, sibcall)
      	(sibcall_value): Call xtensa_expand_call and complete expansion
      	right after that call.
      
      gcc/testsuite/
      	* gcc.target/xtensa/pr108919.c: New test.
      461d3c84
    • Tobias Burnus's avatar
      Fortran: Skip bound conv in gfc_conv_gfc_desc_to_cfi_desc with intent(out) ptr [PR108621] · d3e427f6
      Tobias Burnus authored
      When the dummy argument of the bind(C) proc is 'pointer, intent(out)', the conversion
      of the GFC to the CFI bounds can be skipped: it is not needed and avoids issues with
      noninit memory.
      
      Note that the 'cfi->base_addr = gfc->addr' assignment is kept as the C code of a user
      might assume that a nullified pointer arrives as NULL (or even a specific value).
      For instance, gfortran.dg/c-interop/section-{1,2}.f90 assumes the value NULL.
      
      Note 2: The PR is about a may-be-uninitialized warning with intent(out). In the PR's
      testcase, the pointer was nullified and should not have produced that warning.
      That is a diagnostic issue, now tracked as PR middle-end/108906 as the issue in principle
      still exists (e.g. with 'intent(inout)'). [But no longer for intent(out).]
      
      Note 3: With undefined pointers and no 'intent', accessing uninit memory is unavoidable
      on the caller side as the compiler cannot know what the C function does (but this usage
      determines whether the pointer is permitted be undefined or whether the bounds must be
      gfc-to-cfi converted).
      
      gcc/fortran/ChangeLog:
      
      	PR fortran/108621
      	* trans-expr.cc (gfc_conv_gfc_desc_to_cfi_desc): Skip setting of
      	bounds of CFI desc for 'pointer,intent(out)'.
      
      gcc/testsuite/ChangeLog:
      
      	PR fortran/108621
      	* gfortran.dg/c-interop/fc-descriptor-pr108621.f90: New test.
      d3e427f6
    • GCC Administrator's avatar
      Daily bump. · 43411063
      GCC Administrator authored
      43411063
  5. Feb 24, 2023
    • Joseph Myers's avatar
      Update .po files · c8373dc8
      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, 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.
      c8373dc8
    • Rimvydas Jasinskas's avatar
      Fortran: Add support for WEAK attribute for variables · bcbeebc4
      Rimvydas Jasinskas authored
      
      Add the rest of the weak-*.f90 testcases.
      
      gcc/fortran/ChangeLog:
      
      	* trans-decl.cc (gfc_finish_var_decl): Apply attribute.
      	(generate_local_decl): Add diagnostic for dummy and local variables.
      
      gcc/testsuite/ChangeLog:
      
      	* gfortran.dg/weak-2.f90: New test.
      	* gfortran.dg/weak-3.f90: New test.
      
      Signed-off-by: default avatarRimvydas Jasinskas <rimvydas.jas@gmail.com>
      bcbeebc4
    • Mikael Morin's avatar
      fortran: Plug leak of associated_dummy memory. [PR108923] · 24c9edfa
      Mikael Morin authored
      This fixes a memory leak by accompanying the release of
      gfc_actual_arglist elements' memory with a release of the
      associated_dummy field memory (if allocated).
      Actual argument copy is adjusted as well so that each copy can free
      its field independently.
      
      	PR fortran/108923
      
      gcc/fortran/ChangeLog:
      
      	* expr.cc (gfc_free_actual_arglist): Free associated_dummy
      	memory.
      	(gfc_copy_actual_arglist): Make a copy of the associated_dummy
      	field if it is set in the original element.
      24c9edfa
    • Harald Anlauf's avatar
      Fortran: frontend passes do_subscript leaks gmp memory [PR108924] · 45f406c4
      Harald Anlauf authored
      gcc/fortran/ChangeLog:
      
      	PR fortran/108924
      	* frontend-passes.cc (do_subscript): Clear used gmp variable.
      45f406c4
    • Matthias Kretz's avatar
      libstdc++: Fix formatting · b31186e5
      Matthias Kretz authored
      
      Whitespace changes only.
      
      Signed-off-by: default avatarMatthias Kretz <m.kretz@gsi.de>
      
      libstdc++-v3/ChangeLog:
      
      	* include/experimental/bits/simd.h: Line breaks and indenting
      	fixed to follow the libstdc++ standard.
      	* include/experimental/bits/simd_builtin.h: Likewise.
      	* include/experimental/bits/simd_fixed_size.h: Likewise.
      	* include/experimental/bits/simd_neon.h: Likewise.
      	* include/experimental/bits/simd_ppc.h: Likewise.
      	* include/experimental/bits/simd_scalar.h: Likewise.
      	* include/experimental/bits/simd_x86.h: Likewise.
      b31186e5
    • Matthias Kretz's avatar
      libstdc++: Always-inline most of non-cmath fixed_size implementation · e37b0432
      Matthias Kretz authored
      
      For simd, the inlining behavior should be similar to builtin types. (No
      operator on buitin types is ever translated into a function call.)
      Therefore, always_inline is the right choice (i.e. inline on -O0 as
      well).
      
      Signed-off-by: default avatarMatthias Kretz <m.kretz@gsi.de>
      
      libstdc++-v3/ChangeLog:
      
      	PR libstdc++/108030
      	* include/experimental/bits/simd_fixed_size.h
      	(_SimdImplFixedSize::_S_broadcast): Replace inline with
      	_GLIBCXX_SIMD_INTRINSIC.
      	(_SimdImplFixedSize::_S_generate): Likewise.
      	(_SimdImplFixedSize::_S_load): Likewise.
      	(_SimdImplFixedSize::_S_masked_load): Likewise.
      	(_SimdImplFixedSize::_S_store): Likewise.
      	(_SimdImplFixedSize::_S_masked_store): Likewise.
      	(_SimdImplFixedSize::_S_min): Likewise.
      	(_SimdImplFixedSize::_S_max): Likewise.
      	(_SimdImplFixedSize::_S_complement): Likewise.
      	(_SimdImplFixedSize::_S_unary_minus): Likewise.
      	(_SimdImplFixedSize::_S_plus): Likewise.
      	(_SimdImplFixedSize::_S_minus): Likewise.
      	(_SimdImplFixedSize::_S_multiplies): Likewise.
      	(_SimdImplFixedSize::_S_divides): Likewise.
      	(_SimdImplFixedSize::_S_modulus): Likewise.
      	(_SimdImplFixedSize::_S_bit_and): Likewise.
      	(_SimdImplFixedSize::_S_bit_or): Likewise.
      	(_SimdImplFixedSize::_S_bit_xor): Likewise.
      	(_SimdImplFixedSize::_S_bit_shift_left): Likewise.
      	(_SimdImplFixedSize::_S_bit_shift_right): Likewise.
      	(_SimdImplFixedSize::_S_remquo): Add inline keyword (to be
      	explicit about not always-inline, yet).
      	(_SimdImplFixedSize::_S_isinf): Likewise.
      	(_SimdImplFixedSize::_S_isfinite): Likewise.
      	(_SimdImplFixedSize::_S_isnan): Likewise.
      	(_SimdImplFixedSize::_S_isnormal): Likewise.
      	(_SimdImplFixedSize::_S_signbit): Likewise.
      e37b0432
    • Matthias Kretz's avatar
      libstdc++: More efficient masked inc-/decrement implementation · 6ce55180
      Matthias Kretz authored
      
      Signed-off-by: default avatarMatthias Kretz <m.kretz@gsi.de>
      
      libstdc++-v3/ChangeLog:
      
      	PR libstdc++/108856
      	* include/experimental/bits/simd_builtin.h
      	(_SimdImplBuiltin::_S_masked_unary): More efficient
      	implementation of masked inc-/decrement for integers and floats
      	without AVX2.
      	* include/experimental/bits/simd_x86.h
      	(_SimdImplX86::_S_masked_unary): New. Use AVX512 masked subtract
      	builtins for masked inc-/decrement.
      6ce55180
    • Richard Biener's avatar
      Avoid default-initializing auto_vec<T, N> storage, fix vec<vl_embed> · 2dd68cdd
      Richard Biener authored
      The following avoids default-initializing auto_vec storage for
      non-POD T since that's not what the allocated storage fallback
      will do and it's also not expected for existing cases like
      
        auto_vec<std::pair<unsigned, unsigned>, 64> elts;
      
      which exist to optimize the allocation.
      
      It also fixes the array accesses done by vec<vl_embed> to not
      use its own m_vecdata member but instead access the container
      provided storage via pointer arithmetic.
      
      	* vec.h (vec<T, A, vl_embed>::m_vecdata): Remove.
      	(vec<T, A, vl_embed>::m_vecpfx): Align as T to avoid
      	changing alignment of vec<T, A, vl_embed> and simplifying
      	address.
      	(vec<T, A, vl_embed>::address): Compute as this + 1.
      	(vec<T, A, vl_embed>::embedded_size): Use sizeof the
      	vector instead of the offset of the m_vecdata member.
      	(auto_vec<T, N>::m_data): Turn storage into
      	uninitialized unsigned char.
      	(auto_vec<T, N>::auto_vec): Allow allocation of one
      	stack member.  Initialize m_vec in a special way to
      	avoid later stringop overflow diagnostics.
      	* vec.cc (test_auto_alias): New.
      	(vec_cc_tests): Call it.
      2dd68cdd
    • Richard Biener's avatar
      Change vec<,,vl_embed>::m_vecdata refrences into address () · ef22c3e9
      Richard Biener authored
      As preparation to remove m_vecdata in the vl_embed vector this
      changes references to it into calls to address ().
      
      As I was here it also fixes ::contains to avoid repeated bounds
      checking and the same issue in ::lower_bound which also suffers
      from unnecessary copying around values.
      
      	* vec.h (vec<T, A, vl_embed>::lower_bound): Adjust to
      	take a const reference to the object, use address to
      	access data.
      	(vec<T, A, vl_embed>::contains): Use address to access data.
      	(vec<T, A, vl_embed>::operator[]): Use address instead of
      	m_vecdata to access data.
      	(vec<T, A, vl_embed>::iterate): Likewise.
      	(vec<T, A, vl_embed>::copy): Likewise.
      	(vec<T, A, vl_embed>::quick_push): Likewise.
      	(vec<T, A, vl_embed>::pop): Likewise.
      	(vec<T, A, vl_embed>::quick_insert): Likewise.
      	(vec<T, A, vl_embed>::ordered_remove): Likewise.
      	(vec<T, A, vl_embed>::unordered_remove): Likewise.
      	(vec<T, A, vl_embed>::block_remove): Likewise.
      	(vec<T, A, vl_heap>::address): Likewise.
      ef22c3e9
    • Martin Liska's avatar
      asan: adjust module name for global variables · 94c9b1bb
      Martin Liska authored
      As mentioned in the PR, when we use LTO, we wrongly use ltrans output
      file name as a module name of a global variable. That leads to a
      non-reproducible output.
      
      After the suggested change, we emit context name of normal global
      variables. And for artificial variables (like .Lubsan_data3), we use
      aux_base_name (e.g. "./a.ltrans0.ltrans").
      
      	PR sanitizer/108834
      
      gcc/ChangeLog:
      
      	* asan.cc (asan_add_global): Use proper TU name for normal
      	global variables (and aux_base_name for the artificial one).
      
      gcc/testsuite/ChangeLog:
      
      	* c-c++-common/asan/global-overflow-1.c: Test line and column
      	info for a global variable.
      94c9b1bb
    • Alexandre Oliva's avatar
      [PR105224] C++ modules and AAPCS/ARM EABI clash on inline key methods · 3d1d3ece
      Alexandre Oliva authored
      g++.dg/modules/virt-2_a.C fails on arm-eabi and many other arm targets
      that use the AAPCS variant.  ARM is the only target that overrides
      TARGET_CXX_KEY_METHOD_MAY_BE_INLINE.  It's not clear to me which way
      the clash between AAPCS and C++ Modules design should be resolved, but
      currently it favors AAPCS and thus the test fails, so skip it on
      arm_eabi.
      
      
      for  gcc/testsuite/ChangeLog
      
      	PR c++/105224
      	* g++.dg/modules/virt-2_a.C: Skip on arm_eabi.
      3d1d3ece
    • Jonathan Wakely's avatar
      libstdc++: Constrain net::executor constructors · 8520132b
      Jonathan Wakely authored
      The TS says the arguments to these constructors shall meet the Executor
      requirements, so it's undefined if they don't. Constraining on a subset
      of those requirements won't affect valid cases, but prevents the
      majority of invalid cases from trying to instantiate the constructor.
      
      This prevents the non-explicit executor(Executor) constructor being a
      candidate anywhere that a net::executor could be constructed e.g.
      comparing ip::tcp::v4() == ip::udp::v4() would try to convert both
      operands to executor using that constructor, then compare then using
      operator==(const executor&, const executor&).
      
      libstdc++-v3/ChangeLog:
      
      	* include/experimental/executor (executor): Constrain template
      	constructors.
      8520132b
    • Jonathan Wakely's avatar
      libstdc++: Make net::ip::basic_endpoint comparisons constexpr · 97111dcc
      Jonathan Wakely authored
      libstdc++-v3/ChangeLog:
      
      	* include/experimental/internet (basic_endpoint): Add missing
      	constexpr to comparison operators.
      	* testsuite/experimental/net/internet/endpoint/cons.cc: New test.
      97111dcc
    • Jonathan Wakely's avatar
      libstdc++: Fix members of net::ip::network_v4 · 80e9bac2
      Jonathan Wakely authored
      libstdc++-v3/ChangeLog:
      
      	* include/experimental/internet (network_v4::netmask()): Avoid
      	undefined shift.
      	(network_v4::broadcast()): Optimize and fix for targets with
      	uint_least32_t wider than 32 bits.
      	(network_v4::to_string(const Allocator&)): Fix for custom
      	allocators and optimize using to_chars.
      	(operator==(const network_v4&, const network_v4&)): Add missing
      	constexpr.
      	(operator==(const network_v6&, const network_v6&)): Likewise.
      	* testsuite/experimental/net/internet/network/v4/cons.cc: New test.
      	* testsuite/experimental/net/internet/network/v4/members.cc: New test.
      80e9bac2
Loading