[Git][ghc/ghc][wip/simplifier-tweaks] 64 commits: base: Use strerror_r instead of strerror

Simon Peyton Jones (@simonpj) gitlab at gitlab.haskell.org
Thu Mar 14 16:09:37 UTC 2024



Simon Peyton Jones pushed to branch wip/simplifier-tweaks at Glasgow Haskell Compiler / GHC


Commits:
2859a637 by Ben Gamari at 2024-03-08T18:26:47-05:00
base: Use strerror_r instead of strerror

As noted by #24344, `strerror` is not necessarily thread-safe.
Thankfully, POSIX.1-2001 has long offered `strerror_r`, which is
safe to use.

Fixes #24344.

CLC discussion: https://github.com/haskell/core-libraries-committee/issues/249

- - - - -
edb9bf77 by Jade at 2024-03-09T03:39:38-05:00
Error messages: Improve Error messages for Data constructors in type signatures.

This patch improves the error messages from invalid type signatures by
trying to guess what the user did and suggesting an appropriate fix.

Partially fixes: #17879

- - - - -
cfb197e3 by Patrick at 2024-03-09T03:40:15-05:00
HieAst: add module name #24493

The main purpose of this is to tuck the module name `xxx` in `module xxx where` into the hieAst.
It should fix #24493.

The following have been done:
1. Renamed and update the `tcg_doc_hdr :: Maybe (LHsDoc GhcRn)` to `tcg_hdr_info :: (Maybe (LHsDoc GhcRn), Maybe (XRec GhcRn ModuleName))`
   To store the located module name information.
2. update the `RenamedSource` and `RenamedStuff` with extra `Maybe (XRec GhcRn ModuleName)` located module name information.
3. add test `testsuite/tests/hiefile/should_compile/T24493.hs` to ensure the module name is added and update several relevent tests.
4. accompanied submodule haddoc test update MR in https://gitlab.haskell.org/ghc/haddock/-/merge_requests/53

- - - - -
2341d81e by Vaibhav Sagar at 2024-03-09T03:40:54-05:00
GHC.Utils.Binary: fix a couple of typos

- - - - -
5580e1bd by Ben Gamari at 2024-03-09T03:41:30-05:00
rts: Drop .wasm suffix from .prof file names

This replicates the behavior on Windows, where `Hi.exe` will produce
profiling output named `Hi.prof` instead of `Hi.exe.prof`.

While in the area I also fixed the extension-stripping logic, which
incorrectly rewrote `Hi.exefoo` to `Hi.foo`.

Closes #24515.

- - - - -
259495ee by Cheng Shao at 2024-03-09T03:41:30-05:00
testsuite: drop exe extension from .hp & .prof filenames

See #24515 for details.

- - - - -
c477a8d2 by Ben Gamari at 2024-03-09T03:42:05-05:00
rts/linker: Enable GOT support on all platforms

There is nothing platform-dependent about our GOT implementation and
GOT support is needed by `T24171` on i386.

- - - - -
2e592857 by Vladislav Zavialov at 2024-03-09T03:42:41-05:00
Drop outdated comment on TcRnIllformedTypePattern

This should have been done in 0f0c53a501b but I missed it.

- - - - -
c554b4da by Ben Gamari at 2024-03-09T09:39:20-05:00
rts/CloneStack: Bounds check array write

- - - - -
15c590a5 by Ben Gamari at 2024-03-09T09:39:20-05:00
rts/CloneStack: Don't expose helper functions in header

- - - - -
e831ce31 by Ben Gamari at 2024-03-09T09:39:20-05:00
base: Move internals of GHC.InfoProv into GHC.InfoProv.Types

Such that we can add new helpers into GHC.InfoProv.Types without
breakage.

- - - - -
6948e24d by Ben Gamari at 2024-03-09T09:39:20-05:00
rts: Lazily decode IPE tables

Previously we would eagerly allocate `InfoTableEnt`s for each
info table registered in the info table provenance map. However, this
costs considerable memory and initialization time. Instead we now
lazily decode these tables. This allows us to use one-third the memory
*and* opens the door to taking advantage of sharing opportunities within
a module.

This required considerable reworking since lookupIPE now must be passed
its result buffer.

- - - - -
9204a04e by Ben Gamari at 2024-03-09T09:39:20-05:00
rts/IPE: Don't expose helper in header

- - - - -
308926ff by Ben Gamari at 2024-03-09T09:39:20-05:00
rts/IPE: Share module_name within a Node

This allows us to shave a 64-bit word off of the packed IPE entry size.

- - - - -
bebdea05 by Ben Gamari at 2024-03-09T09:39:20-05:00
IPE: Expose unit ID in InfoTableProv

Here we add the unit ID to the info table provenance structure.

- - - - -
6519c9ad by Ben Gamari at 2024-03-09T09:39:35-05:00
rts: Refactor GHC.Stack.CloneStack.decode

Don't allocate a Ptr constructor per frame.

- - - - -
ed0b69dc by Ben Gamari at 2024-03-09T09:39:35-05:00
base: Do not expose whereFrom# from GHC.Exts

- - - - -
2b1faea9 by Vladislav Zavialov at 2024-03-09T17:38:21-05:00
docs: Update info on TypeAbstractions

* Mention TypeAbstractions in 9.10.1-notes.rst
* Set the status to "Experimental".
* Add a "Since: GHC 9.x" comment to each section.

- - - - -
f8b88918 by Ben Gamari at 2024-03-09T21:21:46-05:00
ci-images: Bump Alpine image to bootstrap with 9.8.2

- - - - -
705e6927 by Ben Gamari at 2024-03-09T21:21:46-05:00
testsuite: Mark T24171 as fragile due to #24512

I will fix this but not in time for 9.10.1-alpha1

- - - - -
c74196e1 by Ben Gamari at 2024-03-09T21:21:46-05:00
testsuite: Mark linker_unload_native as fragile

In particular this fails on platforms without `dlinfo`. I plan to
address this but not before 9.10.1-alpha1.

- - - - -
f4d87f7a by Ben Gamari at 2024-03-09T21:21:46-05:00
configure: Bump version to 9.10

- - - - -
88df9a5f by Ben Gamari at 2024-03-09T21:21:46-05:00
Bump transformers submodule to 0.6.1.1

- - - - -
8176d5e8 by Ben Gamari at 2024-03-09T21:21:46-05:00
testsuite: Increase ulimit for T18623

1 MByte was just too tight and failed intermittently on some platforms
(e.g. CentOS 7). Bumping the limit to 8 MByte should provide sufficient
headroom.

Fixes #23139.

- - - - -
c74b38a3 by Ben Gamari at 2024-03-09T21:21:46-05:00
base: Bump version to 4.20.0.0

- - - - -
b2937fc3 by Ben Gamari at 2024-03-09T21:21:46-05:00
ghc-internal: Set initial version at 9.1001.0

This provides PVP compliance while maintaining a clear correspondence
between GHC releases and `ghc-internal` versions.

- - - - -
4ae7d868 by Ben Gamari at 2024-03-09T21:21:46-05:00
ghc-prim: Bump version to 0.11.0

- - - - -
50798dc6 by Ben Gamari at 2024-03-09T21:21:46-05:00
template-haskell: Bump version to 2.22.0.0

- - - - -
8564f976 by Ben Gamari at 2024-03-09T21:21:46-05:00
base-exports: Accommodate spurious whitespace changes in 32-bit output

It appears that this was

- - - - -
9d4f0e98 by Ben Gamari at 2024-03-09T21:21:46-05:00
users-guide: Move exception backtrace relnotes to 9.10

This was previously mistakenly added to the GHC 9.8 release notes.

- - - - -
145eae60 by Ben Gamari at 2024-03-09T21:21:46-05:00
gitlab/rel_eng: Fix name of Rocky8 artifact

- - - - -
39c2a630 by Ben Gamari at 2024-03-09T21:21:46-05:00
gitlab/rel_eng: Fix path of generate_jobs_metadata

- - - - -
aed034de by Ben Gamari at 2024-03-09T21:21:46-05:00
gitlab/upload: Rework recompression

The old `combine` approach was quite fragile due to use of filename
globbing. Moreover, it didn't parallelize well. This refactoring
makes the goal more obvious, parallelizes better, and is more robust.

- - - - -
dc207d06 by Ben Gamari at 2024-03-10T08:56:08-04:00
configure: Bump GHC version to 9.11

Bumps haddock submodule.

- - - - -
8b2513e8 by Ben Gamari at 2024-03-11T01:20:03-04:00
rts/linker: Don't unload code when profiling is enabled

The heap census may contain references (e.g. `Counter.identity`) to
static data which must be available when the census is reported at the
end of execution.

Fixes #24512.

- - - - -
7810b4c3 by Ben Gamari at 2024-03-11T01:20:03-04:00
rts/linker: Don't unload native objects when dlinfo isn't available

To do so is unsafe as we have no way of identifying references to
symbols provided by the object.

Fixes #24513. Fixes #23993.

- - - - -
0590764c by Ben Gamari at 2024-03-11T01:20:39-04:00
rel_eng/upload: Purge both $rel_name/ and $ver/

This is necessary for prereleases, where GHCup accesses the release via
`$ver/`

- - - - -
b85a4631 by Brandon Chinn at 2024-03-12T19:25:56-04:00
Remove duplicate code normalising slashes

- - - - -
c91946f9 by Brandon Chinn at 2024-03-12T19:25:56-04:00
Simplify regexes with raw strings

- - - - -
1a5f53c6 by Brandon Chinn at 2024-03-12T19:25:57-04:00
Don't normalize backslashes in characters

- - - - -
7ea971d3 by Andrei Borzenkov at 2024-03-12T19:26:32-04:00
Fix compiler crash caused by implicit RHS quantification in type synonyms (#24470)

- - - - -
39f3ac3e by Cheng Shao at 2024-03-12T19:27:11-04:00
Revert "compiler: make genSym use C-based atomic increment on non-JS 32-bit platforms"

This reverts commit 615eb855416ce536e02ed935ecc5a6f25519ae16. It was
originally intended to fix #24449, but it was merely sweeping the bug
under the rug. 3836a110577b5c9343915fd96c1b2c64217e0082 has properly
fixed the fragile test, and we no longer need the C version of genSym.
Furthermore, the C implementation causes trouble when compiling with
clang that targets i386 due to alignment warning and libatomic linking
issue, so it makes sense to revert it.

- - - - -
e6bfb85c by Cheng Shao at 2024-03-12T19:27:11-04:00
compiler: fix out-of-bound memory access of genSym on 32-bit

This commit fixes an unnoticed out-of-bound memory access of genSym on
32-bit. ghc_unique_inc is 32-bit sized/aligned on 32-bit platforms,
but we mistakenly treat it as a Word64 pointer in genSym, and
therefore will accidentally load 2 garbage higher bytes, or with a
small but non-zero chance, overwrite something else in the data
section depends on how the linker places the data segments. This
regression was introduced in !11802 and fixed here.

- - - - -
77171cd1 by Ben Orchard at 2024-03-14T09:00:40-04:00
Note mutability of array and address access primops

Without an understanding of immutable vs. mutable memory, the index
primop family have a potentially non-intuitive type signature:

    indexOffAddr :: Addr# -> Int# -> a
    readOffAddr  :: Addr# -> Int# -> State# d -> (# State# d, a #)

indexOffAddr# might seem like a free generality improvement, which it
certainly is not!

This change adds a brief note on mutability expectations for most
index/read/write access primops.

- - - - -
7da7f8f6 by Alan Zimmerman at 2024-03-14T09:01:15-04:00
EPA: Fix regression discarding comments in contexts

Closes #24533

- - - - -
89166ff5 by Simon Peyton Jones at 2024-03-14T16:07:33+00:00
Several improvements to the handling of coercions

* Make `mkSymCo` and `mkInstCo` smarter
  Fixes #23642

* Fix return role of `SelCo` in the coercion optimiser.
  Fixes #23617

* Make the coercion optimiser `opt_trans_rule` work better for newtypes
  Fixes #23619

- - - - -
232eea83 by Simon Peyton Jones at 2024-03-14T16:07:33+00:00
Simplifier improvements

This MR started as: allow the simplifer to do more in one pass,
arising from places I could see the simplifier taking two iterations
where one would do.  But it turned into a larger project, because
these changes unexpectedly made inlining blow up, especially join
points in deeply-nested cases.

The net result is good: a 1.5% improvement in compile time.  The table
below shows changes over 1%.

The main changes are:

* The SimplEnv now has a seInlineDepth field, which says how deep
  in unfoldings we are.  See Note [Inline depth] in Simplify.Env

* Avoid repeatedly simplifying coercions.
  see Note [Avoid re-simplifying coercions] in Simplify.Iteration
  As you'll see from the Note, this makes use of the seInlineDepth.

* Allow Simplify.Utils.postInlineUnconditionally to inline variables
  that are used exactly once. See Note [Post-inline for single-use things].

* Allow Simplify.Iteration.simplAuxBind to inline used-once things.
  This is another part of Note [Post-inline for single-use things], and
  is really good for reducing simplifier iterations in situations like
      case K e of { K x -> blah }
  wher x is used once in blah.

* Make GHC.Core.SimpleOpt.exprIsConApp_maybe do some simple case
  elimination.  Note [Case elim in exprIsConApp_maybe]

* Many new or rewritten Notes.  E.g. Note [Avoiding simplifying repeatedly]

Join points
~~~~~~~~~~~
* Be very careful about inlining join points. See
  Note [Duplicating join points] in GHC.Core.Opt.Simplify.Iteration

* When making join points, don't do so if the join point is so small
  it will immediately be inlined; check uncondInlineJoin.

* When considering inlining a join point, never do so unless
  there is a positive gain: see (DJ5) in Note [Duplicating join points].

* Do not float join points at all, except to top level.
  See GHC.Core.Opt.SetLevels.dontFloatNonRec

* Do not add an unfolding to a join point at birth.  This is a tricky one
  and has a long Note [Do not add unfoldings to join points at birth]
  It shows up in two places
  - In `mkDupableAlt` do not add an inlining
  - (trickier) In `simplLetUnfolding` don't add an unfolding for a
    fresh join point
  I am not fully satisifed with this, but it works and is well documented.

* In GHC.Core.Unfold.sizeExpr, make jumps small, so that we don't penalise
  having a non-inlined join point.

* Use plan A for dataToTag and tagToEnum

I discovered that GHC.HsToCore.Pmc.Solver.Types.trvVarInfo was very
delicately balanced.  It's a small, heavily used, overloaded function
and it's important that it inlines. By a fluke it was before, but at
various times in my journey it stopped doing so.  So I added an INLINE
pragma to it.

    Metrics: compile_time/bytes allocated
    ------------------------------------------------
           CoOpt_Singletons(normal)   -8.2% GOOD
                LargeRecord(normal)  -22.7% GOOD
                  PmSeriesS(normal)   -4.1%
                  PmSeriesT(normal)   -3.1%
                  PmSeriesV(normal)   -1.6%
                     T11195(normal)   -1.9%
                     T12227(normal)  -19.9% GOOD
                     T12545(normal)   -5.4%
                     T12707(normal)   -2.1% GOOD
                 T13253-spj(normal)  -13.1% GOOD
                     T13386(normal)   -1.6%
                     T14766(normal)   -2.2% GOOD
                    T15630a(normal)          NEW
                     T15703(normal)  -13.5% GOOD
                     T16577(normal)   -4.3% GOOD
                     T17096(normal)   -4.4%
                     T17516(normal)   -0.2%
                     T18223(normal)  -16.3% GOOD
                     T18282(normal)   -5.3% GOOD
                     T18730(optasm)          NEW
                     T18923(normal)   -3.7% GOOD
                    T21839c(normal)   -2.3% GOOD
                      T3064(normal)   -1.3%
                      T5030(normal)  -16.1% GOOD
                   T5321Fun(normal)   -1.5%
                      T6048(optasm)  -11.8% GOOD
                       T783(normal)   -1.4%
                      T8095(normal)   -5.9% GOOD
                      T9630(normal)   -5.1% GOOD

                      T9020(optasm)   +1.5%
                    T18698a(normal)   +1.5%  BAD
                     T14683(normal)   +1.2%
        DsIncompleteRecSel3(normal)   +1.2%
MultiComponentModulesRecomp(normal)   +1.0%
    MultiLayerModulesRecomp(normal)   +1.9%
   MultiLayerModulesTH_Make(normal)   +1.4%
                     T10421(normal)   +1.9%  BAD
                    T10421a(normal)   +3.0%
                     T13056(optasm)   +1.1%
                     T13253(normal)   +1.0%
                      T1969(normal)   +1.1%  BAD
                     T15304(normal)   +1.7%
                      T9675(optasm)   +1.2%
                      T9961(normal)   +2.4%  BAD

                          geo. mean   -1.5%
                          minimum    -22.7%
                          maximum     +3.0%
Metric Decrease:
    CoOpt_Singletons
    LargeRecord
    T12227
    T12707
    T12990
    T13253-spj
    T13536a
    T14766
    T15703
    T16577
    T18223
    T18282
    T18923
    T21839c
    T5030
    T6048
    T8095
    T9630
Metric Increase:
    T10421
    T18698a
    T1969
    T9961

- - - - -
55455474 by Simon Peyton Jones at 2024-03-14T16:07:33+00:00
Improve postInlineUnconditionally

This commit adds two things to postInlineUnconditionally:

1. Do not postInlineUnconditionally join point, ever.
   Doing so does not reduce allocation, which is the main point,
   and with join points that are used a lot it can bloat code.
   See point (1) of Note [Duplicating join points] in
   GHC.Core.Opt.Simplify.Iteration.

2. Do not postInlineUnconditionally a strict (demanded) binding.
   It will not allocate a thunk (it'll turn into a case instead)
   so again the main point of inlining it doesn't hold.  Better
   to check per-call-site.

- - - - -
b1163fb7 by Simon Peyton Jones at 2024-03-14T16:07:33+00:00
More wibbles

* Inline join points whose RHS just calls another join point
* Don't float join points at all (SetLevels)
* Ensure that WorkWrap preserves lambda binders, in case of join points

- - - - -
329c3e58 by Simon Peyton Jones at 2024-03-14T16:07:33+00:00
Unused variable wibbles

- - - - -
e239a94a by Simon Peyton Jones at 2024-03-14T16:07:33+00:00
More import wibbles

- - - - -
adddc6aa by Simon Peyton Jones at 2024-03-14T16:07:33+00:00
More imports

- - - - -
b01b7089 by Simon Peyton Jones at 2024-03-14T16:07:33+00:00
More wibbles

- - - - -
70ae1bbf by Simon Peyton Jones at 2024-03-14T16:07:33+00:00
More on floating join points

* Get rid of the "join ceiling" which I have always hated
* Float joins to top level in final pass only
    (needs documenting--see my GHC log)
* Refactor wantToFloat so that it applies to Rec and NonRec uniformly

- - - - -
660ce223 by Simon Peyton Jones at 2024-03-14T16:07:33+00:00
Comments about floating joins

- - - - -
5ca6974d by Simon Peyton Jones at 2024-03-14T16:07:33+00:00
Improve occurrence analyis for bottoming function calls

See Note [Bottoming function calls]

- - - - -
045227d7 by Simon Peyton Jones at 2024-03-14T16:07:33+00:00
Test output wibbles

- - - - -
5fdcd133 by Simon Peyton Jones at 2024-03-14T16:07:34+00:00
More testsuite wibbles

- - - - -
86bf6d2f by Simon Peyton Jones at 2024-03-14T16:07:34+00:00
Float recursive joins to top level

This seems be be a net win.   Example
    joinrec { f x = ..f x'... } in f v
Despite Note [Floating join point bindings]

- - - - -
9fb899b8 by Simon Peyton Jones at 2024-03-14T16:07:34+00:00
Inline join points that have evaluated things at the use site.

This helps quite a bit with wheel-sieve1.  Example

   let x = <small thunk> in
   join $j = (x,y) in
   case z of
     A -> case x of
            P -> $j
            Q -> blah
     B -> x
     C -> True

Here `x` can't be duplicated into the branches becuase it is used
in both the join point and the A branch.  But if we inline $j we get

   let x = <small thunk> in
   join $j = (x,y) in
   case z of
     A -> case x of x'
            P -> (x', y)
            Q -> blah
     B -> x
     C -> True

and now we /can/ duplicate x into the branches.

- - - - -
7b20d3a7 by Simon Peyton Jones at 2024-03-14T16:07:34+00:00
Two small things

* isConLikeUnfolding is false for OtherCon
* Evaluated args look like NonTrivArg not ValueArg

See GHC log 15 Feb

- - - - -
bb585b86 by Simon Peyton Jones at 2024-03-14T16:07:34+00:00
Further careful changes

- - - - -
e18261b5 by Simon Peyton Jones at 2024-03-14T16:07:51+00:00
Try a more clever discard-eval

Addresses programs like this

  f xs = xs `seq`
         (let t = reverse $ reverse $ reverse $ reverse $ reverse $ reverse xs in
          case xs of
            [] ->  (t,True)
            (_:_) -> (t,False))

Also including the case where t is a join point.

Relates to #24251.  See GHC Log 13 March

- - - - -
401113c9 by Simon Peyton Jones at 2024-03-14T16:08:09+00:00
Wibbles

- - - - -


22 changed files:

- .gitlab-ci.yml
- .gitlab/rel_eng/default.nix
- .gitlab/rel_eng/fetch-gitlab-artifacts/fetch_gitlab.py
- .gitlab/rel_eng/mk-ghcup-metadata/README.mkd
- + .gitlab/rel_eng/recompress-all
- .gitlab/rel_eng/upload.sh
- compiler/GHC.hs
- compiler/GHC/Builtin/primops.txt.pp
- compiler/GHC/Core.hs
- compiler/GHC/Core/Coercion.hs
- compiler/GHC/Core/Coercion/Opt.hs
- compiler/GHC/Core/Opt/Arity.hs
- compiler/GHC/Core/Opt/FloatOut.hs
- compiler/GHC/Core/Opt/Monad.hs
- compiler/GHC/Core/Opt/OccurAnal.hs
- compiler/GHC/Core/Opt/Pipeline.hs
- compiler/GHC/Core/Opt/SetLevels.hs
- compiler/GHC/Core/Opt/Simplify.hs
- compiler/GHC/Core/Opt/Simplify/Env.hs
- compiler/GHC/Core/Opt/Simplify/Inline.hs
- compiler/GHC/Core/Opt/Simplify/Iteration.hs
- compiler/GHC/Core/Opt/Simplify/Monad.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/a33476b9bdca731d1a90466fe866b417f2cdd09c...401113c9731c7dcd47e5f2e39ffb6c5ee3975af4

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/a33476b9bdca731d1a90466fe866b417f2cdd09c...401113c9731c7dcd47e5f2e39ffb6c5ee3975af4
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/20240314/91401caf/attachment-0001.html>


More information about the ghc-commits mailing list