[Git][ghc/ghc][wip/backports-9.8] 44 commits: Add aarch64 alpine bindist

Ben Gamari (@bgamari) gitlab at gitlab.haskell.org
Mon Jan 22 03:06:51 UTC 2024



Ben Gamari pushed to branch wip/backports-9.8 at Glasgow Haskell Compiler / GHC


Commits:
da8d2a29 by Matthew Pickering at 2024-01-21T22:06:34-05:00
Add aarch64 alpine bindist

This is dynamically linked and makes creating statically linked
executables more straightforward.

Fixes #23482

(cherry picked from commit 51b57d6587b75020045c1a1edf9eb02990ca63cc)

- - - - -
53b308e9 by sheaf at 2024-01-21T22:06:34-05:00
Combine GREs when combining in mkImportOccEnv

In `GHC.Rename.Names.mkImportOccEnv`, we sometimes discard one import
item in favour of another, as explained in Note [Dealing with imports]
in `GHC.Rename.Names`. However, this can cause us to lose track of
important parent information.

Consider for example #24084:

  module M1 where { class C a where { type T a } }
  module M2 ( module M1 ) where { import M1 }
  module M3 where { import M2 ( C, T ); instance C () where T () = () }

When processing the import list of `M3`, we start off (for reasons that
are not relevant right now) with two `Avail`s attached to `T`, namely
`C(C, T)` and `T(T)`. We combine them in the `combine` function of
`mkImportOccEnv`; as described in Note [Dealing with imports] we discard
`C(C, T)` in favour of `T(T)`. However, in doing so, we **must not**
discard the information want that `C` is the parent of `T`. Indeed,
losing track of this information can cause errors when importing,
as we could get an error of the form

  ‘T’ is not a (visible) associated type of class ‘C’

We fix this by combining the two GREs for `T` using `plusGRE`.

Fixes #24084

(cherry picked from commit ec3c4488f456f6f9bdd28a09f0b1e87fd3782db9)

- - - - -
c4d1edb1 by Cheng Shao at 2024-01-21T22:06:34-05:00
testsuite: increase timeout of ghc-api tests for wasm32

ghc-api tests for wasm32 are more likely to timeout due to the large
wasm module sizes, especially when testing with wasm native tail
calls, given wasmtime's handling of tail call opcodes are suboptimal
at the moment. It makes sense to increase timeout specifically for
these tests on wasm32. This doesn't affect other targets, and for
wasm32 we don't increase timeout for all tests, so not to risk letting
major performance regressions slip through the testsuite.

(cherry picked from commit 07ab5cc10d4ce8db0c3b099d8bd34da66db51b9e)

- - - - -
a2d7130e by Simon Peyton Jones at 2024-01-21T22:06:34-05:00
Fix non-termination bug in equality solver

constraint left-to-right then right to left, forever.

Easily fixed.

(cherry picked from commit 21b76843e9b51cd27be32b8c595f29a784276229)

- - - - -
d9a34b85 by Cheng Shao at 2024-01-21T22:06:34-05:00
compiler: fix eager blackhole symbol in wasm32 NCG

(cherry picked from commit fe50eb3510ca730c4d2fc57778d380fdc493abd8)

- - - - -
a0631c4a by Cheng Shao at 2024-01-21T22:06:34-05:00
testsuite: fix optasm tests for wasm32

(cherry picked from commit af77114815ad9052261898c830171e49fbed5160)

- - - - -
186956a6 by Matthew Pickering at 2024-01-21T22:06:34-05:00
testsuite: Add wasm32 to testsuite arches with NCG

The compiler --info reports that wasm32 compilers have a NCG, so we
should agree with that here.

(cherry picked from commit 1b90735c99f1179328f6dd67dbcc81f964901a19)

- - - - -
2bb6c062 by Josh Meredith at 2024-01-21T22:06:34-05:00
JavaScript: support unicode code points > 2^16 in toJSString using String.fromCodePoint (#23628)

(cherry picked from commit 09a5c6cccf8f1b517bc01e8cc924e151d9cbae49)

- - - - -
7c419b07 by Josh Meredith at 2024-01-21T22:06:34-05:00
JavaScript: update MK_TUP macros to use current tuple constructors (#23659)

(cherry picked from commit b9d5bfe9e76e18c78dbcb67e1c5c33a15a54dcd0)

- - - - -
60f3a468 by Sylvain Henry at 2024-01-21T22:06:34-05:00
JS: testsuite: use req_c predicate instead of js_broken

(cherry picked from commit 41968fd699a285e1a1b43535fda28a61bd1202f1)

- - - - -
e110b68f by Sylvain Henry at 2024-01-21T22:06:34-05:00
JS: implement some file primitives (lstat,rmdir) (#22374)

- Implement lstat and rmdir.
- Implement base_c_s_is* functions (testing a file type)
- Enable passing tests

(cherry picked from commit 74a4dd2ec6e200b11a56b6f82907feb66e94c90b)

- - - - -
6c31021e by Andreas Klebinger at 2024-01-21T22:06:34-05:00
Fix FMA primops generating broken assembly on x86.

`genFMA3Code` assumed that we had to take extra precations to avoid overwriting
the result of `getNonClobberedReg`. One of these special cases caused a bug resulting
in broken assembly.

I believe we don't need to hadle these cases specially at all, which means this MR simply
deletes the special cases to fix the bug.

Fixes #24160

(cherry picked from commit fa576eb8a55db8e216eed3e7ea8807121b3496f5)

- - - - -
c52d657c by Zubin Duggal at 2024-01-21T22:06:34-05:00
driver: Don't lose track of nodes when we fail to resolve cycles

The nodes that take part in a cycle should include both hs-boot and hs files,
but when we fail to resolve a cycle, we were only counting the nodes from the
graph without boot files.

Fixes #24196

(cherry picked from commit 717c9b59ecfb919cba1b8cec6597d0c2fb3ef1a1)

- - - - -
5293edd0 by Sebastian Graf at 2024-01-21T22:06:34-05:00
Cpr: Turn an assertion into a check to deal with some dead code (#23862)

See the new `Note [Dead code may contain type confusions]`.

Fixes #23862.

(cherry picked from commit 57c391c463f26b7025df9b340ad98416cff1d2b2)

- - - - -
0f37a33e by Zubin Duggal at 2024-01-21T22:06:34-05:00
hadrian: set -Wno-deprecations for directory and Win32

The filepath bump to 1.4.200.1 introduces a deprecation warning.

See https://gitlab.haskell.org/ghc/ghc/-/issues/24240
    https://github.com/haskell/filepath/pull/206

(cherry picked from commit 86f652dc9a649e59e643609c287a510a565f5408)

- - - - -
7da42adb by Moritz Angermann at 2024-01-21T22:06:34-05:00
Drop hard Xcode dependency

XCODE_VERSION calls out to `xcodebuild`, which is only available
when having `Xcode` installed. The CommandLineTools are not
sufficient. To install Xcode, you must have an apple id to download
the Xcode.xip from apple.

We do not use xcodebuild anywhere in our build explicilty. At best
it appears to be a proxy for checking the linker or the compiler.
These should rather be done with
```
xcrun ld -version
```
or similar, and not by proxy through Xcode. The CLR should be
sufficient for building software on macOS.

(cherry picked from commit a3ee3b99e6889fd68da75c6ea7a14d101f71da56)

- - - - -
33e6c67c by Sylvain Henry at 2024-01-21T22:06:34-05:00
Fix unusable units and module reexport interaction (#21097)

This commit fixes an issue with ModUnusable introduced in df0f148feae.

In mkUnusableModuleNameProvidersMap we traverse the list of unusable
units and generate ModUnusable origin for all the modules they contain:
exposed modules, hidden modules, and also re-exported modules. To do
this we have a two-level map:

  ModuleName -> Unit:ModuleName (aka Module) -> ModuleOrigin

So for each module name "M" in broken unit "u" we have:
  "M" -> u:M -> ModUnusable reason

However in the case of module reexports we were using the *target*
module as a key. E.g. if "u:M" is a reexport for "X" from unit "o":
   "M" -> o:X -> ModUnusable reason

Case 1: suppose a reexport without module renaming (u:M -> o:M) from
unusable unit u:
   "M" -> o:M -> ModUnusable reason

Here it's claiming that the import of M is unusable because a reexport
from u is unusable. But if unit o isn't unusable we could also have in
the map:
   "M" -> o:M -> ModOrigin ...

Issue: the Semigroup instance of ModuleOrigin doesn't handle the case
(ModUnusable <> ModOrigin)

Case 2: similarly we could have 2 unusable units reexporting the same module
without renaming, say (u:M -> o:M) and (v:M -> o:M) with u and v
unusable. It gives:

  "M" -> o:M -> ModUnusable ... (for u)
  "M" -> o:M -> ModUnusable ... (for v)

Issue: the Semigroup instance of ModuleOrigin doesn't handle the case
(ModUnusable <> ModUnusable).

This led to #21097, #16996, #11050.

To fix this, in this commit we make ModUnusable track whether the module
used as key is a reexport or not (for better error messages) and we use
the re-export module as key. E.g. if "u:M" is a reexport for "o:X" and u
is unusable, we now record:

    "M" -> u:M -> ModUnusable reason reexported=True

So now, we have two cases for a reexport u:M -> o:X:
   - u unusable: "M" -> u:M -> ModUnusable ... reexported=True
   - u usable:   "M" -> o:X -> ModOrigin   ... reexportedFrom=u:M

The second case is indexed with o:X because in this case the Semigroup
instance of ModOrigin is used to combine valid expositions of a module
(directly or via reexports).

Note that module lookup functions select usable modules first (those who
have a ModOrigin value), so it doesn't matter if we add new ModUnusable
entries in the map like this:

  "M" -> {
    u:M -> ModUnusable ... reexported=True
    o:M -> ModOrigin ...
  }

The ModOrigin one will be used. Only if there is no ModOrigin or
ModHidden entry will the ModUnusable error be printed. See T21097 for an
example printing several reasons why an import is unusable.

(cherry picked from commit cee81370cd6ef256f66035e3116878d4cb82e28b)

- - - - -
fa209919 by Moritz Angermann at 2024-01-21T22:06:34-05:00
[PEi386] Mask SYM_TYPE_DUP_DISCARD in makeSymbolExtra

48e391952c17ff7eab10b0b1456e3f2a2af28a9b
introduced `SYM_TYPE_DUP_DISCARD` to the bitfield.

The linker however, failed to mask the `SYM_TYPE_DUP_DISCARD` value.
Thus `== SYM_TYPE_CODE` comparisons easily failed. This lead to us
relocating DATA lookups (GOT) into E8 (call) and E9 (jump) instructions.

(cherry picked from commit 34f06334025521c2440ebedb0237697fbcc3c6de)

- - - - -
7caca374 by Ilias Tsitsimpis at 2024-01-21T22:06:34-05:00
hadrian: Pass -DNOSMP to C compiler when needed

Hadrian passes the -DNOSMP flag to GHC when the target doesn't support
SMP, but doesn't pass it to CC as well, leading to the following
compilation error on mips64el:

| Run Cc (FindCDependencies CDep) Stage1: rts/sm/NonMovingScav.c => _build/stage1/rts/build/c/sm/NonMovingScav.o.d
Command line: /usr/bin/mips64el-linux-gnuabi64-gcc -E -MM -MG -MF _build/stage1/rts/build/c/hooks/FlagDefaults.thr_debug_p_o.d -MT _build/stage1/rts/build/c/hooks/FlagDefaults.o -Irts/include -I_build/stage1/rts/build -I_build/stage1/rts/build/include -Irts/include -x c rts/hooks/FlagDefaults.c -Wall -Wextra -Wstrict-prototypes -Wmissing-prototypes -Wmissing-declarations -Winline -Wpointer-arith -Wmissing-noreturn -Wnested-externs -Wredundant-decls -Wundef -fno-strict-aliasing -DTHREADED_RTS -DDEBUG -fomit-frame-pointer -O2 -g -Irts -I_build/stage1/rts/build -DDEBUG -fno-omit-frame-pointer -g3 -O0
===> Command failed with error code: 1
In file included from rts/include/Stg.h:348,
                 from rts/include/Rts.h:38,
                 from rts/hooks/FlagDefaults.c:8:
rts/include/stg/SMP.h:416:2: error: #error memory barriers unimplemented on this architecture
  416 | #error memory barriers unimplemented on this architecture
      |  ^~~~~
rts/include/stg/SMP.h:440:2: error: #error memory barriers unimplemented on this architecture
  440 | #error memory barriers unimplemented on this architecture
      |  ^~~~~
rts/include/stg/SMP.h:464:2: error: #error memory barriers unimplemented on this architecture
  464 | #error memory barriers unimplemented on this architecture
      |  ^~~~~

The old make system correctly passed this flag to both GHC and CC [1].

Fix this error by passing -DNOSMP to CC as well.

[1] https://gitlab.haskell.org/ghc/ghc/-/blob/00920f176b0235d5bb52a8e054d89a664f8938fe/rts/ghc.mk#L407

Closes #24082

(cherry picked from commit 257c2807587624592813a42e06a05c5fc34cb38c)

- - - - -
78b6cd82 by Moritz Angermann at 2024-01-21T22:06:34-05:00
nativeGen: section flags for .text$foo only

Commit 3ece9856d157c85511d59f9f862ab351bbd9b38b, was supposed to fix
#22834 in !9810.

It does however add "xr" indiscriminatly to .text sections
even if splitSections is disabled. This leads to the assembler saying:

ghc_1.s:7849:0: error:
     Warning: Ignoring changed section attributes for .text
     |
7849 | .section .text,"xr"
     | ^

(cherry picked from commit e99cf237f84db34be0468a893b10394d6b364bce)

- - - - -
2d09102a by Moritz Angermann at 2024-01-21T22:06:34-05:00
[PEi386 linker] Bounds check and null-deref guard

We should resonably be able to expect that we won't exceed the number of
sections if we assume to be dealing with legal object files. We can however
not guarantee that we get some negative values, and while we try to
special case most, we should exclude negative indexing into the sections
array.

We also need to ensure that we do not try to derefences targetSection,
if it is NULL, due to the switch statement.

(cherry picked from commit df81536f2e53abf521a05eb1e482a076f5849c21)

- - - - -
005ed477 by Sylvain Henry at 2024-01-21T22:06:34-05:00
Avoid out-of-bound array access in bigNatIsPowerOf2 (fix #24066)

bigNatIndex# in the `where` clause wasn't guarded by "bigNatIsZero a".

(cherry picked from commit fe0675770b66a9ed393884d96e276b8d116fa2a2)

- - - - -
5b72356c by Sylvain Henry at 2024-01-21T22:06:34-05:00
Bignum: fix right shift of negative BigNat with native backend

(cherry picked from commit cc1625b1ffbdf086b8380bacd35abc8d85861637)

- - - - -
61f94d5a by Sylvain Henry at 2024-01-21T22:06:34-05:00
Rts: expose rtsOutOfBoundsAccess symbol

(cherry picked from commit cbe4400d2690104053ec544cf7d0a9a13ee914ee)

- - - - -
fc6a2751 by Sylvain Henry at 2024-01-21T22:06:34-05:00
Hadrian: enable `-fcheck-prim-bounds` in validate flavour

This allows T24066 to fail when the bug is present.

Otherwise the out-of-bound access isn't detected as it happens in
ghc-bignum which wasn't compiled with the bounds check.

(cherry picked from commit 72c7380cb780933825bc84924908e01ce0495dc4)

- - - - -
01b79988 by Profpatsch at 2024-01-21T22:06:34-05:00
base: Improve String & IsString documentation

(cherry picked from commit d751c583d29460f033fefb45e685fa40fb3487ad)

- - - - -
129b7160 by Ben Gamari at 2024-01-21T22:06:34-05:00
rts/eventlog: Fix off-by-one in assertion

Previously we failed to account for the NULL terminator `postString`
asserted that there is enough room in the buffer for the string.

(cherry picked from commit d0b17576148d336b67c7d65bcf742f83001413cb)

- - - - -
7f52b4ff by Ben Gamari at 2024-01-21T22:06:34-05:00
rts/eventlog: Honor result of ensureRoomForVariableEvent is

Previously we would keep plugging along, even if isn't enough room for
the event.

(cherry picked from commit a10f9b9bc510051a5b47d31238aad1174f7a1966)

- - - - -
ad59f420 by Ben Gamari at 2024-01-21T22:06:34-05:00
rts/eventlog: Avoid truncating event sizes

Previously ensureRoomForVariableEvent would truncate the desired size to
16-bits, resulting in #24197.

Fixes #24197.

(cherry picked from commit 0e0f41c0e3d9c67fc669e975060e88bccdc7d823)

- - - - -
d2117ec7 by Zubin Duggal at 2024-01-21T22:06:34-05:00
driver: Ensure we actually clear the interactive context before reloading

Previously we called discardIC, but immediately after set the session
back to an old HscEnv that still contained the IC

Partially addresses #24107
Fixes #23405

(cherry picked from commit 58d56644c54b221f265b739829e53f9f5e1216d3)

- - - - -
d8afc2bf by Zubin Duggal at 2024-01-21T22:06:34-05:00
driver: Ensure we force the lookup of old build artifacts before returning the build plan

This prevents us from retaining all previous build artifacts in memory until a
recompile finishes, instead only retaining the exact artifacts we need.

Fixes #24118

(cherry picked from commit 8e5745a0cddf36afb680e1e99675279f0065ad7b)

- - - - -
52992cf6 by Zubin Duggal at 2024-01-21T22:06:34-05:00
testsuite: add test for #24118 and #24107

MultiLayerModulesDefsGhci was not able to catch the leak because it uses
:l which discards the previous environment.

Using :r catches both of these leaks
(cherry picked from commit 105c370ce8d2efe0295c3a50a5866f169b59b5e2)

- - - - -
fa8074b2 by Zubin Duggal at 2024-01-21T22:06:35-05:00
compiler: Add some strictness annotations to ImportSpec and related constructors
This prevents us from retaining entire HscEnvs.

Force these ImportSpecs when forcing the GlobalRdrEltX

Adds an NFData instance for Bag

Fixes #24107

(cherry picked from commit e822ff88f7b139191163d0b2dafe43b318b779f9)

- - - - -
1ce5252a by Zubin Duggal at 2024-01-21T22:06:35-05:00
compiler: Force IfGlobalRdrEnv in NFData instance.

(cherry picked from commit 522c12a43b34ad4ca7f3f916fa630d33a4fe6efb)

- - - - -
228f29c9 by Claudio Bley at 2024-01-21T22:06:35-05:00
Only exit ghci in -e mode when :add command fails

Previously, when running `ghci -e ':add Sample.hs'` the process would
exit with exit code 1 if the file exists and could be loaded.

Fixes #24115

(cherry picked from commit d561073727186c7b456c9ef113ccb7fc0df4560e)

- - - - -
0c484431 by mmzk1526 at 2024-01-21T22:06:35-05:00
Use "-V" for alex version check for better backward compatibility
Fixes #24302.
In recent versions of alex, "-v" is used for "--verbose" instead of "-version".

(cherry picked from commit c7be0c680d96ba6209c86e509ab2682e5041a53d)

- - - - -
b6696e74 by Ben Gamari at 2024-01-21T22:06:35-05:00
distrib: Rediscover otool and install_name_tool on Darwin

In the bindist configure script we must rediscover the `otool` and
`install_name_tool`s since they may be different from the build
environment.

Fixes #24211.

(cherry picked from commit 292983c841b4facd5c48fcec9689448d66bcb90e)

- - - - -
2078494b by Zubin Duggal at 2024-01-21T22:06:35-05:00
ci: Ensure we use the correct bindist name for the test artifact when generating
release ghcup metadata

Fixes #24268

(cherry picked from commit 989bf8e53c08eb22de716901b914b3607bc8dd08)

- - - - -
7e2a7824 by Stefan Schulze Frielinghaus at 2024-01-21T22:06:35-05:00
llvmGen: Align objects in the data section

Objects in the data section may be referenced via tagged pointers.
Thus, align those objects to a 4- or 8-byte boundary for 32- or 64-bit
platforms, respectively.  Note, this may need to be reconsidered if
objects with a greater natural alignment requirement are emitted as e.g.
128-bit atomics.

Fixes #24163.

(cherry picked from commit dfe1c3540e4b519b62b862b5966dfec5cae9ece1)

- - - - -
b0d05d50 by Zubin Duggal at 2024-01-21T22:06:35-05:00
docs: document permissibility of -XOverloadedLabels (#24249)

Document the permissibility introduced by
https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0170-unrestricted-overloadedlabels.rst

(cherry picked from commit c247b6befe6a599688bad0a3383424f7ea12d5f2)

- - - - -
5a663583 by Simon Peyton Jones at 2024-01-21T22:06:35-05:00
Take care when simplifying unfoldings

This MR fixes a very subtle bug exposed by #24242.

See Note [Environment for simplLetUnfolding].

I also updated a bunch of Notes on shadowing

(cherry picked from commit d8baa1bdeea1753afc939a20119d3ce555301167)

- - - - -
e441b9bd by Simon Peyton Jones at 2024-01-21T22:06:35-05:00
Make TYPE and CONSTRAINT not-apart

Issue #24279 showed up a bug in the logic in GHC.Core.Unify.unify_ty
which is supposed to make TYPE and CONSTRAINT be not-apart.

Easily fixed.

(cherry picked from commit af6932d6c068361c6ae300d52e72fbe13f8e1f18)

- - - - -
34e2a575 by Zubin Duggal at 2024-01-21T22:06:35-05:00
ci: Fix typo in mk_ghcup_metadata.py

There was a missing colon in the fix to #24268 in 989bf8e53c08eb22de716901b914b3607bc8dd08

(cherry picked from commit 4a39b5ffb85246d0dc491e36a80449afdbcc74cc)

- - - - -
181925d3 by sheaf at 2024-01-21T22:06:35-05:00
Use lookupOccRn_maybe in TH.lookupName

When looking up a value, we want to be able to find both variables
and record fields. So we should not use the lookupSameOccRn_maybe
function, as we can't know ahead of time which record field namespace
a record field with the given textual name will belong to.

Fixes #24293

(cherry picked from commit c5fc7304d56c7a1e0a7bc6e53e23b976772fc10e)

- - - - -


30 changed files:

- .gitlab/gen_ci.hs
- .gitlab/jobs.yaml
- .gitlab/rel_eng/fetch-gitlab-artifacts/fetch_gitlab.py
- .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py
- compiler/GHC/CmmToAsm/Ppr.hs
- compiler/GHC/CmmToAsm/Wasm/FromCmm.hs
- compiler/GHC/CmmToAsm/X86/CodeGen.hs
- compiler/GHC/CmmToAsm/X86/Instr.hs
- compiler/GHC/CmmToLlvm/Data.hs
- compiler/GHC/Core.hs
- compiler/GHC/Core/Opt/CSE.hs
- compiler/GHC/Core/Opt/CprAnal.hs
- compiler/GHC/Core/Opt/FloatIn.hs
- compiler/GHC/Core/Opt/Pipeline.hs
- compiler/GHC/Core/Opt/Simplify/Iteration.hs
- compiler/GHC/Core/Opt/Simplify/Utils.hs
- compiler/GHC/Core/Opt/SpecConstr.hs
- compiler/GHC/Core/Unify.hs
- compiler/GHC/Data/Bag.hs
- compiler/GHC/Driver/Make.hs
- compiler/GHC/Iface/Errors/Ppr.hs
- compiler/GHC/Iface/Errors/Types.hs
- compiler/GHC/Rename/Env.hs
- compiler/GHC/Rename/Names.hs
- compiler/GHC/Stg/CSE.hs
- compiler/GHC/StgToJS/Linker/Utils.hs
- compiler/GHC/Tc/Gen/Splice.hs
- compiler/GHC/Tc/Solver/Equality.hs
- compiler/GHC/Types/Avail.hs
- compiler/GHC/Types/Name/Reader.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/9d424e332165e7c0f7817f28a1ccdd216f5cfd67...181925d3528f174954aca1caf01cca1bb6b04ea3

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/9d424e332165e7c0f7817f28a1ccdd216f5cfd67...181925d3528f174954aca1caf01cca1bb6b04ea3
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20240121/d1100db7/attachment-0001.html>


More information about the ghc-commits mailing list