[Git][ghc/ghc][wip/ghc-9.6-backports] 35 commits: testsuite: Add tests for #23146

Zubin (@wz1000) gitlab at gitlab.haskell.org
Tue Sep 12 10:29:32 UTC 2023



Zubin pushed to branch wip/ghc-9.6-backports at Glasgow Haskell Compiler / GHC


Commits:
9a6b1a37 by Ben Gamari at 2023-09-12T15:05:13+05:30
testsuite: Add tests for #23146

Both lifted and unlifted variants.

(cherry picked from commit 33cf4659f209ef8e97be188279216a2f4fe0cf51)

- - - - -
d75a2fd8 by Ben Gamari at 2023-09-12T15:05:13+05:30
codeGen: Fix some Haddocks

(cherry picked from commit 76727617bccc88d1466ad6dc1442ab8ebb34f79a)

- - - - -
1269c629 by Ben Gamari at 2023-09-12T15:05:13+05:30
codeGen: Give proper LFInfo to datacon wrappers

As noted in `Note [Conveying CAF-info and LFInfo between modules]`,
when importing a binding from another module we must ensure that it gets
the appropriate `LambdaFormInfo` if it is in WHNF to ensure that
references to it are tagged correctly.

However, the implementation responsible for doing this,
`GHC.StgToCmm.Closure.mkLFImported`, only dealt with datacon workers and
not wrappers. This lead to the crash of this program in #23146:

    module B where

    type NP :: [UnliftedType] -> UnliftedType
    data NP xs where
      UNil :: NP '[]

    module A where
    import B

    fieldsSam :: NP xs -> NP xs -> Bool
    fieldsSam UNil UNil = True

    x = fieldsSam UNil UNil

Due to its GADT nature, `UNil` produces a trivial wrapper

    $WUNil :: NP '[]
    $WUNil = UNil @'[] @~(<co:1>)

which is referenced in the RHS of `A.x`. Due to the above-mentioned bug
in `mkLFImported`, the references to `$WUNil` passed to `fieldsSam` were
not tagged. This is problematic as `fieldsSam` expected its arguments to
be tagged as they are unlifted.

The fix is straightforward: extend the logic in `mkLFImported` to cover
(nullary) datacon wrappers as well as workers. This is safe because we
know that the wrapper of a nullary datacon will be in WHNF, even if it
includes equalities evidence (since such equalities are not runtime
relevant).

Thanks to @MangoIV for the great ticket and @alt-romes for his
minimization and help debugging.

Fixes #23146.

(cherry picked from commit 33a8c348cae5fd800c015fd8c2230b8066c7c0a4)

- - - - -
8cc54e16 by Rodrigo Mesquita at 2023-09-12T15:05:13+05:30
codeGen: Fix LFInfo of imported datacon wrappers

As noted in #23231 and in the previous commit, we were failing to give a
an LFInfo of LFCon to a nullary datacon wrapper from another module,
failing to properly tag pointers which ultimately led to the
segmentation fault in #23146.

On top of the previous commit which now considers wrappers where we
previously only considered workers, we change the order of the guards so
that we check for the arity of the binding before we check whether it is
a constructor. This allows us to
(1) Correctly assign `LFReEntrant` to imported wrappers whose worker was
nullary, which we previously would fail to do
(2) Remove the `isNullaryRepDataCon` predicate:
    (a) which was previously wrong, since it considered wrappers whose
    workers had zero-width arguments to be non-nullary and would fail to
    give `LFCon` to them
    (b) is now unnecessary, since arity == 0 guarantees
        - that the worker takes no arguments at all
        - and the wrapper takes no arguments and its RHS must be an
          application of the worker to zero-width-args only.
        - we lint these two items with an assertion that the datacon
          `hasNoNonZeroWidthArgs`

We also update `isTagged` to use the new logic in determining the
LFInfos of imported Ids.

The creation of LFInfos for imported Ids and this detail are explained
in Note [The LFInfo of Imported Ids].

Note that before the patch to those issues we would already consider these
nullary wrappers to have `LFCon` lambda form info; but failed to re-construct
that information in `mkLFImported`

Closes #23231, #23146

(I've additionally batched some fixes to documentation I found while
investigating this issue)

(cherry picked from commit 2fc18e9e784ccc775db8b06a5d10986588cce74a)

- - - - -
461183d6 by Sebastian Graf at 2023-09-12T15:05:13+05:30
DmdAnal: Unleash demand signatures of free RULE and unfolding binders (#23208)

In #23208 we observed that the demand signature of a binder occuring in a RULE
wasn't unleashed, leading to a transitively used binder being discarded as
absent. The solution was to use the same code path that we already use for
handling exported bindings.

See the changes to `Note [Absence analysis for stable unfoldings and RULES]`
for more details.

I took the chance to factor out the old notion of a `PlusDmdArg` (a pair of a
`VarEnv Demand` and a `Divergence`) into `DmdEnv`, which fits nicely into our
existing framework. As a result, I had to touch quite a few places in the code.

This refactoring exposed a few small bugs around correct handling of bottoming
demand environments. As a result, some strictness signatures now mention uniques
that weren't there before which caused test output changes to T13143, T19969 and
T22112. But these tests compared whole -ddump-simpl listings which is a very
fragile thing to begin with. I changed what exactly they test for based on the
symptoms in the corresponding issues.

There is a single regression in T18894 because we are more conservative around
stable unfoldings now. Unfortunately it is not easily fixed; let's wait until
there is a concrete motivation before invest more time.

Fixes #23208.

(cherry picked from commit c30ac25f7dfaded58bb2ff85d4bffe662e4af8b1)

- - - - -
da25216d by Matthew Craven at 2023-09-12T15:05:13+05:30
StgToCmm: Upgrade -fcheck-prim-bounds behavior

Fixes #21054. Additionally, we can now check for range overlap
when generating Cmm for primops that use memcpy internally.

(cherry picked from commit 65a442fccd081d9370ae4ee4e74f116139b5c2c8)

- - - - -
be3df45f by Ben Gamari at 2023-09-12T15:05:13+05:30
hadrian: Always canonicalize topDirectory

Hadrian's `topDirectory` is intended to provide an absolute path to the
root of the GHC tree. However, if the tree is reached via a symlink this

One question here is whether the `canonicalizePath` call is expensive
enough to warrant caching. In a quick microbenchmark I observed that
`canonicalizePath "."` takes around 10us per call; this seems
sufficiently low not to worry.

Alternatively, another approach here would have been to rather move the
canonicalization into `m4/fp_find_root.m4`. This would have avoided
repeated canonicalization but sadly path canonicalization is a hard
problem in POSIX shell.

Addresses #22451.

(cherry picked from commit 5efa9ca545d8d33b9be4fc0ba91af1db38f19276)

- - - - -
262f1bd6 by aadaa_fgtaa at 2023-09-12T15:05:13+05:30
Optimise ELF linker (#23464)

- cache last elements of `relTable`, `relaTable` and `symbolTables` in `ocInit_ELF`
- cache shndx table in ObjectCode
- run `checkProddableBlock` only with debug rts

(cherry picked from commit b3e1436f968c0c36a27ea0339ee2554970b329fe)

- - - - -
8f52d208 by Ben Gamari at 2023-09-12T15:05:14+05:30
rts: Ensure that pinned allocations respect block size

Previously, it was possible for pinned, aligned allocation requests to
allocate beyond the end of the pinned accumulator block. Specifically,
we failed to account for the padding needed to achieve the requested
alignment in the "large object" check. With large alignment requests,
this can result in the allocator using the capability's pinned object
accumulator block to service a request which is larger than
`PINNED_EMPTY_SIZE`.

To fix this we reorganize `allocatePinned` to consistently account for
the alignment padding in all large object checks. This is a bit subtle
as we must handle the case of a small allocation request filling the
accumulator block, as well as large requests.

Fixes #23400.

(cherry picked from commit fd8c57694a00f6359bd66365f1284388c869ac60)

- - - - -
2313c939 by Ben Gamari at 2023-09-12T15:05:14+05:30
testsuite: Add test for #23400

(cherry picked from commit 98185d5212fb0464dcbcca0ca2c33326a7a002e8)

- - - - -
70c569c9 by Ben Gamari at 2023-09-12T15:05:14+05:30
base: Fix incorrect CPP guard

This was guarded on `darwin_HOST_OS` instead of `defined(darwin_HOST_OS)`.

(cherry picked from commit d7ef1704aeba451bd3e0efbdaaab2638ee1f0bc8)

- - - - -
9c35dfd6 by Ben Gamari at 2023-09-12T15:05:14+05:30
rts/Trace: Ensure that debugTrace arguments are used

As debugTrace is a macro we must take care to ensure that
the fact is clear to the compiler lest we see warnings.

(cherry picked from commit 7c7d1f66d35f73a2faa898a33aa80cd276159dc2)

- - - - -
327263a8 by Ben Gamari at 2023-09-12T15:05:14+05:30
rts: Various warnings fixes

(cherry picked from commit cb92051e3d85575ff6abd753c9b135930cc50cf8)

- - - - -
6d5cd7a1 by Ben Gamari at 2023-09-12T15:05:14+05:30
hadrian: Ignore warnings in unix and semaphore-compat

(cherry picked from commit dec81dd1fd0475dde4929baae625d155387300bb)

- - - - -
fc35a2f4 by Krzysztof Gogolewski at 2023-09-12T15:05:14+05:30
Show an error when we cannot default a concrete tyvar

Fixes #23153

(cherry picked from commit 0da18eb79540181ae9835e73d52ba47ec79fff6b)

- - - - -
f682846e by sheaf at 2023-09-12T15:13:02+05:30
Handle ConcreteTvs in inferResultToType

This patch fixes two issues.

  1. inferResultToType was discarding the ir_frr information, which meant
     some metavariables ended up being MetaTvs instead of ConcreteTvs.

     This function now creates new ConcreteTvs as necessary, instead of
     always creating MetaTvs.

  2. startSolvingByUnification can make some type variables concrete.
     However, it didn't return an updated type, so callers of this
     function, if they don't zonk, might miss this and accidentally
     perform a double update of a metavariable.

     We now return the updated type from this function, which avoids
     this issue.

Fixes #23154

- - - - -
9a1ab671 by Krzysztof Gogolewski at 2023-09-12T15:13:02+05:30
Use tcInferFRR to prevent bad generalisation

Fixes #23176

(cherry picked from commit 4b89bb54a1d1d6a7b30a6bbfd21eed5d85506813)

- - - - -
f2f1b790 by Simon Peyton Jones at 2023-09-12T15:28:50+05:30
Look both ways when looking for quantified equalities

When looking up (t1 ~# t2) in the quantified constraints,
check both orientations.  Forgetting this led to #23333.

(cherry picked from commit 40c7daed0c971e58e86a8189f82f72e9213af8b6)

- - - - -
a4649c0c by Moisés Ackerman at 2023-09-12T15:33:23+05:30
Add failing test case for #23492

(cherry picked from commit 6074cc3cda9b9836c784942a1aa7f766fb142787)

- - - - -
b288fa80 by Moisés Ackerman at 2023-09-12T15:33:34+05:30
Use generated src span for catch-all case of record selector functions

This fixes #23492. The problem was that we used the real source span
of the field declaration for the generated catch-all case in the
selector function, in particular in the generated call to
`recSelError`, which meant it was included in the HIE output. Using
`generatedSrcSpan` instead means that it is not included.

(cherry picked from commit 356a269258a50bf67811fe0edb193fc9f82dfad1)

- - - - -
9d319905 by Matthew Pickering at 2023-09-12T15:36:50+05:30
Add -fpolymorphic-specialisation flag (off by default at all optimisation levels)

Polymorphic specialisation has led to a number of hard to diagnose
incorrect runtime result bugs (see #23469, #23109, #21229, #23445) so
this commit introduces a flag `-fpolymorhphic-specialisation` which
allows users to turn on this experimental optimisation if they are
willing to buy into things going very wrong.

Ticket #23469

(cherry picked from commit 9f01d14b5bc1c73828b2b061206c45b84353620e)

- - - - -
9734beed by Bryan Richter at 2023-09-12T15:37:39+05:30
Add missing void prototypes to rts functions

See #23561.

(cherry picked from commit 82ac6bf113526f61913943b911089534705984fb)

- - - - -
cd4441e9 by Ben Gamari at 2023-09-12T15:38:16+05:30
Define FFI_GO_CLOSURES

The libffi shipped with Apple's XCode toolchain does not contain a
definition of the FFI_GO_CLOSURES macro, despite containing references
to said macro. Work around this by defining the macro, following the
model of a similar workaround in OpenJDK [1].

[1] https://github.com/openjdk/jdk17u-dev/pull/741/files

(cherry picked from commit 8b35e8caafeeccbf06b7faa70e807028a3f0ff43)

- - - - -
f41d82b6 by Ben Gamari at 2023-09-12T15:41:03+05:30
hadrian: Ensure that way-flags are passed to CC

Previously the way-specific compilation flags (e.g. `-DDEBUG`,
`-DTHREADED_RTS`) would not be passed to the CC invocations. This meant
that C dependency files would not correctly reflect
dependencies predicated on the way, resulting in the rather
painful #23554.

Closes #23554.

(cherry picked from commit cca74dab6809f8cf7ffc2ec9df689e06aa425110)

- - - - -
5e6852b7 by Krzysztof Gogolewski at 2023-09-12T15:42:11+05:30
Fix #23567, a specializer bug

Found by Simon in https://gitlab.haskell.org/ghc/ghc/-/issues/23567#note_507834

The testcase isn't ideal because it doesn't detect the bug in master,
unless doNotUnbox is removed as in
https://gitlab.haskell.org/ghc/ghc/-/issues/23567#note_507692.
But I have confirmed that with that modification, it fails before
and passes afterwards.

(cherry picked from commit bf9b9de0685e23c191722dfdb78d28b44f1cba05)

- - - - -
96f0c412 by Dave Barton at 2023-09-12T15:42:40+05:30
Fix some broken links and typos

(cherry picked from commit 4457da2a7dba97ab2cd2f64bb338c904bb614244)

- - - - -
cf9bb35e by Bodigrim at 2023-09-12T15:47:12+05:30
Add since annotations for Data.Foldable1

(cherry picked from commit 054261dd319b505392458da7745e768847015887)

- - - - -
bda64da6 by Ben Gamari at 2023-09-12T15:49:07+05:30
rts/RtsSymbols: Add AArch64 outline atomic operations

Fixes #22012 by adding the symbols described in
https://github.com/llvm/llvm-project/blob/main/llvm/docs/Atomics.rst#libcalls-atomic.

Ultimately this would be better addressed by #22011, but this is a first
step in the right direction and fixes the immediate symptom.

Note that we dropped the `__arch64_cas16` operations as these provided
by all platforms's compilers. Also, we don't link directly against the
libgcc/compiler-rt definitions but rather provide our own wrappers to
work around broken toolchains (e.g. https://bugs.gentoo.org/868018).

Generated via https://gitlab.haskell.org/ghc/ghc/-/snippets/5733.

(cherry picked from commit 1aa5733a4480420fdc146322d86dd143321a3da6)

- - - - -
ba7e3ae8 by Matthew Pickering at 2023-09-12T15:49:32+05:30
driver: Fix -S with .cmm files

There was an oversight in the driver which assumed that you would always
produce a `.o` file when compiling a .cmm file.

Fixes #23610

(cherry picked from commit 76983a0dca64dfb7e94aea0c4f494921f8513b41)

- - - - -
3a440450 by sheaf at 2023-09-12T15:50:53+05:30
Valid hole fits: don't panic on a Given

The function GHC.Tc.Errors.validHoleFits would end up panicking when
encountering a Given constraint. To fix this, it suffices to filter out
the Givens before continuing.

Fixes #22684

(cherry picked from commit 630e302617a4a3e00d86d0650cb86fa9e6913e44)

- - - - -
51c97d63 by Matthew Pickering at 2023-09-12T15:51:19+05:30
simplifier: Correct InScopeSet in rule matching

The in-scope set passedto the `exprIsLambda_maybe` call lacked all the
in-scope binders. @simonpj suggests this fix where we augment the
in-scope set with the free variables of expression which fixes this
failure mode in quite a direct way.

Fixes #23630

(cherry picked from commit 4f5538a8e2a8b9bc490bcd098fa38f6f7e9f4d73)

- - - - -
375c2225 by Ben Gamari at 2023-09-12T15:51:40+05:30
rts/win32: Ensure reliability of IO manager shutdown

When the Win32 threaded IO manager shuts down, `ioManagerDie` sends an
`IO_MANAGER_DIE` event to the IO manager thread using the
`io_manager_event` event object. Finally, it will closes the event object,
and invalidate `io_manager_event`.

Previously, `readIOManagerEvent` would see that `io_manager_event` is
invalid and return `0`, suggesting that everything is right with the
world. This meant that if `ioManagerDie` invalidated the handle before
the event manager was blocked on the event we would end up in a
situation where the event manager would never realize it was asked to
shut down.

Fix this by ensuring that `readIOManagerEvent` instead returns
`IO_MANAGER_DIE` when we detect that the event object has been
invalidated by `ioManagerDie`.

Fixes #23691.

(cherry picked from commit 01db1117e18f140987f608a78f3e929242d6f00c)

- - - - -
63675c0f by Ben Gamari at 2023-09-12T15:56:01+05:30
codeGen: Ensure that TSAN is aware of writeArray# write barriers

By using a proper release store instead of a fence.

(cherry picked from commit aca20a5d4fde1c6429c887624bb95c9b54b7af73)

- - - - -
5626e627 by Ben Gamari at 2023-09-12T15:56:08+05:30
codeGen: Ensure that array reads have necessary barriers

This was the cause of #23541.

(cherry picked from commit 453c0531f2edf49b75c73bc45944600d8d7bf767)

- - - - -
dd3f569a by Ben Gamari at 2023-09-12T15:57:07+05:30
linker/PEi386: Don't sign-extend symbol section number

Previously we incorrectly interpreted PE section numbers as signed
values. However, this isn't the case; rather, it's an unsigned 16-bit number
with a few special bit-patterns (0xffff and 0xfffe). This resulted in #22941
as the linker would conclude that the sections were invalid.

Fixing this required quite a bit of refactoring.

Closes #22941.

(cherry picked from commit 0eb54c050e46f447224167166dd6d2805ca8cdf5)

- - - - -


27 changed files:

- compiler/GHC/Cmm/CLabel.hs
- compiler/GHC/Core/DataCon.hs
- compiler/GHC/Core/Opt/DmdAnal.hs
- compiler/GHC/Core/Opt/SpecConstr.hs
- compiler/GHC/Core/Opt/Specialise.hs
- compiler/GHC/Core/Rules.hs
- compiler/GHC/Core/Tidy.hs
- compiler/GHC/CoreToStg/Prep.hs
- compiler/GHC/Driver/CodeOutput.hs
- compiler/GHC/Driver/Flags.hs
- compiler/GHC/Driver/Pipeline.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/Stg/InferTags/Rewrite.hs
- compiler/GHC/Stg/Syntax.hs
- compiler/GHC/Stg/Unarise.hs
- compiler/GHC/StgToCmm/Closure.hs
- compiler/GHC/StgToCmm/Env.hs
- compiler/GHC/StgToCmm/Foreign.hs
- compiler/GHC/StgToCmm/Monad.hs
- compiler/GHC/StgToCmm/Prim.hs
- compiler/GHC/StgToCmm/Types.hs
- compiler/GHC/Tc/Errors.hs
- compiler/GHC/Tc/Errors/Ppr.hs
- compiler/GHC/Tc/Errors/Types.hs
- compiler/GHC/Tc/Gen/Bind.hs
- compiler/GHC/Tc/Gen/Head.hs
- compiler/GHC/Tc/Solver/Canonical.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/06cf01a608ca5993454c3c6b81a5fa99fb9b7011...dd3f569a35d31361707fdf75f383b7a53968e032

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/06cf01a608ca5993454c3c6b81a5fa99fb9b7011...dd3f569a35d31361707fdf75f383b7a53968e032
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/20230912/2e9cd60e/attachment-0001.html>


More information about the ghc-commits mailing list