[Git][ghc/ghc][wip/backports-9.12] 224 commits: haddock: Allow building with GHC 9.12

Ben Gamari (@bgamari) gitlab at gitlab.haskell.org
Thu Jan 23 02:19:37 UTC 2025



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


Commits:
362afd63 by Zubin Duggal at 2024-10-02T18:12:52+05:30
haddock: Allow building with GHC 9.12

Also bump `binaryInterfaceVersion` to 45 to detect binary version changes.

- - - - -
18860aa6 by Andreas Klebinger at 2024-10-13T21:07:34+05:30
SpecConstr: Introduce a separate argument limit for forced specs.

We used to put no limit at all on specializations forced via the SPEC
argument. This isn't always reasonable so we introduce a very high limit
that applies to forced specializations, a flag to control it, and we now
emit a warning if we fail a specialization because we exceed the
warning.

Fixes #25197

(cherry picked from commit da20cac16d0982c982f9d6779dc8174e5184fe15)

- - - - -
0904d0c1 by Andreas Klebinger at 2024-10-13T21:08:23+05:30
ghc-experimental: Expose primops and ghc extensions via GHC.PrimOps

This will be the new place for functions that would have gone into
GHC.Exts in the past but are not stable enough to do so now.

Addresses #25242

(cherry picked from commit 39497eeda74fc7f1e7ea89292de395b16f69cee2)

- - - - -
187b2d5d by Sylvain Henry at 2024-10-13T21:08:36+05:30
RTS: cleanup timerfd file descriptors after a fork (#25280)

When we init a timerfd-based ticker, we should be careful to cleanup the
old file descriptors (e.g. after a fork).

(cherry picked from commit e9dc26907e13eeb73514ff3f70323b40b40ef8ac)

- - - - -
b9b6807e by Matthew Pickering at 2024-10-13T21:08:51+05:30
Bump LLVM upper bound to allow LLVM 19

Also bumps the ci-images commit so that the deb12 images uses LLVM 19
for testing.

-------------------------
Metric Decrease:
    size_hello_artifact_gzip
    size_hello_unicode_gzip
-------------------------

Fixes #25295

(cherry picked from commit 36bbb167f354a2fbc6c4842755f2b1e374e3580e)

- - - - -
d6b8a4fb by ARATA Mizuki at 2024-10-13T21:09:19+05:30
Use bundled llc/opt on Windows (#22438)

(cherry picked from commit 92976985625ffba551f1e1422f5e3a0cbf7beb89)

- - - - -
f9a0dc6d by Andreas Klebinger at 2024-10-13T21:09:36+05:30
Change versionig of ghc-experimental to follow ghc versions.

Just like ghc-internal it will now use the @ProjectVersionForLib@ macro for versioning.
This means for ghc=9.10.1, ghc-experimental's version will be 9.1001.0 and so on.

This fixes #25289

(cherry picked from commit 2293c0b7d709df7be04f596e72c97fd2435c4134)

- - - - -
a85c33c4 by Rodrigo Mesquita at 2024-10-13T21:09:47+05:30
determinism: Deterministic MonadGetUnique LlvmM

Update LlvmM to thread a unique deterministic supply (using UniqDSMT),
and use it in the MonadGetUnique instance.

This makes uniques sampled from LlvmM deterministic, which guarantees
object determinism with -fllvm.

Fixes #25274

(cherry picked from commit 64e876bc0a5dd5d59b47ee3969b52a3bcecb37e6)

- - - - -
623a2534 by Cheng Shao at 2024-10-13T21:09:56+05:30
testsuite: remove accidentally checked in debug print logic

(cherry picked from commit bcb293f216e56c8dfd199f990e8eaa48071ef845)

- - - - -
6bbb7588 by Daniel Díaz at 2024-10-13T21:10:06+05:30
Clarify the meaning of "exactly once" in LinearTypes

Solves documentaion issue #25084.

(cherry picked from commit 535a2117239f0d0e4588c6616fcd8deed725cfc0)

- - - - -
b78e8c5b by Krzysztof Gogolewski at 2024-10-13T21:10:14+05:30
Only allow (a => b) :: Constraint rather than CONSTRAINT rep

Fixes #25243

(cherry picked from commit 92f8939a5fa689dc0143501cfeac0b3b2cd7abd6)

- - - - -
a4328a4c by Teo Camarasu at 2024-10-13T21:11:42+05:30
Add changelog entries for !12479

(cherry picked from commit c9590ba0703d65ecb9d71ac8390c1ae1144bd9d0)

- - - - -
616dfef0 by Matthew Pickering at 2024-10-13T21:12:05+05:30
Fix registerArch for riscv64

The register allocator doesn't support vector registers on riscv64,
therefore advertise as NoVectors.

Fixes #25314

(cherry picked from commit af59749abb723283fa42b51f62a8ac8b345a7f8f)

- - - - -
76549660 by Matthew Pickering at 2024-10-13T21:12:20+05:30
riscv: Avoid using csrr instruction to test for vector registers

The csrr instruction isn't allowed in qemu user-mode, and raises an
illegal instruction error when it is encountered.

Therefore for now, we just hard-code that there is no support for vector
registers since the rest of the compiler doesn't support vector
registers for riscv.

Fixes #25312

(cherry picked from commit a49e66fcf26632b31991384193e9fc0f7d051adc)

- - - - -
30e85658 by Andreas Klebinger at 2024-10-13T21:12:35+05:30
Add support for fp min/max to riscv

Fixes #25313

(cherry picked from commit 115a30e9142b4481de3ba735396e9d0417d46445)

- - - - -
a4b9b1a2 by Sven Tennie at 2024-10-13T21:12:45+05:30
CCallConv test: Align argument types

The C calling convention / standard requires that arguments and their
values are of the same type.

(cherry picked from commit 5fd320da57bb52458bb1e8c14c5311129d88a3a7)

- - - - -
328dedef by sheaf at 2024-10-13T21:12:56+05:30
user's guide: update docs for X86 CPU flags

This commit updates the section of the user's guide pertaining to
X86 feature flags with the following changes:

  - the NCG backend now supports SIMD, so remove all text
    that says the contrary,
  - the LLVM backend does not "automatically detect" features,
    so remove any text that makes that claim.

(cherry picked from commit 9c9c790dbca89722080f47158001ac3920f11606)

- - - - -
7b07c101 by Matthew Pickering at 2024-10-13T21:13:04+05:30
ci: Add nightly & release ubuntu-22.04 jobs

This adds build of bindists on ubuntu-22.04 on nightly and release
pipelines.

We also update ghcup-metadata to provide ubuntu-22.04 bindists on
ubuntu-22.04.

Fixes #25317

(cherry picked from commit 504900755e3297c000a3bcf4f20eaae1f10298f4)

- - - - -
86f3005b by Cheng Shao at 2024-10-13T21:13:52+05:30
driver: bail out when -fllvm is passed to GHC not configured with LLVM

This patch makes GHC bail out with an proper error message when it's
not configured with LLVM but users attempt to pass -fllvm, see #25011
and added comment for details.

Fixes #25011

Co-authored-by: Rodrigo Mesquita <rodrigo.m.mesquita at gmail.com>
(cherry picked from commit 2338a971ce45ce7bc6ba2711e40966ec5ff12359)

- - - - -
abd0d124 by Simon Peyton Jones at 2024-10-13T21:16:19+05:30
Consider Wanteds with rewriters as insoluble

This MR fixes #25325

See GHC.Tc.Types.Constraint, Note [Insoluble Wanteds], especially (IW2)

There is a small change in the error message for T14172, but it looks
entirely acceptable to me.

(cherry picked from commit 083703a12cd34369e7ed2f0efc4a5baee47aedab)

- - - - -
fbbba0f1 by Simon Peyton Jones at 2024-10-13T21:16:27+05:30
Wibbles

(cherry picked from commit 0dfaeb66fb8457e7339abbd44d5c53a81ad8ae3a)

- - - - -
7164dbca by Simon Peyton Jones at 2024-10-13T21:16:33+05:30
Spelling errors

(cherry picked from commit 09d24d828e48c2588a317e6dad711f8673983703)

- - - - -
aa5026c7 by sheaf at 2024-10-13T21:16:57+05:30
LLVM: use sse4.2 instead of sse42

LLVM expects the former instead of the latter since version 3.4.

Fixes #25019

(cherry picked from commit 694489edf35c35b29fbdf09a8e3fdc404469858f)

- - - - -
0b323326 by sheaf at 2024-10-13T21:17:15+05:30
LLVM: make SSE4.2 imply +popcnt

For consistency with the NCG as well as with Clang and GCC, we make
the SSE4.2 feature flag imply +popcnt when using the LLVM backend.

Fixes #25353

(cherry picked from commit 06ae85071b95376bd1eb354f7cc7901aed45b625)

- - - - -
b1f40130 by Ben Gamari at 2024-10-13T21:17:26+05:30
base: Improve documentation of Control.Exception.Backtrace

(cherry picked from commit 0060ece762d7a936daf28195676b6162c30dc845)

- - - - -
95880157 by Ben Gamari at 2024-10-13T21:17:55+05:30
testsuite: Normalise trailing digits from hole fits output

The type variables in the holes fit output from
`abstract_refinement_hole_fits` is quite sensitive to compiler
configuration. Specifically, a slight change in the inlining
behavior of `throw` changes type variable naming in `(>>=)` and a few
others.

Ideally we would make hole fits output more deterministic but in the
meantime we simply normalise this difference away as it not relevant
to the test's goal.

(cherry picked from commit d029f1700effa626ff622700b198ed49ee8b6c19)

- - - - -
f92a8a84 by Ben Gamari at 2024-10-13T21:18:09+05:30
base: Add test for #25066

(cherry picked from commit da5d7d0d8bde06a1c29612fd17b6a579fc523036)

- - - - -
3d0fe159 by Ben Gamari at 2024-10-13T21:22:40+05:30
base: Fix #25066

As noted in #25066, the exception backtrace proposal introduced a rather
subtle performance regression due to simplification producing Core which
the demand analyser concludes may diverge with a precise exception. The
nature of the problem is more completely described in the new Note
[Hiding precise exception signature in throw].

The (rather hacky) solution we use here hides the problematic
optimisation through judicious use of `noinline`. Ultimately however we
will want a more principled solution (e.g. #23847).

Fixes #255066

CLC proposal: https://github.com/haskell/core-libraries-committee/issues/290

Metric Decrease:
    T9872d

(cherry picked from commit eb7ddae1a2b3fb1be1cd635849516a6398327b29)

- - - - -
772b4f59 by Artem Pelenitsyn at 2024-10-13T21:22:40+05:30
Docs: Linear types: link Strict Patterns subsection

Also, fix a bug in RST with missing newline before a listing.

Co-authored-by: Arnaud Spiwack <arnaud at spiwack.net>
(cherry picked from commit 4dd30cba51c7936dc53f0c1d331f88a590f93013)

- - - - -
1418869f by Ben Gamari at 2024-10-13T21:22:40+05:30
base: Add `HasCallStack` constraint to `ioError`

As proposed in core-libraries-committee#275.

(cherry picked from commit 876d6e0e807c074d5c71370aa3c3451bbcb28342)

- - - - -
b5ad81c7 by Matthew Pickering at 2024-10-13T21:22:40+05:30
Fix toException method for ExceptionWithContext

Fixes #25235

(cherry picked from commit 9bfd9fd0730359b4e88e97b08d3654d966a9a11d)

- - - - -
35f20223 by Matthew Pickering at 2024-10-13T21:22:40+05:30
Exception rethrowing

Basic changes:

* Change `catch` function to propagate exceptions using the
  WhileHandling mechanism.
* Introduce `catchNoPropagate`, which does the same as before, but
  passes an exception which can be rethrown.
* Introduce `rethrowIO` combinator, which rethrows an exception with a
  context and doesn't add a new backtrace.
* Introduce `tryWithContext` for a variant of `try` which can rethrow
  the exception with it's original context.
* onException is modified to rethrow the original error rather than
  creating a new callstack.
* Functions which rethrow in GHC.Internal.IO.Handle.FD,
  GHC.Internal.IO.Handle.Internals, GHC.Internal.IO.Handle.Text, and
  GHC.Internal.System.IO.Error are modified to not add a new callstack.

Implements CLC proposal#202 <https://github.com/haskell/core-libraries-committee/issues/202>

(cherry picked from commit ac0040286a8962b728a7cdb3c1be4691db635366)

- - - - -
a2ec22e7 by Rodrigo Mesquita at 2024-10-13T21:26:21+05:30
Add test for #25300

(cherry picked from commit 0e5cff6676426d614739c74bf6a953ef6e9659e6)

- - - - -
d92aa23a by Rodrigo Mesquita at 2024-10-13T21:26:30+05:30
Backport !13302 docs to users guide

(cherry picked from commit e44e448ea8745a04724420edfa6ab4d24252a53f)

- - - - -
d2f2a3b2 by Alan Zimmerman at 2024-10-13T21:26:50+05:30
EPA: Remove unused hsCaseAnnsRest

We never populate it, so remove it.

(cherry picked from commit 4a2f0f1302f5919dfc9c8cbc410fceb19e7309ba)

- - - - -
b2c53e75 by Alan Zimmerman at 2024-10-13T21:29:24+05:30
EPA: Remove [AddEpAnn] from (most of) HsExpr

EPA: introduce EpAnnLam for lambda annotationsi, and remove `glAA`
from `Parser.y`, it is the same as `glR`

EPA: Remove unused annotation from XOpApp

EPA: Use EpToken for XNPat and XNegApp

EPA: specific anns for XExplicitTuple / XTuplePat / sumPatParens.

EPA: Use specific annotation for MultiIf

EPA: Move annotations into FunRhs

EPA: Remove [AddEpAnn] from SigPat and ExprWithTySig

EPA: Remove [AddEpAnn] from ArithSeq

EPA: Remove [AddEpAnn] from HsProc

EPA: Remove [AddEpAnn] from HsStatic

EPA: Remove [AddEpAnn] from BindStmt

EPA: Remove [AddEpAnn] from TransStmt

EPA: Remove [AddEpAnn] from HsTypedSplice

EPA: Remove [AddEpAnn] from HsUntypedSpliceExpr
(cherry picked from commit ef481813719c5f6d9d97b60ffef4617307d24c80)

- - - - -
7564b6a7 by Zubin Duggal at 2024-10-13T21:30:30+05:30
hadrian: Handle broken symlinks properly when creating source dist directories

If we have a broken symlink in the repository, don't try to `need` the symlink
or the target of the symlink. Attempting to do so has `shake` attempt to read the
target to compute its hash, which fails because the target doesn't exist.

(cherry picked from commit 8b402da2738ef6bbc17409f1daac7448e064503a)

- - - - -
39e19e26 by Zubin Duggal at 2024-10-13T21:30:37+05:30
hadrian: exclude cabal.project.symlink.broken from source archives

Cabal 3.14 introduced a broken symlink in its testsuite. Unfortunately,
this broke our source distribution as we use use `tar --dereference` to avoid
issues with symlink compatibility on windows, and `tar --dereference` chokes
when it encounters any broken symlinks.

We can't get rid of `--dereference` because symlinks are generally broken on
windows, so the only option is to exclude this file from source archives.

see also https://github.com/haskell/cabal/issues/10442

(cherry picked from commit 16f97667a859337e8c82636aca7dd7102aa94b55)

- - - - -
c6dd5542 by Zubin Duggal at 2024-10-13T21:30:44+05:30
Bump Cabal submodule to 3.14

Metric Decrease:
    MultiLayerModulesTH_OneShot
Metric Increase:
    haddock.Cabal

(cherry picked from commit f1a2c9fc140baa0aaeda00c02648aa75deb59723)

- - - - -
e78c7ef9 by Zubin Duggal at 2024-10-14T14:20:59+05:30
haddock: oneshot tests can drop files if they share modtimes. Stop this by
including the filename in the key.

Ideally we would use `ghc -M` output to do a proper toposort

Partially addresses #25372

- - - - -
f230e29f by Zubin Duggal at 2024-10-15T04:26:11+05:30
testsuite: normalise some versions in callstacks

- - - - -
b19de476 by Zubin Duggal at 2024-10-15T04:26:11+05:30
testsuite: use -fhide-source-paths to normalise some backpack tests

- - - - -
fbf0889e by Zubin Duggal at 2024-10-15T04:26:11+05:30
testsuite/haddock: strip version identifiers and unit hashes from html tests

- - - - -
473a201c by Zubin Duggal at 2024-10-15T04:26:11+05:30
Bump base bound to 4.21 for GHC 9.12

- - - - -
a79a587e by Zubin Duggal at 2024-10-15T04:26:11+05:30
testsuite: fix normalisation of T9930fail so that it doesn't get tripped up by ghc executable (ARGV[0]) differences

- - - - -
f858875e by Zubin Duggal at 2024-10-15T04:41:35+05:30
testsuite: normalise windows file seperators

- - - - -
24e5761e by Zubin Duggal at 2024-10-15T04:55:36+05:30
testsuite: Mark 25300A as broken on windows

- - - - -
ca2b21c3 by Zubin Duggal at 2024-10-15T04:55:41+05:30
Prepare 9.12.1 alpha

- - - - -
128d1b18 by Alan Zimmerman at 2024-10-30T16:52:57+05:30
EPA: Remove [AddEpAnn] from IE, Pat and some Tys

EPA: Remove [AddEpAnn] from LazyPat

EPA: Remove [AddEpAnn] from RecordCon/RecordUpd/ConPat

EPA: Remove [AddEpAnn] from HsFieldBind

EPA: Remove [AddEpAnn] from PatSynBind

EPA: Remove [AddEpAnn] from IPBind

EPA: Remove [AddEpAnn] from FixSig

EPA: Remove [AddEpAnn] from activation rules

EPA: Remove [AddEpann] from SpecInstSig

EPA: Remove [AddEpAnn] from MinimalSig

EPA: Remove [AddEpAnn] from SCCFunSig

EPA: Remove [AddEpAnn] from CompleteMatchSig

EPA: Remove [AddEpAnn] from AnnSig, as used in PatSynSig, ClassOpSig, TypeSig

EPA: Remove [AddEpAnn] from IEThingAbs

EPA: Remove [AddEpAnn] from IEThingAll / IEThingWith

EPA: Remove [AddEpAnn] from IEModuleContents

EPA: Remove [AddEpAnn] from HsOpTy

EPA: Remove [AddEpAnn] for various binders

EPA: Remove [AddEpAnn] for HsIParamTy
(cherry picked from commit e9cc469954eb19c5c131f9cfc1f0ede6ea9e9848)

- - - - -
bc19b10c by Alan Zimmerman at 2024-10-30T16:53:14+05:30
EPA: Remove [AddEpAnn] commit 3

EPA: Remove [AddEpAnn] from HsDocTy

EPA: Remove [AddEpAnn] from HsBangTy

EPA: Remove [AddEpAnn] from HsExplicitListTy

EPA: Remove [AddEpAnn] from HsExplicitTupleTy

EPA: Remove [AddEpAnn] from HsTypedBracket

EPA: Remove [AddEpAnn] from HsUntypedBracket

EPA: Remove [AddEpAnn] from PatBuilderOpApp

EPA: break out 'EpToken "|"' from ClassDecl anns

EPA: Remove [AddEpAnn] from ClassDecl

EPA: Remove [AddEpAnn] from SynDecl
(cherry picked from commit 5f67db48bdef51905132d990cfaaa0df6532ea99)

- - - - -
96090209 by Cheng Shao at 2024-10-30T16:53:30+05:30
Revert "compiler: start deprecating cmmToRawCmmHook"

This reverts commit 1c064ef1f3e1aa2afc996e962ad53effa99ec5f4. Turns
out the GHC-WPC project does use it to observe Cmm in the pipeline,
see #25363.

(cherry picked from commit 525d451e175c7d6acfa968ce99d8d3fc7a8af0c7)

- - - - -
ba012ad5 by Cheng Shao at 2024-10-30T16:53:44+05:30
rts: fix pointer overflow undefined behavior in bytecode interpreter

This patch fixes an unnoticed undefined behavior in the bytecode
interpreter. It can be caught by building `rts/Interpreter.c` with
`-fsanitize=pointer-overflow`, the warning message is something like:

```
rts/Interpreter.c:1369:13: runtime error: addition of unsigned offset to 0x004200197660 overflowed to 0x004200197658
SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/Interpreter.c:1369:13
rts/Interpreter.c:1265:13: runtime error: addition of unsigned offset to 0x004200197660 overflowed to 0x004200197658
SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/Interpreter.c:1265:13
rts/Interpreter.c:1645:13: runtime error: addition of unsigned offset to 0x0042000b22f8 overflowed to 0x0042000b22f0
SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/Interpreter.c:1645:13
```

Whenever we do something like `SpW(-1)`, the negative argument is
implicitly converted to an unsigned integer type and causes pointer
arithmetic overflow. It happens to be harmless for most targets since
overflowing would wrap the result to desired value, but it's still
coincidental and undefined behavior. Furthermore, it causes real
damage to the wasm backend, given clang-20 will emit invalid wasm code
that crashes at run-time for this kind of C code! (see
https://github.com/llvm/llvm-project/issues/108770)

The fix here is adding some explicit casts to ensure we always use the
signed `ptrdiff_t` type as right hand operand of pointer arithmetic.

(cherry picked from commit 5bcfefd5bb73c18a9bad63d1813968832b696f9a)

- - - - -
cb003daf by Alan Zimmerman at 2024-10-30T16:54:21+05:30
EPA: Remove [AddEpAnn] Commit 4

EPA: Remove [AddEpAnn] from DataDecl

This is quite a big change.
The most important part is moving the annotations into HsDataDefn,
using a specific annotation data type.

It has a knock-on to everything that uses HsDataDefn

EPA: Remove [AddEpAnn] for FunDep

EPA: Remove [AddEpann] from FamilyDecl

EPA: Remove [AddEpAnn] From InjectivityAnn

EPA: Remove [AddEpAnn] from DefaultDecl

EPA: Remove [AddEpAnn] from RuleDecls

EPA: Remove [AddEpAnn] from Warnings
(cherry picked from commit 25edf84977fa15b9911ecbdf614789893ad0e108)

- - - - -
ef8096d9 by Daan Rijks at 2024-10-30T16:55:36+05:30
Expand the haddocks for Control.Category

(cherry picked from commit fbbbd010c5537480deaedc812a235311e13ef767)

- - - - -
57c0c460 by Andrew Lelechenko at 2024-10-30T16:55:46+05:30
documentation: more examples for Control.Category

(cherry picked from commit 076c1a104f55750a49de03694786180bd78eb9b6)

- - - - -
30d12c46 by Cheng Shao at 2024-10-30T16:58:18+05:30
ghci: mitigate host/target word size mismatch in BCOByteArray serialization

This patch mitigates a severe host/target word size mismatch issue in
BCOByteArray serialization logic introduced since !12142, see added
note for detailed explanation.

(cherry picked from commit 90891962ad4d2c781e68062de01e25eea999ae1b)
(cherry picked from commit 860596329a85295277aa21854f4aeae2b755c36f)

- - - - -
d256f923 by Cheng Shao at 2024-10-30T16:58:18+05:30
ghci: use plain malloc for mkConInfoTable on non-TNTC platforms

This patch avoids using mmap() to allocate executable memory for
mkConInfoTable on platforms without tables-next-to-code, see added
comment for explanation.

(cherry picked from commit 839ac52e94f8ecf878e522dba0575466af248267)
(cherry picked from commit 9723a703e3fb53383d4afb49d012f9de43c4235b)

- - - - -
50d5feec by Cheng Shao at 2024-10-30T16:58:18+05:30
ghc-internal: add missing CPPs for wasm

This patch adds some missing CPP guards to ghc-internal, given those
functions are non existent on wasm and would cause linking issues.

(cherry picked from commit a998f69d2de062b7290e78221d55e8c49bf95bbc)
(cherry picked from commit f95de54149e66627079d42cfa0b5b70286a3aae7)

- - - - -
647752c8 by Cheng Shao at 2024-10-30T16:58:18+05:30
rts: rename prelude.js to prelude.mjs

This commit renames prelude.js to prelude.mjs for wasm backend rts
jsbits, and slightly adjusts the jsbits contents. This is for
preparing the implementation of dyld.mjs that contains wasm dynamic
linker logic, which needs to import prelude.mjs as a proper ESM
module.

(cherry picked from commit 71a471e7495f1fbf6b44cfbe4e930c99131c583e)
(cherry picked from commit 1d5a2ff899d9c6905a216b24d5c4fc5d54654166)

- - - - -
3218f014 by Cheng Shao at 2024-10-30T16:58:18+05:30
rts: add __wrapped_freeJSVal

This commit wraps imported freeJSVal in a __wrapped_freeJSVal C
function for wasm backend RTS. In general, wasm imports are only
supposed to be directly called by C; they shouldn't be used as
function pointers, which confuses wasm-ld at link-time when generating
shared libraries.

(cherry picked from commit 33d9db17f31f59ef72d6d8dac033a84c45d3c216)
(cherry picked from commit 151017ca9483b77a83f0bde4eb20af490816e62a)

- - - - -
68e780b5 by Cheng Shao at 2024-10-30T16:58:18+05:30
rts: correct stale link in comment

(cherry picked from commit 0d0a16a81b3875c0e21c0bbe9659edc6312c4846)
(cherry picked from commit dfb3988f3b6a96282cbf4e7edf95f15191dc8c36)

- - - - -
6c08d83c by Cheng Shao at 2024-10-30T16:58:18+05:30
rts: drop interpretBCO support from non-dyn ways on wasm

This commit drops interpretBCO support from non dynamic rts ways on
wasm. The bytecode interpreter is only useful when the RTS linker also
works, and on wasm it only works for dynamic ways anyway. An
additional benefit of dropping interpretBCO is reduction in code size
of linked wasm modules, especially since interpretBCO references
ffi_call which is an auto-generated large function in libffi-wasm and
unused by most user applications.

(cherry picked from commit 90a35c41bb676b5e68212f63b187d2c50439714c)
(cherry picked from commit 21dff5baafd20d2a796896c47c243b2c877e2ad4)

- - - - -
319d4a46 by Cheng Shao at 2024-10-30T16:58:18+05:30
rts: don't build predefined GloblRegs for wasm PIC mode

This commit wraps the predefined GlobalRegs in Wasm.S under a CPP
guard to prevent building for PIC mode. When building dynamic ways of
RTS, the wasm globals that represent STG GlobalRegs will be created
and supplied by dyld.mjs. The current wasm dylink convention doesn't
properly support exporting relocatable wasm globals at all, any wasm
global exported by a .so is assumed to be a GOT.mem entry.

(cherry picked from commit 98a32ec551dd95534c1a8eaccb0f67dbe5f19648)
(cherry picked from commit 70f75b0defd8c1c7941581cd333ca198046c3d15)

- - - - -
1fa9b36b by Cheng Shao at 2024-10-30T16:58:18+05:30
rts: fix conflicting StgRun definitions on wasm

This commit fixes conflicting StgRun definition when building dynamic
ways of RTS for wasm in unregisterised mode.

(cherry picked from commit bef94bde53f07a1b0d7eb16d3d0eb1bd62f5f992)
(cherry picked from commit b9b1a3a95588218b8b823f3315adad0fb7c2ed0c)

- - - - -
92eed1ed by Cheng Shao at 2024-10-30T16:58:18+05:30
hadrian: use targetSupportsRPaths predicate

This commit changes the hostSupportsRPaths predicate to
targetSupportsRPaths and use that to decide whether to pass
RPATH-related link-time options. It's not applied to stage0, we should
just use the default link-time options of stageBoot ghc.

(cherry picked from commit a6a82cdb7162f32a1b73a2a6224d6d9cd208962c)
(cherry picked from commit 7e1f1b0778f581d2b72cfb533c65918b199e6247)

- - - - -
355ac972 by Cheng Shao at 2024-10-30T16:58:18+05:30
hadrian: disable internal-interpreter of ghc library when cross compiling

This commit disable the internal-interpreter flag of ghc library when
cross compiling, only external interpreter works in such cases.

(cherry picked from commit f232c872c6adf4472b5a1c88812c57aa2aa76cbe)
(cherry picked from commit ce1387a065033fc1b85faa314be52f61a9057778)

- - - - -
af73ef6d by Cheng Shao at 2024-10-30T16:58:18+05:30
hadrian: enable internal-interpreter for ghc-bin stage0

This commit enables internal-interpreter flag for ghc-bin even when
compiling stage0, as long as target supports ghci. It enables ghci
functionality for cross targets that support ghci, since cross ghc-bin
is really stage0.

(cherry picked from commit 577c1819ab4eb3369cafdaf24114b74da21ce4b4)
(cherry picked from commit 37b3d585e3f0f5c97a2ab375b8ac4ec9c3c17661)

- - - - -
dcd550ab by Cheng Shao at 2024-10-30T16:58:18+05:30
hadrian: fix CFLAGS for gmp shared objs on wasm

This commit adds -fvisibility=default to CFLAGS of gmp when building
for wasm. This is required to generate the ghc-bignum shared library
without linking errors. Clang defaults to -fvisibility=hidden for wasm
targets, which will cause issues when a symbol is expected to be
exported in a shared library but without explicit visibility attribute
annotation.

(cherry picked from commit c247f2eef9e8450837cbaad1668c6178d094a8fb)
(cherry picked from commit 18e5383329ca4a4bfe3a63f828a4f74f94031550)

- - - - -
3d6f16cb by Cheng Shao at 2024-10-30T16:58:18+05:30
hadrian: re-enable PIC for gmp on wasm

This commit re-enables --with-pic=yes configuration option of gmp when
building for wasm, given we're about to include support for shared
libraries, TH and ghci.

(cherry picked from commit 775410fdfc5d6faf287eecdaae170af9f8a59bb9)
(cherry picked from commit b537609f4f399538ee9e65df4f3442922693d487)

- - - - -
4f4f378a by Cheng Shao at 2024-10-30T16:58:18+05:30
hadrian: add the host_fully_static flavour transformer

This commit adds the host_fully_static flavour transformer to hadrian,
which ensures stage0 is fully statically linked while still permitting
stage1 libdir to contain shared libraries. This is intended to be used
by the wasm backend to build portable linux bindists that contain wasm
shared libraries.

(cherry picked from commit b45080a3e34200767b76faca495f5aea95bb94f5)
(cherry picked from commit c12980bf63c23bb1cbf3e3b3c27a4278a38f97d8)

- - - - -
f69cf2a5 by Cheng Shao at 2024-10-30T16:58:18+05:30
ci: update wasm jobs configuration

This commit bumps ci-image revision to use updated wasm toolchain, and
use host_fully_static instead of fully_static for wasm jobs so to
ensure wasm shared libraries can be properly built.

(cherry picked from commit 5043507ca32e31d14869a0a11dd317529f616fc2)
(cherry picked from commit cbf0b2757b60313f356d701d0857cce44afe8b69)

- - - - -
66c473f2 by Cheng Shao at 2024-10-30T16:58:18+05:30
hadrian/testsuite: implement config.cross logic

This commit implements the config.cross field in the testsuite driver.
It comes from the "cross compiling" ghc info field for both
in-tree/out-of-tree GHC, and is an accurate predicate of whether we're
cross-compiling or not (compared to the precense of target emulator),
and is useful to implement predicates to assert the precense of
internal interpreter (only available on non-cross GHC) for tests that
do require it (e.g. plugins).

(cherry picked from commit 2956a3f7ecd58a6fda81447100404941c0ed837d)
(cherry picked from commit 00fef7bcd722c86b5b65d5189d47b9197b0c05a5)

- - - - -
cd124d94 by Cheng Shao at 2024-10-30T16:58:18+05:30
hadrian/compiler: implement targetRTSLinkerOnlySupportsSharedLibs

This patch implements the targetRTSLinkerOnlySupportsSharedLibs
predicate in hadrian. Its definition in hadrian is the single source
of truth, and the information propagates to ghc settings file, ghc
driver and testsuite driver. It is used in various places to ensure
dynamic dependency is selected when the target RTS linker only
supports loading dynamic code.

(cherry picked from commit 8c74a0eda41255ead134f05598f5da70992a7054)
(cherry picked from commit 9d2e02f911f42ffc6934f189b1d30e95ec47cc49)

- - - - -
2daf1ddd by Cheng Shao at 2024-10-30T16:58:18+05:30
testsuite: don't use host cpu features when testing cross ghc

This patch disables CPU feature detection logic when testing cross
GHC, since those features don't make sense for the target anyway.

(cherry picked from commit b4c3c34090088378870a6705d30665aac6d5c455)
(cherry picked from commit 17386f368a72bba5ed5b3a831e9e9cb744c2f989)

- - - - -
0ab21132 by Cheng Shao at 2024-10-30T16:58:18+05:30
testsuite: implement & use req_plugins predicate

This commit implements req_plugins predicate to indicate that the test
requires plugin functionality. Currently this means cross GHC is
disabled since internal-interpreter doesn't work in cross GHC yet.

(cherry picked from commit 3c21b696abc9acf375307eb91ccc678965487843)
(cherry picked from commit 78600342635c931131ebcabb0fc6584fa44b6bbe)

- - - - -
53187cb7 by Cheng Shao at 2024-10-30T16:58:18+05:30
testsuite: make use of config.interp_force_dyn

This commit takes config.interp_force_dyn into consideration when
setting up TH/ghci way flags.

(cherry picked from commit 93b8af8009a6e174b8d75f766dba2dc4d9aa9119)
(cherry picked from commit 2741e5cf30ae2450b84a53b3b1ac6583ece7de2b)

- - - - -
b4431854 by Cheng Shao at 2024-10-30T16:58:18+05:30
testsuite: bump T17572 timeout

(cherry picked from commit 94673d419a8cdf71d722c93da9860ad8807657e7)
(cherry picked from commit c5d97b796f6167d44501cb2ac69ef01432d38c3e)

- - - - -
980adc2e by Cheng Shao at 2024-10-30T16:58:18+05:30
testsuite: bump T22744 pre_cmd timeout

(cherry picked from commit 2b5efc2d6b0b051ab0458ea0e2a2747b23190827)
(cherry picked from commit e3f42443852f73504b3854737c94a32534b4b3db)

- - - - -
2be13ac4 by Cheng Shao at 2024-10-30T16:58:18+05:30
testsuite: skip terminfo_so for cross ghc

(cherry picked from commit 45102e2ad39d95c06887be036722f793df236a04)
(cherry picked from commit c93876ff7cd01344dc356d66eaf9f80f661660a9)

- - - - -
908d6621 by Cheng Shao at 2024-10-30T16:58:18+05:30
testsuite: fix shared library size tests for cross ghc

This commit fixes shared library size tests (e.g. array_so in
testsuite/tests/perf/size/all.T) when testing cross ghc. Previously,
if shared library file extension of host and target differs, those
tests will fail with framework errors due to not finding the right
files.

(cherry picked from commit 05e40406709fd325476a0fec89488a500094ecec)
(cherry picked from commit d00c26a51a23e4fb7bc7d5c44033b9ee3e4f9149)

- - - - -
bd769e85 by Cheng Shao at 2024-10-30T16:58:18+05:30
testsuite: skip ghc api tests that attempt to spawn processes inside wasm

This commit skips a few ghc api tests on wasm, since they would
attempt to spawn processes inside wasm, which is not supported at all.

(cherry picked from commit fa68f83355ecca1f72f4593a1ed0422fa8fcb6a6)
(cherry picked from commit aa49631399728d6e25625205eedf66d27dc152cb)

- - - - -
1e80537e by Cheng Shao at 2024-10-30T16:58:18+05:30
testsuite: skip T22840 due to broken -dtag-inference-checks on wasm

(cherry picked from commit 1241c04e72107e1648f9aba5e857b48ec3bac96f)
(cherry picked from commit 689c9267e758f3381a098ae5de120d84741fb2eb)

- - - - -
d5e9623d by Cheng Shao at 2024-10-30T16:58:18+05:30
testsuite: ensure $(ghciWayFlags) can be overridden

This commit revises boilerplate.mk in testsuite as well as a few other
places, to ensure the tests that do make use of $(ghciWayFlags) can
receive the right $(ghciWayFlags) from testsuite driver config.

(cherry picked from commit 78c8b90006ac4d0a4de4e72295f8a57de4b9beca)
(cherry picked from commit 6d0cdeedc42d6571e1cd17b862f09e8027baeb75)

- - - - -
b83ceaf4 by Cheng Shao at 2024-10-30T16:58:18+05:30
testsuite: skip rdynamic on wasm

(cherry picked from commit 47989ecc6ddfbe68ba2213c6c2b0d29ed958c330)
(cherry picked from commit e220adb3dd370bae29e1f741bf5b4088d79f2599)

- - - - -
838e9839 by Cheng Shao at 2024-10-30T16:58:18+05:30
testsuite: skip T2615 on wasm

This commit marks T2615 as skip on wasm, given LD_* environment
variables aren't supported on wasm anyway.

(cherry picked from commit fefb4ea1dee945ace173b63c808c593fc167803f)
(cherry picked from commit 39d746e16e235889e39a6a8faefaef34522af89e)

- - - - -
cb100a9c by Cheng Shao at 2024-10-30T16:58:18+05:30
testsuite: mark MultiLayerModulesTH_Make/MultiLayerModulesTH_OneShot as fragile on wasm

(cherry picked from commit 77c797625483be968bb51c1518020895ca5ecb11)
(cherry picked from commit 990addfc8ec7a4f13ed52f435e4f203fe60ff39b)

- - - - -
59a3f31a by Cheng Shao at 2024-10-30T16:58:18+05:30
testsuite: fix T16180 on wasm

This commit fixes T16180 on wasm once TH support is flipped on. The
fix is simply adding right asm code for wasm.

(cherry picked from commit 69bb4745218d2d54c82e33fa529ccf9ba3819fac)
(cherry picked from commit ddff197541d5974bd8067362a6828c2361c69c33)

- - - - -
66a0442d by Cheng Shao at 2024-10-30T16:58:18+05:30
driver: fix -fexternal-interpreter flag for JS backend

Previously, -fexternal-interpreter is broken for JS backend, since GHC
would attempt to launch a non-existent ghc-iserv* executable. This
commit fixes it by adjusting pattern matching order in
setTopSessionDynFlags.

(cherry picked from commit 621c753dee540be65208d1fdcd1728ba9f2b4320)
(cherry picked from commit 4d38dc40506057c5a3449b1841414ea8378a9f42)

- - - - -
cb8d1184 by Cheng Shao at 2024-10-30T16:58:18+05:30
driver: use interpreterDynamic predicate in preloadLib

This commit use the interpreterDynamic predicate in preloadLib to
decide if we should do dynLoadObjs instead of loadObj. Previously we
used hostIsDynamic which was only written with non-cross internal
interpreter in mind.

The testsuite is also adjusted to remove hard-wired -fPIC flag for
cbits (doesn't work in i386 RTS linker in vanilla way, #25260) and
properly pass ghc_th_way_flags to ghc.

(cherry picked from commit 80aa89831c18162ce5591400c41b4cd8f77db0e4)
(cherry picked from commit 1b30373da385f2931f77443e56156089d6218dcc)

- - - - -
752677dc by Cheng Shao at 2024-10-30T16:58:18+05:30
compiler: fix Cmm dynamic CLabels for wasm

This commit fixes the handling of dynamic CLabels for the wasm
backend. Just do the simplest handling: preserve the original CLabel,
both unreg/NCG backends can handle them properly without issue.

(cherry picked from commit 744114618678ed1eac7a699c738ffa3223d1b41a)
(cherry picked from commit 762933824140e5af24ea27c998fdca699b7b8c53)

- - - - -
49fe20a4 by Cheng Shao at 2024-10-30T16:58:18+05:30
driver: add necessary compile-time flags for wasm PIC mode

This commit adds necessary compile-time flags when compiling for wasm
PIC mode, see added comment for detailed explanation.

(cherry picked from commit f6abaf13c527e372edea2d70f9c012da8624e27c)
(cherry picked from commit 9834ac3b086c7489084edef8a81ce1155d739f30)

- - - - -
ccff9bc6 by Cheng Shao at 2024-10-30T16:58:18+05:30
driver: add necessary link-time flags for wasm shared libs

This commit adds necessary link-time flags for wasm shared libs, see
added comments for detailed explanation.

(cherry picked from commit 9745fcfbffb6434bacdec69082739c9e0229c6f2)
(cherry picked from commit 5c94cee60e631e4f5b2458377a1179cc5ad680db)

- - - - -
724a9240 by Cheng Shao at 2024-10-30T16:58:18+05:30
driver: enforce -fno-use-rpaths for wasm

This commit ensures the GHC driver never passes any RPATH-related
link-time flags on wasm, which is not supported at all.

(cherry picked from commit 649aae00c34014fcb64244de59961635563bf06a)
(cherry picked from commit 55d8b48d125fc92c5e7679c0be6202d002f8e3c1)

- - - - -
cec1a8a3 by Cheng Shao at 2024-10-30T16:58:18+05:30
driver: ensure static archives are picked when linking static .wasm modules

This commit ensures static archives are picked when linking .wasm
modules which are supposed to be fully static, even when ghc may be
invoked with -dynamic, see added comment for explanation.

(cherry picked from commit 47baa9044a786ab04b6b68cf008f1254471c3cc1)
(cherry picked from commit 1638d829e8c4c34d1a430799ea6c1a762bad9b38)

- - - - -
46f944be by Cheng Shao at 2024-10-30T16:58:18+05:30
compiler: fix dynamic_too_enable for targets that require dynamic libraries

This commit fixes dynamic_too_enable for targets whose RTS linker can
only load dynamic code.

(cherry picked from commit fc3a55917e9c6c64765f11e0703853b9eed230fe)
(cherry picked from commit ba24a6bd70c06c8e02a29cc4ca5a39488c9edfe5)

- - - - -
01684c08 by Cheng Shao at 2024-10-30T16:58:18+05:30
compiler: fix checkNonStdWay for targets that require dynamic libraries

This commit fixes checkNonStdWay to ensure that for targets whose RTS
linker can only load dynamic code, the dynamic way of object is
selected.

(cherry picked from commit 94ef949ef8b52cebaf8d4a81d7a169e100da2a73)
(cherry picked from commit 38474be061ff58bc725a90b0994669d1477fe24e)

- - - - -
205b8af3 by Cheng Shao at 2024-10-30T16:58:18+05:30
ghc-bin: enforce dynamic way when the target requires so

This commit makes ghc-bin use dynamic way when it is doing interactive
stuff on certain targets whose RTS linker can only handle dynamic
code.

(cherry picked from commit 88e992489e1574b471a55ff9ddace2c81a09ba63)
(cherry picked from commit 50dc1ac1f9ad3ba62558346ef44759794508c863)

- - - - -
fdf17574 by Cheng Shao at 2024-10-30T16:58:18+05:30
hadrian/ghci: add wasm dyld

This commit adds the wasm dynamic linker implementation, as well as
ghci logic to call it and hadrian logic to install it to the correct
location. See the top-level note in utils/jsffi/dyld.mjs for more
details.

(cherry picked from commit 549582eff80da6a8c5b7449755eaa726c208c324)
(cherry picked from commit 5b545e3c9a2ca3bdf82cc24de92c1d977c8fff57)

- - - - -
8e1d564d by Cheng Shao at 2024-10-30T16:58:18+05:30
driver: fix getGccSearchDirectory for wasm target

This commit fixes getGccSearchDirectory logic for wasm target, ensures
the correct search directory containing libc.so etc can be found by
GHC. getGccSearchDirectory is also exported so it can be used
elsewhere to obtain the wasi-sdk libdir and pass to the dyld script.

(cherry picked from commit b562e3a6fab87422f40997f84b11a05505df2fcb)
(cherry picked from commit d3510168869357f78527df9cc0fa0197c8c2016c)

- - - - -
e7d3bf92 by Cheng Shao at 2024-10-30T16:58:18+05:30
driver: add wasm backend iserv logic

This commit adds wasm backend iserv logic to the driver, see added
comments for explanation.

(cherry picked from commit 2d6107dc0e461f6d339ea14712b6f0cb9a619680)
(cherry picked from commit c07205fc70e17ffb228ca17f0eb239f2c858fe94)

- - - - -
c20a5175 by Cheng Shao at 2024-10-30T16:58:18+05:30
compiler: add PIC support to wasm backend NCG

This commit adds support for generating PIC to the wasm backend NCG.

(cherry picked from commit 61f5baa5bd6e8d0daa20af4dc7c3213a48f99019)
(cherry picked from commit 9f8b78240c438fd8c32727f8cbce3ee644d517be)

- - - - -
7608bc46 by Cheng Shao at 2024-10-30T16:58:18+05:30
hadrian/compiler: flip on support for shared libs & ghci for wasm

This commit flips on the support for shared libs and ghci for the wasm
target, given all required support logic has been added in previous
commits.

(cherry picked from commit 652e72394b715abc931b1104a4b683bb16909695)
(cherry picked from commit e11dc80550084af2ea8aeba96e8a2a8a67468c03)

- - - - -
07832d18 by Cheng Shao at 2024-10-30T16:58:19+05:30
testsuite: flip on support for shared libs, TH & ghci for wasm

This commit flips on support for shared libs, TH & ghci for wasm in
the testsuite, given support has been landed in previous commits.

(cherry picked from commit 74a1f6818d1592ebceab8e0fbb6be1973f38fe78)
(cherry picked from commit 2e63876a44236bc67af1aa0ed71db0acf6ac04a3)

- - - - -
89adaa88 by Luite Stegeman at 2024-10-30T16:58:53+05:30
Interpreter: Add locking for communication with external interpreter

This adds locking to communication with the external interpreter
to prevent concurrent tasks interfering with each other. This
fixes Template Haskell with the external interpreter in parallel (-j)
builds.

Fixes #25083

(cherry picked from commit d5f420450e86cedca819ca401b184917c6478c1a)

- - - - -
35922587 by Alan Zimmerman at 2024-10-30T16:59:07+05:30
EPA: Remove [AddEpAnn] Commit 5

EPA: Remove [AddEpAnn] from AnnPragma

EPA: Remove [AddEpAnn] From ForeignDecl

EPA: Remove [AddEpAnn] from RoleAnnotDecl

EPA: Remove [AddEpAnn] from StandaloneKindSig

EPA: Remove [AddEpAnn] From HsDeriving

EPA: Remove [AddEpAnn] from ConDeclField

EPA: Remove [AddEpAnn] from ConDeclGADT

EPA: Remove [AddEpAnn] from ConDeclH98

EPA: Remove [AddEpAnn] from ClsInstDecl
(cherry picked from commit 7f61ed4e6f3b4d5933fa699ec2fc9dbab8052f7e)

- - - - -
744fda1b by Daneel Yaitskov at 2024-10-30T16:59:45+05:30
base: speed up traceEventIO and friends when eventlogging is turned off #17949

Check the RTS flag before doing any work with the given lazy string.

Fix #17949

Co-authored-by: Michael Peyton Jones <me at michaelpj.com>
Co-authored-by: Sylvain Henry <sylvain at haskus.fr>
Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com>
(cherry picked from commit a04959b8964c8d09897cfae1fd7b06ac53ebee95)

- - - - -
6509bb40 by Andrzej Rybczak at 2024-10-30T17:00:07+05:30
Adjust catches to properly rethrow exceptions

https://gitlab.haskell.org/ghc/ghc/-/merge_requests/13302 implemented exception
rethrowing proposal, but it didn't adjust `catches`. This fixes it.

(cherry picked from commit 148059fea534aced44649c739cd0fad4c25a99f0)

- - - - -
db954955 by Cheng Shao at 2024-10-30T17:00:18+05:30
hadrian: fix bindist executable wrapper logic for cross targets

This commit fixes an oversight of hadrian wrapper generation logic:
when doing cross compilation, `wrapper` is called on executable names
with cross prefix, therefore we must use `isSuffixOf` when matching to
take the cross prefix into account. Also add missing cross prefix to
ghci wrapper content and fix hsc2hs wrapper logic.

(cherry picked from commit edc02197b95488e8752c988e0e92ed6253c04b8c)

- - - - -
508eb2db by Rodrigo Mesquita at 2024-10-30T17:00:58+05:30
determinism: Interface re-export list det

In 'DocStructureItem' we want to make sure the 'Avails' are sorted, for
interface file determinism. This commit introduces 'DetOrdAvails', a
newtype that should only be constructed by sorting Avails with
'sortAvails' unless the avails are known to be deterministically
ordered. This newtype is used by 'DocStructureItem' where 'Avails' was
previously used to ensure the list of avails is deterministically sorted
by construction.

Note: Even though we order the constructors and avails in the interface
file, the order of constructors in the haddock output is still
determined from the order of declaration in the source. This was also
true before, when the list of constructors in the interface file <docs>
section was non-deterministic. Some haddock tests such as
"ConstructorArgs" observe this (check the order of constructors in
out/ConstructorArgs.html vs src/ConstructorArgs.hs vs its interface file)

The updated tests are caused by haddock corners where the order in the
source is not preserved (and was non-deterministic before this PR):
    * Module header in the latex backend
    * Re-export of pattern synonyms associated to a datatype (#25342)

Fixes #25304

(cherry picked from commit b3f7fb80781bac756efdd7fdde836bf4742a75fc)

- - - - -
16cb5517 by Rodrigo Mesquita at 2024-10-30T17:00:58+05:30
Revert "ci: Allow abi-test to fail."

After #25304, the abi-test with interface and object determinism
succeeds.

This reverts commit 7b37afc9f3e79559055488998ee73187886a0e00.

(cherry picked from commit e39c8c993c1da534c5893ca418d1fa4cbb9e0a0a)

- - - - -
678794cd by Alan Zimmerman at 2024-10-30T17:01:12+05:30
EPA: reduce [AddEpann] in AnnList

Remove it from the `al_rest` field, and make `AnnList` parameterized
on a type to be used in `al_rest`, for the various use cases.

(cherry picked from commit 7b1b0c6deab87bfc4d2b4ddfda40ed735c28cd53)

- - - - -
e66de62b by Rodrigo Mesquita at 2024-10-30T17:01:25+05:30
Fix -fobject-determinism flag definition

The flag should be defined as an fflag to make sure the
-fno-object-determinism flag is also an available option.

Fixes #25397

(cherry picked from commit 4a00731eda964ec551f920b0319b24db2073687c)

- - - - -
f082e86e by Simon Peyton Jones at 2024-10-30T17:01:36+05:30
Fix optimisation of InstCo

It turned out (#25387) that the fix to #15725 was not quite right:

  commit 48efbc04bd45d806c52376641e1a7ed7278d1ec7
  Date:   Mon Oct 15 10:25:02 2018 +0200

    Fix #15725 with an extra Sym

Optimising InstCo is quite subtle, and the invariants surrounding
the LiftingContext in the coercion optimiser were not stated explicitly.

This patch refactors the InstCo optimisation, and documents these
invariants.  See
  * Note [Optimising InstCo]
  * Note [The LiftingContext in optCoercion]

I also did some refactoring of course:

* Instead of a Bool swap-flag, I am not using GHC.Types.Basic.SwapFlag

* I added some invariant-checking the coercion-construction functions
  in GHC.Core.Coercion.Opt.  (Sadly these invariants don't hold during
  typechecking, becuase the types are un-zonked, so I can't put these
  checks in GHC.Core.Coercion.)

(cherry picked from commit 23ddcc0102b3b0c31829a8f67003f4f00fb52f9a)

- - - - -
da4402b0 by Cheng Shao at 2024-10-30T17:02:27+05:30
testsuite: add T25414 test case marked as broken

This commit adds T25414 test case to demonstrate #25414. It is marked
as broken and will be fixed by the next commit.

(cherry picked from commit b1eed26f10645e8d918402b7fc29b07e0b294757)

- - - - -
d5390862 by Hassan Al-Awwadi at 2024-10-31T17:13:29+05:30
Put RdrName in the foExt field of FieldOcc

The main purpose of this commit is to rip RdrName out of FieldOcc, in
accordance with #21592, and as a side note it has simplified the method
we use to deal with ambiguity somewhat.

To do the first, we make FieldOccs store (LIdP p) instead of always
storing Located RdrName, and moved the readername to the extension
points where necessary.

For the second, well, we just turn an ambiguous RdrName into a unbound
Name through mkUnboundName. Later during disambiguateRecordBinds of the
type checking phase, we will try and do type-directed disambiguation based
on the rdrName field (for now), so this hack works out fine.

See Note [Ambiguous FieldOcc in record updates] for more details.

There are two additional minor changes in this commit:
*  The HsRecSel constructor of HsExpr has been moved to the extension
constuctors, since its really GHC specific.
*  HsProjection no longer has a Located DotFieldOcc as a field, but just a
regular DotFieldOcc, since DotFieldOcc already wraps a located
FieldLabelString

co-authored by: @Jade       <Jade512 at proton.me>
                @alt-romes  <rodrigo.m.mesquita at gmail.com>

(cherry picked from commit 1587cccfe7c3c1db3ccc48437b47ccb6ae215701)

- - - - -
c580b505 by Cheng Shao at 2024-10-31T17:13:29+05:30
driver: fix foreign stub handling logic in hscParsedDecls

This patch fixes foreign stub handling logic in `hscParsedDecls`.
Previously foreign stubs were simply ignored here, so any feature that
involve foreign stubs would not work in ghci (e.g. CApiFFI). The patch
reuses `generateByteCode` logic and eliminates a large chunk of
duplicate logic that implements Core to bytecode generation pipeline
here. Fixes #25414.

(cherry picked from commit e70009bc5b388ed02db12ee7a99bca0e4c283c87)

- - - - -
7202e2ac by Andrew Lelechenko at 2024-10-31T17:13:29+05:30
hadrian: allow -Wunused-imports for text package

(cherry picked from commit 90746a591919fc51a0ec9dec58d8f1c8397040e3)

- - - - -
4595620a by Andrew Lelechenko at 2024-10-31T17:13:29+05:30
Bump text submodule to 2.1.2

(cherry picked from commit 853050c386ff8634b950204edf4c7f8d973f9a89)

- - - - -
ccd4f869 by Zubin Duggal at 2024-10-31T17:13:29+05:30
configure: Set release version to 9.12.0 instead of 9.12.

This means our alphas will be properly named.

- - - - -
ec2f40b4 by Zubin Duggal at 2024-10-31T17:13:29+05:30
Bump binary submodule to 0.8.9.2

(cherry picked from commit 7199869a52ab45e8856658248bf807954d58cc20)

- - - - -
d2a10e25 by Ben Gamari at 2024-10-31T17:13:29+05:30
Bump process submodule to v1.6.25.0

(cherry picked from commit 18f532f3ed021fff9529f50da2006b8a8d8b1df7)

- - - - -
c0eb35df by Zubin Duggal at 2024-10-31T17:13:29+05:30
testsuite: normalise execvp vs exec differences in process tests

Fixes #25431

(cherry picked from commit a23d8e73166725b699af88a36e97c63b2a0ede25)

- - - - -
8de7406f by Zubin Duggal at 2024-11-12T13:42:19+05:30
testsuite: allow metric increase for TcPlugin_RewritePerf
this is an empty commit to allow this backports batch to be merged.

Metric Increase:
    TcPlugin_RewritePerf

- - - - -
b1994328 by Alan Zimmerman at 2024-11-14T16:17:28+05:30
EPA: Remove AddEpann commit 7

EPA: Remove [AddEpAnn] from HYPHEN in Parser.y

The return value is never used, as it is part of the backpack
configuration parsing.

EPA: Remove last [AddEpAnn] usages

Remove residual usage in GHC. It is still used
- In haddock TTG extension point definitions (to be removed)
- Some check-exact residual, to be removed
- Comments around DisambECP in PostProcess

EPA: Clean up [AddEpAnn] from check-exact

There is one left, to be cleaned up when we remove AddEpann itself

EPA: Remove [AddEpAnn] from haddock

The TTG extension points need a value, it is not critical what that
value is, in most cases.

EPA: Remove AddEpAnn from HsRuleAnn

EPA: Remove AddEpAnn from HsCmdArrApp
(cherry picked from commit dbc77ce804c0f410f3f2894a158d0ee899ce64f5)

- - - - -
210b59c4 by Alan Zimmerman at 2024-11-14T16:17:37+05:30
EPA: Remove AddEpAnn Commit 8/final

EPA: Remove AddEpAnn from AnnList

EPA: Remove AddEpAnn from GrhsAnn

This is the last actual use

EPA: Remove NameAdornment from NameAnn

Also rework AnnContext to use EpToken, and AnnParen

EPA: Remove AddEpAnn.  Final removal

There are now none left, except for in a large note/comment in
PostProcess, describing the historical transition to the
disambiguation infrastructure

(cherry picked from commit 8a6691c3a947a21c7dcc9772d6cc396894c4756f)

- - - - -
c43414d2 by Alan Zimmerman at 2024-11-14T16:17:49+05:30
EPA: Remove AnnKeywordId.

This was used as part of AddEpAnn, and is no longer needed.

Also remove all the haddock comments about which of are attached to
the various parts of the AST.  This is now clearly captured in the
appropriate TTG extension points, and the `ExactPrint.hs` file.

(cherry picked from commit d5e7990ca9637ebee2293b22815fa0c393231baf)

- - - - -
43dd7718 by Alan Zimmerman at 2024-11-14T16:18:00+05:30
EPA: use explicit vertical bar token for ExplicitSum / SumPat

(cherry picked from commit f859d61c4832b16ae3b4dd14aad5cb41b0051de3)

- - - - -
aa59a1ef by Alan Zimmerman at 2024-11-14T16:21:51+05:30
EPA: Bring in last EpToken usages

For import declarations, NameAnnCommas and NPlusKPat.

And remove anchor, it is the same as epaLocationRealSrcSpan.

(cherry picked from commit 0bc94360908011167284ee4c283c343350cbba78)

- - - - -
788ae992 by Alan Zimmerman at 2024-11-14T19:03:38+05:30
EPA: Capture location of '_' for wild card type binder

And keep track of promotion status in HsExplicitTupleTy, so the
round-trip ppr test works for it.

Updates Haddock output too, using the PromotionFlag in
HsExplicitTupleTy.

Closes #25454

(cherry picked from commit 9ad9ac63abed33aa48d4df40142d2809bdfd1ff0)

- - - - -
344bb0f3 by Alan Zimmerman at 2024-11-14T19:04:35+05:30
EPA: Correctly capture leading semis in decl list

Closes #25467

(cherry picked from commit 0614abef967c2ee9fb83955f18460715160a557a)

- - - - -
8662d966 by ur4t at 2024-11-14T19:05:02+05:30
GHCi: fix improper location of ghci_history file

Fixes #24266

(cherry picked from commit 6f0a62db5dc79640433c61e83ea1427665304869)

- - - - -
014126ba by Rodrigo Mesquita at 2024-11-14T19:05:43+05:30
Deprecation for WarnCompatUnqualifiedImports

Fixes #25330

(cherry picked from commit 68e2da5a9ed2f0221b0b17a19032d909a1ea1037)

- - - - -
3b7dc559 by Andreas Klebinger at 2024-11-14T19:06:05+05:30
Compile T25062 simd tests even if we can't run them.

Helps avoid them being utterly broken.

Fixes #25341

(cherry picked from commit 1c21e7d4358162342b707f20ae2765ad02affdf3)

- - - - -
31a75a91 by Ben Gamari at 2024-11-14T19:06:21+05:30
rts/Disassembler: Fix encoding of BRK_FUN instruction

The offset of the CC field was not updated after the encoding change in
b85b11994e0130ff2401dd4bbdf52330e0bcf776. Fix this.

Fixes #25374.

(cherry picked from commit 721ac00d63216e5e6512baba09b6ebb3cc456ebf)

- - - - -
eccd1ef0 by Ben Gamari at 2024-11-14T19:06:44+05:30
configure: Check version number validity

Here we verify the previously informal invariant that stable release
version numbers must have three components, preventing costly failed
releases.

Specifically, the check fails in the following scenarios:

 * `version=9.13` while `RELEASE=YES` since this would imply a
   release made from an unstable branch
 * `version=9.13.0` since unstable versions should only have two
   components
 * `version=9.12` since this has the wrong number of version components
   for a stable branch

Fixes #25390.

(cherry picked from commit c02add17f04c0521f0cb97b4c8511b47f4b639d7)

- - - - -
9d431ca7 by Teo Camarasu at 2024-11-14T19:07:03+05:30
docs: link to #14474 in the template-haskell docs

(cherry picked from commit 747fd3224f9832a97367aaf7e6085a9b0a26fba9)

- - - - -
29923e5f by Peter Trommler at 2024-11-14T19:07:33+05:30
PPC NCG: Implement fmin and fmax

(cherry picked from commit fdd9f62ad3deb64dabef438032a1e8c89c98cd99)

- - - - -
c3fb73d2 by Sebastian Graf at 2024-11-14T19:07:47+05:30
DmdAnal: Make `prompt#` lazy (#25439)

This applies the same treatment to `prompt#` as for `catch#`.
See `Note [Strictness for mask/unmask/catch/prompt]`.

Fixes #25439.

(cherry picked from commit 00d58ae18a7ce8db6b2d57261a08ba8c1c2549b5)

- - - - -
53d2a948 by Zubin Duggal at 2024-11-14T19:08:09+05:30
release: copy zip files into the correct directory

Fixes #25446

(cherry picked from commit 346e4cd1903b2cbcc9bb7c39652666c513eb2a59)

- - - - -
c29445eb by Zubin Duggal at 2024-11-14T19:08:16+05:30
release: Sign .gz bindists too

Fixes #25447

(cherry picked from commit bbdbe2254df1bfc9157cfb409afc93f8157712cd)

- - - - -
f5b5d1dc by Zubin Duggal at 2024-11-14T19:11:16+05:30
Bump exceptions submodule to 0.10.9

- - - - -
ba786681 by Zubin Duggal at 2024-11-14T19:56:41+05:30
Bump file-io submodule to 0.1.4

- - - - -
3a7ffdbb by Zubin Duggal at 2024-11-14T19:56:41+05:30
bump os-string submodule to 2.0.6

- - - - -
53b46fd4 by Zubin Duggal at 2024-11-14T19:56:41+05:30
bump transformers submodule to 0.6.1.2

- - - - -
27dc2664 by Zubin Duggal at 2024-11-14T19:56:41+05:30
Bump directory submodule to v1.3.9.0

- - - - -
80df8808 by Zubin Duggal at 2024-11-14T19:56:41+05:30
Bump Win32 submodule to v2.14.1.0

- - - - -
29bfae2c by Zubin Duggal at 2024-11-14T19:56:41+05:30
Bump filepath submodule to 1.5.3.0

- - - - -
97b0dff2 by Zubin Duggal at 2024-11-14T23:00:10+05:30
Bump file-io submodule to avoid usage of QuasiQuotes

- - - - -
a1f56d6d by Zubin Duggal at 2024-11-26T16:36:33+05:30
Bump unix submodule to 2.8.6.0

- - - - -
348179be by Matthew Pickering at 2024-11-26T16:36:56+05:30
Exception rethrowing

Basic changes:

* Change `catch` function to propagate exceptions using the
  WhileHandling mechanism.
* Introduce `catchNoPropagate`, which does the same as before, but
  passes an exception which can be rethrown.
* Introduce `rethrowIO` combinator, which rethrows an exception with a
  context and doesn't add a new backtrace.
* Introduce `tryWithContext` for a variant of `try` which can rethrow
  the exception with it's original context.
* onException is modified to rethrow the original error rather than
  creating a new callstack.
* Functions which rethrow in GHC.Internal.IO.Handle.FD,
  GHC.Internal.IO.Handle.Internals, GHC.Internal.IO.Handle.Text, and
  GHC.Internal.System.IO.Error are modified to not add a new callstack.

Implements CLC proposal#202 <https://github.com/haskell/core-libraries-committee/issues/202>

(cherry picked from commit 6e68b1177ea6fde381060268c377f67f6097877a)

- - - - -
9d5f116c by Rodrigo Mesquita at 2024-11-26T16:38:55+05:30
exceptions: Improve the message layout as per #285

This commit fixes the layout of the additional information included when
displaying an exception, namely the type of the exception.

It also fixes the default handler's heading message to work well
together with the improved display message of SomeException.

CLC proposal#285

(cherry picked from commit a4e0d23596b45f27f5faad2363c77698abe900b1)

- - - - -
39c9228c by Rodrigo Mesquita at 2024-11-26T16:39:07+05:30
Display type and callstack of exception on handler

This commit changes the Exception instance of SomeException to *simply*
display the underlying exception in `displayException`. The augmented
exception message that included the type and backtrace of the exception
are now only printed on a call to `displayExceptionWithInfo`.

At a surface level, existing programs should behave the same since the
`uncaughtExceptionHandler`, which is responsible for printing out uncaught
exceptions to the user, will use `displayExceptionWithInfo` by default.

However, unlike the instance's `displayException` method, the
`uncaughtExceptionHandler` can be overriden with
`setUncaughtExceptionHandler`. This makes the extra information opt-in
without fixing it the instance, which can be valuable if your program
wants to display uncaught exceptions to users in a user-facing way
(ie without backtraces).

This is what was originally agreed for CLC#231 or CLC#261 with regard to
the type of the exception information.

The call stack also becoming part of the default handler rather than the
Exception instance is an ammendment to CLC#164.

Discussion of the ammendment is part of CLC#285.

(cherry picked from commit 284ffab334bcda838865ff4804bc04f9082d81b3)

- - - - -
39ecdcb9 by Rodrigo Mesquita at 2024-11-26T16:39:37+05:30
Remove redundant CallStack from exceptions

Before the exception backtraces proposal was implemented, ErrorCall
accumulated its own callstack via HasCallStack constraints, but
ExceptionContext is now accumulated automatically.

The original ErrorCall mechanism is now redundant and we get a duplicate
CallStack

Updates Cabal submodule to fix their usage of ErrorCallWithLocation to ErrorCall

CLC proposal#285

Fixes #25283

(cherry picked from commit 36cddd2ce1a3bc62ea8a1307d8bc6006d54109cf)

- - - - -
5f7a6678 by Rodrigo Mesquita at 2024-11-26T16:39:48+05:30
Freeze call stack in error throwing functions

CLC proposal#285

(cherry picked from commit 7a74330bf55a85573ed02298b92b7b3fc06f2fed)

- - - - -
1848cfb0 by Rodrigo Mesquita at 2024-11-26T16:39:56+05:30
De-duplicate displayContext and displayExceptionContext

The former was unused except for one module where it was essentially
re-defining displayExceptionContext.

Moreover, this commit extends the fix from
bfe600f5bb3ecd2c8fa71c536c63d3c46984e3f8 to displayExceptionContext too,
which was missing.

(cherry picked from commit 3abf31a45ddbc80901baefdc6325fc3351c5deec)

- - - - -
900aa787 by Rodrigo Mesquita at 2024-11-26T16:40:05+05:30
Re-export NoBacktrace from Control.Exception

This was originally proposed and accepted in section
    "2.7   Capturing Backtraces on Exceptions"
of the CLC proposal for exception backtraces.

However, the implementation missed this re-export, which this commit now
fixes.

(cherry picked from commit c0d783f8a94ee6b72ff3c20e0a974cd09edd96ff)

- - - - -
b7337c54 by Rodrigo Mesquita at 2024-11-26T16:40:12+05:30
Fix exception backtraces from GHCi

When running the program with `runhaskell`/`runghc` the backtrace should
match the backtrace one would get by compiling and running the program.
But currently, an exception thrown in a program interpreted with
`runhaskell` will:

    * Not include the original exception backtrace at all
    * Include the backtrace from the internal GHCi/ghc rethrowing of the
      original exception

This commit fixes this divergence by not annotating the ghc(i) backtrace
(with NoBacktrace) and making sure that the backtrace of the original
exception is serialized across the boundary and rethrown with the
appropriate context.

Fixes #25116

The !13301 MR (not this commit in particular) improves performance of
MultiLayerModules. Unfortunately, T3294 regresses on aarch64-linux-deb12
by 1% allocations. Since this patch must be merged for 9.12 ASAP, we
will not be able to investigate the slight regression on this platform
in time.

-------------------------
Metric Decrease:
    MultiLayerModulesRecomp
    MultiLayerModulesTH_OneShot
Metric Increase:
    T3294
-------------------------

(cherry picked from commit 802b5c3e118dad9fcfbe61a3fa4d7bf4592356a8)

- - - - -
e92bfcb9 by Rodrigo Mesquita at 2024-11-26T16:40:25+05:30
base: Add to changelog.md CLC #285

(cherry picked from commit 3e89eb65895b4ea390d0fd2cd4f8bc688a602e34)

- - - - -
ab5867a9 by Zubin Duggal at 2024-11-26T16:42:52+05:30
Bump array and stm submodules for exception output changes

- - - - -
7688daae by Rodrigo Mesquita at 2024-11-26T16:43:13+05:30
Re-introduce ErrorCallWithLocation with a deprecation pragma

With the removal of the duplicate backtrace, part of CLC proposal #285,
the constructor `ErrorCallWithLocation` was removed from base.

This commit re-introduces it with a deprecation.

(cherry picked from commit d1172e20f29e6fbf53fa95726492bdb998c52582)

- - - - -
df632282 by Brandon Chinn at 2024-11-26T16:43:29+05:30
Fix CRLF in multiline strings (#25375)

(cherry picked from commit 7bd407a67cd7810d3ff1e6d18885555175383a35)

- - - - -
5654b8ba by Matthew Pickering at 2024-11-26T16:43:57+05:30
ghc-internal: Update to Unicode 16

This patch updates the automatically generated code for querying unicode
properties to unicode 16.

Fixes #25402

(cherry picked from commit bfe64df85683d63ccfa438fed0999193b703d48c)

- - - - -
0117fed6 by ARATA Mizuki at 2024-11-26T16:44:12+05:30
x86 NCG SIMD: Lower packFloatX4#, insertFloatX4# and broadcastFloatX4# to SSE1 instructions

Fixes #25441

Co-authored-by: sheaf <sam.derbyshire at gmail.com>
(cherry picked from commit a0e168ec0b6f18ffeddaf8a5dfc68e84563630b8)

- - - - -
467f71c6 by Arnaud Spiwack at 2024-11-26T16:45:13+05:30
Add test for #25185

(cherry picked from commit 791a47b205f1d7cc04f27fc780905f8d4fa042fa)

- - - - -
eda04ebd by Arnaud Spiwack at 2024-11-26T16:46:10+05:30
Quick look: emit the multiplicity of app heads in tcValArgs

Otherwise it's not scaled properly by the context, allowing unsound
expressions.

Fixes #25185.

(cherry picked from commit 374e18e5e79125375a49432da939abbb36268c8a)

- - - - -
dbac8232 by sheaf at 2024-11-26T16:46:45+05:30
X86 NCG: allow VXOR at scalar floating-point types

The NCG can emit VXOR instructions at scalar floating-point types,
but the pretty-printer would panic instead of emitting the appropriate
VXORPS/VXORPD instructions. This patch rectifies that oversight.

Fixes #25455

(cherry picked from commit 3936bf1bc37c9f8ea662ed4b57a3a28b5a670c54)

- - - - -
df943652 by sheaf at 2024-11-26T16:46:58+05:30
Include diagnostic reason in -fdiagnostics-as-json

This commit ensures that the -fdiagnostics-as-json output includes the
diagnostic reason. This allows the full error message produced by GHC
to be re-constructed from the JSON output.

Fixes #25403

(cherry picked from commit 831aab2238e682e2977b4959afa100df928cec09)

- - - - -
ff7a27be by sheaf at 2024-11-26T16:47:12+05:30
x86 NCG: fix regUsageOfInstr for VMOVU & friends

This commit fixes the implementation of 'regUsageOfInstr' for vector
operations that take an 'Operand' as the destination, by ensuring that
when the destination is an address then the address should be *READ*,
and not *WRITTEN*.

Getting this wrong is a disaster, as it means the register allocator
has incorrect information, which can lead to it discard stores to
registers, segfaults ensuing.

Fixes #25486

(cherry picked from commit 1fc02399fcc82a222033919c8d3c5db4b382cb97)

- - - - -
345ea654 by Cheng Shao at 2024-11-26T16:47:26+05:30
driver: fix hpc undefined symbol issue in TH with -fprefer-byte-code

This commit fixes an undefined symbol error in RTS linker when
attempting to compile home modules with -fhpc and
-fbyte-code-and-object-code/-fprefer-byte-code, see #25510 for
detailed description and analysis of the bug.

Also adds T25510/T25510c regression tests to test make mode/oneshot
mode of the bug.

(cherry picked from commit bcbcdaaf2df58e3b7a2756d044c4169a724e03d9)

- - - - -
2645523b by Andreas Klebinger at 2024-11-26T16:47:55+05:30
Compacting GC: Handle black holes in large objects.

As #14497 showed black holes can appear inside large objects when
we capture a computation and later blackhole it like we do for AP_STACK
closures.

Fixes #24791

(cherry picked from commit 7f90f319531c312a074d21688b05f664f0d173fc)

- - - - -
0121b76f by Zubin Duggal at 2024-11-26T18:00:38+05:30
Bump os-string submodule to 2.0.8

- - - - -
962ceb50 by Zubin Duggal at 2024-11-26T18:00:38+05:30
Bump file-io submodule to avoid usage of QuasiQuotes

- - - - -
7bc6877f by Zubin Duggal at 2024-11-26T18:00:38+05:30
Bump filepath submodule to 1.5.4.0

- - - - -
90b49376 by Zubin Duggal at 2024-11-27T18:55:49+05:30
Add haskeline to stage0Packages

Otherwise we link against boot inplace and boot unix as boot haskeline
depends on boot unix.

- - - - -
77f340a2 by Zubin Duggal at 2024-11-27T18:58:23+05:30
Fix ghc-e005 after HasCallstack changes

- - - - -
9478b5ae by Zubin Duggal at 2024-11-27T19:02:38+05:30
Bump file-io submodule to 0.1.5

- - - - -
6fc1fa3b by Zubin Duggal at 2024-11-28T14:31:01+05:30
Bump ghc-prim and template-haskell versions

- - - - -
5d938345 by Zubin Duggal at 2024-11-28T18:23:25+05:30
testsuite: Also match <VERSION> placeholders when normalising callsites

(cherry picked from commit 2807f91bfb0b1e60ea8668622eae344e9ff5d840)

- - - - -
83377584 by Ben Gamari at 2024-12-13T09:52:25+05:30
rts/linker: Fix out-of-bounds mapping logic

Previously the structure of `mmapInRegion` concealed a subtle bug
concerning handling of `mmap` returning mappings below the beginning of
the desired region. Specifically, we would reset `p = result + bytes`
and then again reset `p = region->start` before looping around for
another iteration. This resulted in an infinite loop on FreeBSD.

Fixes #25492.

(cherry picked from commit 292ed74ea908b64490e91346b890cbebdcde37d0)

- - - - -
194ad792 by Ben Gamari at 2024-12-13T09:53:38+05:30
rts/linker/Elf: Resolve _GLOBAL_OFFSET_TABLE_

(cherry picked from commit 952a1243a77ac73222659a49a642b20e80d77cdb)

- - - - -
f5ed23d9 by Ben Gamari at 2024-12-13T09:53:50+05:30
rts/linker: Clarify debug output

(cherry picked from commit 20912f5bac6fe4146172accc1849d9b762eb45e3)

- - - - -
051d8a37 by Ben Gamari at 2024-12-13T09:54:37+05:30
rts: Allow ExecPage to allocate anywhere in address space

Currently the ExecPage facility has two users:

 * GHCi, for constructing info tables, and
 * the adjustor allocation path

Despite neither of these have any spatial locality constraints ExecPage
was using the linker's `mmapAnonForLinker`, which tries hard to ensure
that mappings end up nearby the executable image. This makes adjustor
allocation needlessly subject to fragmentation concerns.

We now instead return less constrained mappings, improving the
robustness of the mechanism.

Addresses #25503.

(cherry picked from commit a104508d2ea5bbc61c4a756dca42fc043b329709)

- - - - -
fa0348b8 by Cheng Shao at 2024-12-13T09:54:47+05:30
rts: remove -Wl,-U,___darwin_check_fd_set_overflow hack

This patch bumps macOS minimum SDK version to 11.0 for x86_64-darwin
to align it with aarch64-darwin. This allows us to get rid of the
horrible -Wl,-U,___darwin_check_fd_set_overflow hack, which is causing
linker warnings and testsuite failures on macOS 15. Fixes #25504.

(cherry picked from commit 88c4fe1d8a3bdbedf3972fde12f663a974cc2191)

- - - - -
563a3124 by Ben Gamari at 2024-12-13T09:54:56+05:30
base: Fix incorrect mentions of GHC.Internal.Numeric

These were incorrectly changed by the automated refactoring of the
`ghc-internal` migration.

Fixes #25521.

(cherry picked from commit c3fc9b861fd00a85a4fcbd9960b8242d9fabe04b)

- - - - -
a9e0cfe7 by Ben Gamari at 2024-12-13T09:55:33+05:30
testsuite: Handle division-by-zero more gracefully

Previously we would fail with an ZeroDivisionError.

Fixes #25321

(cherry picked from commit 513775082b89deae3f83896031caf0e89a7ed333)

- - - - -
a2c033cf by Ben Gamari at 2024-12-13T09:55:33+05:30
hadrian: Bump directory bound to >=1.3.9

Earlier versions of `directory` are racy on Windows due to #24382.

Also includes necessary Hadrian bootstrap plan bump.

Fixes #24382.

(cherry picked from commit 7890f2d8526dd90584eaa181ab10bd30d90e6743)

- - - - -
14d80de1 by Brandon Chinn at 2024-12-13T09:56:20+05:30
Fix panic in multiline string with unterminated gap (#25530)

(cherry picked from commit a8ceccf397216f63d609c4f7471506773c98572f)

- - - - -
4ae5ef94 by Brandon Chinn at 2024-12-13T09:56:29+05:30
Add test case for unterminated multiline string

(cherry picked from commit 9e464ad01f5f60f774504fcaf8d0c30bdd291159)

- - - - -
2feb717e by Matthew Pickering at 2024-12-13T09:56:47+05:30
typechecker: Perform type family consistency checks in topological order

Consider a module M importing modules A, B and C.

We can waste a lot of work depending on the order that the modules are
checked for family consistency.

Consider that C imports A and B. When compiling C we must have already
checked A and B for consistency, therefore if C is processed first then
A and B will not need to be checked for consistency again.

If A and B are compared first, then the consistency checks will be
performed against (wasted as we already performed them for C).

At the moment the order which modules are checked is non-deterministic.

Clearly we should engineer that C is checked before B and A, but by what
scheme?

A simple one is to observe that if a module M is in the transitive
closure of X then the size of the consistent family set of M is less
than or equal to size of the consistent family set of X.

Therefore by sorting the imports by the size of the consistent family
set and processing the largest first, you make sure to process modules
in topological order.

In practice we have observed that this strategy has reduced the amount
of consistency checks performed.

One solution to #25554

(cherry picked from commit 13fe48d40004d9cdf3c73300a18f144bdc5191d9)

- - - - -
c0b36c68 by Ben Gamari at 2024-12-13T09:56:55+05:30
testsuite: Add test for #25560

(cherry picked from commit 683115a40fd989a287fa51efe140af9448526098)

- - - - -
74e42943 by Ben Gamari at 2024-12-13T09:57:04+05:30
compiler: Don't attempt to TSAN-instrument SIMD operations

TSAN only provides instrumentation for 8, 16, 32, and 64-bit memory
loads/stores. Don't attempt to instrument wider operations.

Fixes #25563.

(cherry picked from commit e745e3a30670440c9cf65450835d4eddada784eb)

- - - - -
f8b36d9b by Ben Gamari at 2024-12-13T09:57:17+05:30
hadrian: Mitigate mktexfmt race

At least some versions of Texlive's `mktexfmt` utility cannot be invoked
concurrently in their initial run since they fail to handle failure of
`mkdir` due to racing. Specifically, we see

```
| Run Xelatex: users_guide.tex => /tmp/extra-dir-9616886274866
| Run Xelatex: Haddock.tex => /tmp/extra-dir-9616886274869
This is XeTeX, Version 3.14159265-2.6-0.999992 (TeX Live 2020) (preloaded format=xelatex)
 restricted \write18 enabled.
kpathsea: Running mktexfmt xelatex.fmt
mktexfmt: mktexfmt is using the following fmtutil.cnf files (in precedence order):
mktexfmt:   /usr/share/texlive/texmf-dist/web2c/fmtutil.cnf
mktexfmt: mktexfmt is using the following fmtutil.cnf file for writing changes:
mktexfmt:   /builds/ghc/ghc/tmp-home/.texlive2020/texmf-config/web2c/fmtutil.cnf
/usr/bin/mktexfmt: mkdir(/builds/ghc/ghc/tmp-home/.texlive2020/texmf-var/web2c/) failed for tree /builds/ghc/ghc/tmp-home/.texlive2020/texmf-var/web2c: File exists at /usr/share/texlive/tlpkg/TeXLive/TLUtils.pm line 937.
I can't find the format file `xelatex.fmt'!
```

That is two `mktexfmt` invocations (for the user's guide and haddock
builds) attempted to create `$HOME/texlive2020/texmf-var/web2c` and
raced. One of the two `mkdir`'s consequently failed, bringing down the
entire build.

We avoid this by ensuring that the first `xelatex` invocation is always
performed serially.

Fixes #25564.

(cherry picked from commit 41dae5b86955094aa4c5647f63f1f52f1a8a5519)

- - - - -
ada12a20 by Ben Gamari at 2024-12-13T09:57:41+05:30
rts/CheckUnload: Reset old_objects if unload is skipped

Previously `checkUnload` failed to reset `old_objects` when it decided
not to unload (e.g. due to heap profiling being enabled).

Fixes #24935.

(cherry picked from commit 9efbc51f99118e8f9c3abf2bcb6dc3295893ded6)

- - - - -
f43b1d65 by Ben Gamari at 2024-12-13T09:57:53+05:30
rts/CheckUnload: Don't prepare to unload if we can't unload

Previously `prepareUnloadCheck` would move the `objects` list to
`old_objects` even when profiling (where we cannot unload). This caused
us to vacate the `objects` list during major GCs, losing track of loaded
objects. Fix this by ensuring that `prepareUnloadCheck` and
`checkUnload` both use the same short-cutting logic.

(cherry picked from commit 34d3e8e69b62b92cc438514f7fb8e37ce639efea)

- - - - -
5c9c3e3f by Zubin Duggal at 2024-12-13T10:00:58+05:30
Bump Cabal submodule to 3.14.1.0

- - - - -
89790626 by Zubin Duggal at 2024-12-13T10:16:14+05:30
Bump directory submodule to 0.12.2.0

- - - - -
9321f8b7 by Andreas Klebinger at 2024-12-13T10:24:04+05:30
Document -fmax-forced-spec-args=⟨n⟩ in the 9.12 changelog.

Fixes #25544

(cherry picked from commit e2d2645c01d45149420bb07987b1634e577adc04)

- - - - -
66d66a25 by Andreas Klebinger at 2024-12-13T10:25:30+05:30
Document -fwrite-if-compression in release notes.

(cherry picked from commit 93335a250347ed0591d240701a56ff171a9a5561)

- - - - -
f29620c8 by Adam Gundry at 2024-12-13T10:27:57+05:30
Fix formatting issues and make corrections to 9.12.1 release notes

(cherry picked from commit 6ce3e546083304c4f2da060184b3b73f48dd8fc0)

- - - - -
15c719f3 by Zubin Duggal at 2024-12-13T16:59:48+05:30
Changelog fixes

- - - - -
dc86785e by Zubin Duggal at 2024-12-13T16:59:48+05:30
ghcup metatdata: use fedora33 for redhat

Redhat 9 doesn't have libtinfo.so.5 anymore

- - - - -
fc647a65 by Ben Gamari at 2024-12-13T16:59:48+05:30
testsuite: Introduce req_c_rts

As suggested by @hsyl20, this is intended to mark tests that rely on the
behavior of the C RTS.

(cherry picked from commit 1e84b41108d96cb721dd11281105fdf621105a12)

- - - - -
cbfd0829 by Zubin Duggal at 2024-12-13T16:59:48+05:30
release: copy index.html from correct directory

- - - - -
0ba478fe by Matthew Pickering at 2024-12-13T16:59:48+05:30
configure: Allow happy-2.0.2

happy-2.0.2 can be used to compile GHC.

happy-2.0 and 2.0.1 have bugs which make it unsuitable to use.

The version bound is now == 1.20.* || >= 2.0.2 && < 2.1

Fixes #25276

(cherry picked from commit 0029ca91c845dd4530eb2c4606ad5bd59775cec2)

- - - - -
24b4914a by Cristiano Moraes at 2024-12-13T16:59:48+05:30
configure: Find C++ probing when GCC version is the latest but G++ is old #23118

(cherry picked from commit 78ad81ecef846f73fee0f6c1a86cd6f19aa29b21)

- - - - -
95d35d6c by Ben Gamari at 2024-12-13T16:59:48+05:30
configure: Accept happy-2.1.2

happy-2.1 was released in late Oct 2024. I have confirmed that master
bootstraps with it. Here we teach configure to accept this tool.

Fixes #25438.

(cherry picked from commit 1fd83f865ffb620f4f7c4c59787710206dcadb90)

- - - - -
86f29950 by Ben Gamari at 2024-12-13T16:59:48+05:30
configure: Implement ld override whitelist

Bring `configure` into alignment with `ghc-toolchain`, ensuring that the
ld-override logic will only take effect on Linux and Windows.

Fixes #25501.

(cherry picked from commit 992259962191b0b774dfeeabb46729376c7fe7cf)

- - - - -
dde3796b by Zubin Duggal at 2024-12-13T23:41:56+05:30
hadrian-multi: warn on unused imports

os-string has redundant imports

- - - - -
52b58a66 by Zubin Duggal at 2024-12-13T23:41:56+05:30
ghcup metadata: output metadata fragment in CI

- - - - -
39e4fed1 by Zubin Duggal at 2024-12-13T23:41:56+05:30
rel-eng: ghcup metadata generation: generated yaml anchors with meaningful names

(cherry picked from commit d83f5bd730a8aef37d8a38b3560590d9798f8e45)
(cherry picked from commit 280b627869da55a22b4b9a3458e6115b06b5fff4)

- - - - -
e226fcf0 by Ben Gamari at 2024-12-14T14:47:47+05:30
ghc-internal: Drop GHC.Internal.Data.Enum

This module consists only of reexports and consequently there is no
reason for it to exist.

(cherry picked from commit 55d8304e02000b3ec33d254794e84d159dc93926)

- - - - -
227c86d4 by Ben Gamari at 2024-12-14T14:47:47+05:30
base: Introduce Data.Bounded

As proposed in [CLC#208] but unfortunately `Data.Enum` was already
incorrectly introduced in the `ghc-internal` refactor.

[CLC#208]: https://github.com/haskell/core-libraries-committee/issues/208

(cherry picked from commit 56b9f484fd89b5c2c69045dcd5690f68699ba0b1)

- - - - -
ce8458e9 by Ben Gamari at 2024-12-14T14:47:47+05:30
base: Deprecate export of Bounded from Data.Enum

This begins the process of bringing us into compliance with
[CLC#208].

[CLC#208]: https://github.com/haskell/core-libraries-committee/issues/208

(cherry picked from commit 336d392e417203c492fec15ecf91dd444cb70936)

- - - - -
65c1928d by Ben Gamari at 2024-12-14T14:47:47+05:30
base: Mention incorrect Data.Enum addition in changelog

(cherry picked from commit dd7ca93903eba8c63261656ca3d245f9e8baa662)

- - - - -
032b058c by Ben Gamari at 2024-12-15T21:21:51+05:30
base: Reintroduce {Show,Enum} IoSubSystem

These instances were dropped in !9676 but not approved by the CLC.

Addresses #25549.

(cherry picked from commit dfd1db48aaa1ee6c109e9a05ce34672418f17f59)

- - - - -
dc7c0f85 by Zubin Duggal at 2024-12-15T21:21:51+05:30
RELEASE=YES

- - - - -
daf659b6 by Zubin Duggal at 2024-12-15T21:28:10+05:30
ci: allow test-primops to fail as a workaround to #25582

- - - - -
eb2859af by Ben Gamari at 2025-01-16T17:20:25-05:00
Revert "Division by constants optimization"

This appears to be responsible for the regression described in #25653.

This reverts commit daff1e30219d136977c71f42e82ccc58c9013cfb.

- - - - -
e7097cf5 by Ben Gamari at 2025-01-16T17:20:25-05:00
testsuite: Introduce div2 test

This is a useful test from !8392 which is worth keeping around.

- - - - -
e6850133 by Ben Gamari at 2025-01-16T17:20:25-05:00
testsuite: Test shift correctness in mul2 test

- - - - -
2a48b7b5 by Ben Gamari at 2025-01-16T17:20:25-05:00
testsuite: Add regression test for #25653

- - - - -
f6aa9f65 by Ben Gamari at 2025-01-22T13:17:55-05:00
Cmm/Parser: Add surface syntax for Mul2 MachOps

These are otherwise very hard to test in isolation.

- - - - -
33a74ef5 by Ben Gamari at 2025-01-22T15:02:48-05:00
Add release notes for 9.12.2

- - - - -
a6f47532 by Ben Gamari at 2025-01-22T15:02:59-05:00
configure: Set RELEASE=NO

- - - - -


30 changed files:

- .gitattributes
- .gitlab-ci.yml
- .gitlab/ci.sh
- .gitlab/generate-ci/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
- .gitlab/rel_eng/recompress-all
- .gitlab/rel_eng/upload.sh
- CODEOWNERS
- compiler/GHC.hs
- compiler/GHC/Builtin/Names.hs
- compiler/GHC/Builtin/primops.txt.pp
- compiler/GHC/Cmm/Config.hs
- compiler/GHC/Cmm/MachOp.hs
- compiler/GHC/Cmm/Opt.hs
- compiler/GHC/Cmm/Parser.y
- compiler/GHC/Cmm/Pipeline.hs
- compiler/GHC/Cmm/Sink.hs
- compiler/GHC/Cmm/ThreadSanitizer.hs
- compiler/GHC/CmmToAsm/Format.hs
- compiler/GHC/CmmToAsm/PIC.hs
- compiler/GHC/CmmToAsm/PPC/CodeGen.hs
- compiler/GHC/CmmToAsm/PPC/Instr.hs
- compiler/GHC/CmmToAsm/PPC/Ppr.hs
- compiler/GHC/CmmToAsm/RV64/CodeGen.hs
- compiler/GHC/CmmToAsm/RV64/Instr.hs
- compiler/GHC/CmmToAsm/RV64/Ppr.hs
- compiler/GHC/CmmToAsm/Wasm.hs
- compiler/GHC/CmmToAsm/Wasm/Asm.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/7366808fcab007963d1b225912356fc27ab86208...a6f47532aa7c5e08f9d7549e72839b400d932cb8

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/7366808fcab007963d1b225912356fc27ab86208...a6f47532aa7c5e08f9d7549e72839b400d932cb8
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/20250122/97dcc351/attachment-0001.html>


More information about the ghc-commits mailing list