[Git][ghc/ghc][wip/bump-win32-tarballs] 1812 commits: rts: Consolidate RtsSymbols from libc

Ben Gamari (@bgamari) gitlab at gitlab.haskell.org
Wed Jan 11 02:51:19 UTC 2023



Ben Gamari pushed to branch wip/bump-win32-tarballs at Glasgow Haskell Compiler / GHC


Commits:
e2b60be8 by Ben Gamari at 2022-01-15T03:41:16-05:00
rts: Consolidate RtsSymbols from libc

Previously (9ebda74ec5331911881d734b21fbb31c00a0a22f) `environ` was
added to `RtsSymbols` to ensure that environment was correctly
propagated when statically linking. However, this introduced #20577
since platforms are inconsistent in whether they provide a prototype for
`environ`. I fixed this by providing a prototype but while doing so
dropped symbol-table entry, presumably thinking that it was redundant
due to the entry in the mingw-specific table.

Here I reintroduce the symbol table entry for `environ` and move libc
symbols shared by Windows and Linux into a new macro,
`RTS_LIBC_SYMBOLS`, avoiding this potential confusion.

- - - - -
0dc72395 by Tamar Christina at 2022-01-15T03:41:55-05:00
winio: fix heap corruption and various leaks.

- - - - -
4031ef62 by Eric Lindblad at 2022-01-15T20:11:55+00:00
wikipedia link
- - - - -
a13aff98 by Eric Lindblad at 2022-01-17T08:25:51-05:00
ms link
- - - - -
f161e890 by sheaf at 2022-01-17T14:52:50+00:00
Use diagnostic infrastructure in GHC.Tc.Errors

- - - - -
18c797b8 by Jens Petersen at 2022-01-18T16:12:14-05:00
hadrian BinaryDist: version ghc in ghciScriptWrapper

like we do for the non-Hadrian wrapper script.
Otherwise if $bindir/ghc is a different ghc version then versioned ghci will incorrectly run the other ghc version instead.
(Normally this would only happen if there are parallel ghc versions installed in bindir.)
All the other wrapper scripts already have versioned executablename
- - - - -
310424d0 by Matthew Pickering at 2022-01-18T16:12:50-05:00
Correct type of static forms in hsExprType

The simplest way to do this seemed to be to persist the whole type in
the extension field from the typechecker so that the few relevant places

 * Desugaring can work out the return type by splitting this type rather
   than calling `dsExpr` (slightly more efficient).
 * hsExprType can just return the correct type.
 * Zonking has to now zonk the type as well

The other option we considered was wiring in StaticPtr but that is
actually quite tricky because StaticPtr refers to StaticPtrInfo which
has field selectors (which we can't easily wire in).

Fixes #20150

- - - - -
7ec783de by Matthew Pickering at 2022-01-18T16:12:50-05:00
Add test for using type families with static pointers

Issue was reported on #13306

- - - - -
2d205154 by Sebastian Graf at 2022-01-18T16:13:25-05:00
Stricten the Strict State monad

I found it weird that most of the combinators weren't actually strict. Making
`pure` strict in the state should hopefully give Nested CPR an easier time to
unbox the nested state.

- - - - -
5a6efd21 by Ben Gamari at 2022-01-18T16:14:01-05:00
rts/winio: Fix #18382

Here we refactor WinIO's IO completion scheme, squashing a memory leak
and fixing #18382.
To fix #18382 we drop the special thread status introduced for IoPort
blocking, BlockedOnIoCompletion, as well as drop the non-threaded RTS's
special dead-lock detection logic (which is redundant to the GC's
deadlock detection logic), as proposed in #20947.

Previously WinIO relied on foreign import ccall "wrapper" to create an
adjustor thunk which can be attached to the OVERLAPPED structure passed
to the operating system. It would then use foreign import ccall
"dynamic" to back out the original continuation from the adjustor. This
roundtrip is significantly more expensive than the alternative, using a
StablePtr. Furthermore, the implementation let the adjustor leak,
meaning that every IO request would leak a page of memory.

Fixes T18382.

- - - - -
01254ceb by Matthew Pickering at 2022-01-18T16:14:37-05:00
Add note about heap invariant

Closed #20904

- - - - -
21510698 by Sergey Vinokurov at 2022-01-18T16:15:12-05:00
Improve detection of lld linker

Newer lld versions may include vendor info in --version output and
thus the version string may not start with ‘LLD’.

Fixes #20907

- - - - -
95e7964b by Peter Trommler at 2022-01-18T20:46:08-05:00
Fix T20638 on big-endian architectures

The test reads a 16 bit value from an array of 8 bit values. Naturally,
that leads to different values read on big-endian architectures than
on little-endian. In this case the value read is 0x8081 on big-endian
and 0x8180 on little endian. This patch changes the argument of the `and`
machop to mask bit 7 which is the only bit different. The test still checks
that bit 15 is zero, which was the original issue in #20638.

Fixes #20906.

- - - - -
fd0019a0 by Eric Lindblad at 2022-01-18T20:46:48-05:00
ms and gh links
- - - - -
85dc61ee by Zubin Duggal at 2022-01-18T20:47:23-05:00
ci: Fix subtlety with  not taking effect because of time_it (#20898)

- - - - -
592e4113 by Anselm Schüler at 2022-01-19T13:31:49-05:00
Note that ImpredicativeTypes doesn’t allow polymorphic instances

See #20939

- - - - -
3b009e1a by Ben Gamari at 2022-01-19T13:32:25-05:00
base: Add CTYPE pragmas to all foreign types

Fixes #15531 by ensuring that we know the corresponding C type for all
marshalling wrappers.

Closes #15531.

- - - - -
516eeb9e by Robert Hensing at 2022-01-24T21:28:24-05:00
Add -fcompact-unwind

This gives users the choice to enable __compact_unwind sections
when linking. These were previously hardcoded to be removed.

This can be used to solved the problem "C++ does not catch
exceptions when used with Haskell-main and linked by ghc",
https://gitlab.haskell.org/ghc/ghc/-/issues/11829

It does not change the default behavior, because I can not
estimate the impact this would have.

When Apple first introduced the compact unwind ABI, a number of
open source projects have taken the easy route of disabling it,
avoiding errors or even just warnings shortly after its
introduction.

Since then, about a decade has passed, so it seems quite possible
that Apple itself, and presumably many programs with it, have
successfully switched to the new format, to the point where the
old __eh_frame section support is in disrepair. Perhaps we should
get along with the program, but for now we can test the waters
with this flag, and use it to fix packages that need it.

- - - - -
5262b1e5 by Robert Hensing at 2022-01-24T21:28:24-05:00
Add test case for C++ exception handling

- - - - -
a5c94092 by Sebastian Graf at 2022-01-24T21:29:00-05:00
Write Note [Strict State monad] to explain what G.U.M.State.Strict does

As requested by Simon after review of !7342.

I also took liberty to define the `Functor` instance by hand, as the derived one
subverts the invariants maintained by the pattern synonym (as already stated in
`Note [The one-shot state monad trick]`).

- - - - -
9b0d56d3 by Eric Lindblad at 2022-01-24T21:29:38-05:00
links
- - - - -
4eac8e72 by Ben Gamari at 2022-01-24T21:30:13-05:00
ghc-heap: Drop mention of BlockedOnIOCompletion

Fixes bootstrap with GHC 9.0 after 5a6efd218734dbb5c1350531680cd3f4177690f1

- - - - -
7d7b9a01 by Ryan Scott at 2022-01-24T21:30:49-05:00
Hadrian: update the index-state to allow building with GHC 9.0.2

Fixes #20984.

- - - - -
aa50e118 by Peter Trommler at 2022-01-24T21:31:25-05:00
testsuite: Mark test that require RTS linker

- - - - -
871ce2a3 by Matthew Pickering at 2022-01-25T17:27:30-05:00
ci: Move (most) deb9 jobs to deb10

deb9 is now end-of-life so we are dropping support for producing
bindists.

- - - - -
9d478d51 by Ryan Scott at 2022-01-25T17:28:06-05:00
DeriveGeneric: look up datacon fixities using getDataConFixityFun

Previously, `DeriveGeneric` would look up the fixity of a data constructor
using `getFixityEnv`, but this is subtly incorrect for data constructors
defined in external modules. This sort of situation can happen with
`StandaloneDeriving`, as noticed in #20994. In fact, the same bug has occurred
in the past in #9830, and while that bug was fixed for `deriving Read` and
`deriving Show`, the fix was never extended to `DeriveGeneric` due to an
oversight. This patch corrects that oversight.

Fixes #20994.

- - - - -
112e9e9e by Zubin Duggal at 2022-01-25T17:28:41-05:00
Fix Werror on alpine

- - - - -
781323a3 by Matthew Pickering at 2022-01-25T17:29:17-05:00
Widen T12545 acceptance window

This test has been the scourge of contributors for a long time.

It has caused many failed CI runs and wasted hours debugging a test
which barely does anything. The fact is does nothing is the reason for
the flakiness and it's very sensitive to small changes in initialisation costs,
in particular adding wired-in things can cause this test to fluctuate
quite a bit.

Therefore we admit defeat and just bump the threshold up to 10% to catch
very large regressions but otherwise don't care what this test does.

Fixes #19414

- - - - -
e471a680 by sheaf at 2022-01-26T12:01:45-05:00
Levity-polymorphic arrays and mutable variables

This patch makes the following types levity-polymorphic in their
last argument:

  - Array# a, SmallArray# a, Weak# b, StablePtr# a, StableName# a

  - MutableArray# s a, SmallMutableArray# s a,
    MutVar# s a, TVar# s a, MVar# s a, IOPort# s a

The corresponding primops are also made levity-polymorphic, e.g.
`newArray#`, `readArray#`, `writeMutVar#`, `writeIOPort#`, etc.

Additionally, exception handling functions such as `catch#`, `raise#`,
`maskAsyncExceptions#`,... are made levity/representation-polymorphic.

Now that Array# and MutableArray# also work with unlifted types,
we can simply re-define ArrayArray# and MutableArrayArray# in terms
of them. This means that ArrayArray# and MutableArrayArray# are no
longer primitive types, but simply unlifted newtypes around Array# and
MutableArrayArray#.

This completes the implementation of the Pointer Rep proposal
  https://github.com/ghc-proposals/ghc-proposals/pull/203

Fixes #20911

-------------------------
Metric Increase:
    T12545
-------------------------

-------------------------
Metric Decrease:
    T12545
-------------------------

- - - - -
6e94ba54 by Andreas Klebinger at 2022-01-26T12:02:21-05:00
CorePrep: Don't try to wrap partial applications of primops in profiling ticks.

This fixes #20938.

- - - - -
b55d7db3 by sheaf at 2022-01-26T12:03:01-05:00
Ensure that order of instances doesn't matter

The insert_overlapping used in lookupInstEnv used to return different
results depending on the order in which instances were processed.
The problem was that we could end up discarding an overlapping instance
in favour of a more specific non-overlapping instance. This is a
problem because, even though we won't choose the less-specific instance
for matching, it is still useful for pruning away other instances,
because it has the overlapping flag set while the new instance doesn't.

In insert_overlapping, we now keep a list of "guard" instances, which
are instances which are less-specific that one that matches (and hence
which we will discard in the end), but want to keep around solely for
the purpose of eliminating other instances.

Fixes #20946

- - - - -
61f62062 by sheaf at 2022-01-26T12:03:40-05:00
Remove redundant SOURCE import in FitTypes

Fixes #20995

- - - - -
e8405829 by sheaf at 2022-01-26T12:04:15-05:00
Fix haddock markup in GHC.Tc.Errors.Types
- - - - -
590a2918 by Simon Peyton Jones at 2022-01-26T19:45:22-05:00
Make RULE matching insensitive to eta-expansion

This patch fixes #19790 by making the rule matcher do on-the-fly
eta reduction.  See Note [Eta reduction the target] in GHC.Core.Rules

I found I also had to careful about casts when matching; see
Note [Casts in the target] and Note [Casts in the template]

Lots more comments and Notes in the rule matcher

- - - - -
c61ac4d8 by Matthew Pickering at 2022-01-26T19:45:58-05:00
alwaysRerun generation of ghcconfig

This file needs to match exactly what is passed as the testCompiler.
Before this change the settings for the first compiler to be tested
woudl be stored and not regenerated if --test-compiler changed.

- - - - -
b5132f86 by Matthew Pickering at 2022-01-26T19:45:58-05:00
Pass config.stage argument to testsuite

- - - - -
83d3ad31 by Zubin Duggal at 2022-01-26T19:45:58-05:00
hadrian: Allow testing of the stage1 compiler (#20755)

- - - - -
a5924b38 by Joachim Breitner at 2022-01-26T19:46:34-05:00
Simplifier: Do the right thing if doFloatFromRhs = False

If `doFloatFromRhs` is `False` then the result from `prepareBinding`
should not be used. Previously it was in ways that are silly (but not
completly wrong, as the simplifier would clean that up again, so no
test case).

This was spotted by Simon during a phone call.

Fixes #20976

- - - - -
ce488c2b by Simon Peyton Jones at 2022-01-26T19:47:09-05:00
Better occurrence analysis with casts

This patch addresses #20988 by refactoring the way the
occurrence analyser deals with lambdas.

Previously it used collectBinders to split off a group of binders,
and deal with them together.  Now I deal with them one at a time
in occAnalLam, which allows me to skip casts easily.  See
    Note [Occurrence analysis for lambda binders]
about "lambda-groups"

This avoidance of splitting out a list of binders has some good
consequences.  Less code, more efficient, and I think, more clear.

The Simplifier needed a similar change, now that lambda-groups
can inlude casts.  It turned out that I could simplify the code
here too, in particular elminating the sm_bndrs field of StrictBind.
Simpler, more efficient.

Compile-time metrics improve slightly; here are the ones that are
+/- 0.5% or greater:

                                  Baseline
              Test    Metric         value     New value Change
--------------------------------------------------------------------
   T11303b(normal) ghc/alloc    40,736,702    40,543,992  -0.5%
    T12425(optasm) ghc/alloc    90,443,459    90,034,104  -0.5%
    T14683(normal) ghc/alloc 2,991,496,696 2,956,277,288  -1.2%
    T16875(normal) ghc/alloc    34,937,866    34,739,328  -0.6%
   T17977b(normal) ghc/alloc    37,908,550    37,709,096  -0.5%
    T20261(normal) ghc/alloc   621,154,237   618,312,480  -0.5%
     T3064(normal) ghc/alloc   190,832,320   189,952,312  -0.5%
     T3294(normal) ghc/alloc 1,604,674,178 1,604,608,264  -0.0%
   T5321FD(normal) ghc/alloc   270,540,489   251,888,480  -6.9% GOOD
  T5321Fun(normal) ghc/alloc   300,707,814   281,856,200  -6.3% GOOD
     WWRec(normal) ghc/alloc   588,460,916   585,536,400  -0.5%

         geo. mean                                        -0.3%

Metric Decrease:
    T5321FD
    T5321Fun

- - - - -
4007905d by Roland Senn at 2022-01-26T19:47:47-05:00
Cleanup tests in directory ghci.debugger. Fixes #21009

* Remove wrong comment about panic in `break003.script`.
* Improve test `break008`.
* Add test `break028` to `all.T`
* Fix wrong comments in `print019.script`, `print026.script` and `result001.script`.
* Remove wrong comments from `print024.script` and `print031.script`.
* Replace old module name with current name in `print035.script`.

- - - - -
3577defb by Matthew Pickering at 2022-01-26T19:48:22-05:00
ci: Move source-tarball and test-bootstrap into full-build

- - - - -
6e09b3cf by Matthew Pickering at 2022-01-27T02:39:35-05:00
ci: Add ENABLE_NUMA flag to explicitly turn on libnuma dependency

In recent releases a libnuma dependency has snuck into our bindists
because the images have started to contain libnuma. We now explicitly
pass `--disable-numa` to configure unless explicitly told not to by
using the `ENABLE_NUMA` environment variable.

So this is tested, there is one random validate job which builds with
--enable-numa so that the code in the RTS is still built.

Fixes #20957 and #15444

- - - - -
f4ce4186 by Simon Peyton Jones at 2022-01-27T02:40:11-05:00
Improve partial signatures

As #20921 showed, with partial signatures, it is helpful to use the
same algorithm (namely findInferredDiff) for
* picking the constraints to retain for the /group/
  in Solver.decideQuantification
* picking the contraints to retain for the /individual function/
  in Bind.chooseInferredQuantifiers

This is still regrettably declicate, but it's a step forward.

- - - - -
0573aeab by Simon Peyton Jones at 2022-01-27T02:40:11-05:00
Add an Outputable instance for RecTcChecker

- - - - -
f0adea14 by Ryan Scott at 2022-01-27T02:40:47-05:00
Expand type synonyms in markNominal

`markNominal` is repsonsible for setting the roles of type variables
that appear underneath an `AppTy` to be nominal. However, `markNominal`
previously did not expand type synonyms, so in a data type like this:

```hs
data M f a = MkM (f (T a))

type T a = Int
```

The `a` in `M f a` would be marked nominal, even though `T a` would simply
expand to `Int`. The fix is simple: call `coreView` as appropriate in
`markNominal`. This is much like the fix for #14101, but in a different spot.

Fixes #20999.

- - - - -
18df4013 by Simon Peyton Jones at 2022-01-27T08:22:30-05:00
Define and use restoreLclEnv

This fixes #20981.  See Note [restoreLclEnv vs setLclEnv]
in GHC.Tc.Utils.Monad.

I also use updLclEnv rather than get/set when I can, because it's
then much clearer that it's an update rather than an entirely new
TcLclEnv coming from who-knows-where.

- - - - -
31088dd3 by David Feuer at 2022-01-27T08:23:05-05:00
Add test supplied in T20996 which uses data family result kind polymorphism

David (@treeowl) writes:

> Following @kcsongor, I've used ridiculous data family result kind
> polymorphism in `linear-generics`, and am currently working on getting
> it into `staged-gg`. If it should be removed, I'd appreciate a heads up,
> and I imagine Csongor would too.
>
> What do I need by ridiculous polymorphic result kinds? Currently, data
> families are allowed to have result kinds that end in `Type` (or maybe
> `TYPE r`? I'm not sure), but not in concrete data kinds. However, they
> *are* allowed to have polymorphic result kinds. This leads to things I
> think most of us find at least quite *weird*. For example, I can write
>
> ```haskell
> data family Silly :: k
> data SBool :: Bool -> Type where
>   SFalse :: SBool False
>   STrue :: SBool True
>   SSSilly :: SBool Silly
> type KnownBool b where
>   kb :: SBool b
> instance KnownBool False where kb = SFalse
> instance KnownBool True where kb = STrue
> instance KnownBool Silly where kb = Silly
> ```
>
> Basically, every kind now has potentially infinitely many "legit" inhabitants.
>
> As horrible as that is, it's rather useful for GHC's current native
> generics system. It's possible to use these absurdly polymorphic result
> kinds to probe the structure of generic representations in a relatively
> pleasant manner. It's a sort of "formal type application" reminiscent of
> the notion of a formal power series (see the test case below). I suspect
> a system more like `kind-generics` wouldn't need this extra probing
> power, but nothing like that is natively available as yet.
>
> If the ridiculous result kind polymorphism is banished, we'll still be
> able to do what we need as long as we have stuck type families. It's
> just rather less ergonomical: a stuck type family has to be used with a
> concrete marker type argument.

Closes #20996

Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com>

- - - - -
8fd2ac25 by Andreas Abel at 2022-01-27T18:34:54-05:00
Whitespace only

- - - - -
7a854743 by Andreas Abel at 2022-01-27T18:34:54-05:00
Ctd. #18087: complete :since: info for all warnings in users guide

Some warnings have been there "forever" and I could not trace back the
exact genesis, so I wrote "since at least 5.04".

The flag `helpful-errors` could have been added in 7.2 already.  I
wrote 7.4 since I have no 7.2 available and it is not recognized by 7.0.

- - - - -
f75411e8 by Andreas Abel at 2022-01-27T18:34:54-05:00
Re #18087 user's guide: add a note that -Wxxx used to be -fwarn-xxx

The warning option syntax -W was introduced in GHC 8.

The note should clarify what e.g. "since 7.6" means in connection with
"-Wxxx": That "-fwarn-xxx" was introduced in 7.6.1.

[ci skip]

- - - - -
3cae7fde by Peter Trommler at 2022-01-27T18:35:30-05:00
testsuite: Fix AtomicPrimops test on big endian

- - - - -
6cc6080c by Ben Gamari at 2022-01-27T18:36:05-05:00
users-guide: Document GHC_CHARENC environment variable

As noted in #20963, this was introduced in
1b56c40578374a15b4a2593895710c68b0e2a717 but was no documentation
was added at that point.

Closes #20963.
- - - - -
ee21e2de by Ben Gamari at 2022-01-27T18:36:41-05:00
rts: Clean up RTS flags usage message

Align flag descriptions and acknowledge that some flags may not be
available unless the user linked with `-rtsopts` (as noted in #20961).

Fixes #20961.

- - - - -
7f8ce19e by Simon Peyton Jones at 2022-01-27T18:37:17-05:00
Fix getHasGivenEqs

The second component is supposed to be "insoluble equalities arising
from givens".  But we were getting wanteds too; and that led to an
outright duplication of constraints.  It's not harmful, but it's not
right either.

I came across this when debugging something else.  Easily fixed.

- - - - -
f9ef2d26 by Simon Peyton Jones at 2022-01-27T18:37:17-05:00
Set the TcLclEnv when solving a ForAll constraint

Fix a simple omission in GHC.Tc.Solver.Canonical.solveForAll,
where we ended up with the wrong TcLclEnv captured in an implication.

Result: unhelpful error message (#21006)

- - - - -
bc6ba8ef by Sylvain Henry at 2022-01-28T12:14:41-05:00
Make most shifts branchless

- - - - -
62a6d037 by Simon Peyton Jones at 2022-01-28T12:15:17-05:00
Improve boxity in deferAfterPreciseException

As #20746 showed, the demand analyser behaved badly in a key I/O
library (`GHC.IO.Handle.Text`), by unnessarily boxing and reboxing.

This patch adjusts the subtle function deferAfterPreciseException;
it's quite easy, just a bit subtle.

See the new Note [deferAfterPreciseException]

And this MR deals only with Problem 2 in #20746.
Problem 1 is still open.

- - - - -
42c47cd6 by Ben Gamari at 2022-01-29T02:40:45-05:00
rts/trace: Shrink tracing flags

- - - - -
cee66e71 by Ben Gamari at 2022-01-29T02:40:45-05:00
rts/EventLog: Mark various internal globals as static

- - - - -
6b0cea29 by Ben Gamari at 2022-01-29T02:40:45-05:00
Propagate PythonCmd to make build system

- - - - -
2e29edb7 by Ben Gamari at 2022-01-29T02:40:45-05:00
rts: Refactor event types

Previously we would build the eventTypes array at runtime during RTS
initialization. However, this is completely unnecessary; it is
completely static data.

- - - - -
bb15c347 by Ben Gamari at 2022-01-29T02:40:45-05:00
rts/eventlog: Ensure that flushCount is initialized

- - - - -
268efcc9 by Matthew Pickering at 2022-01-29T02:41:21-05:00
Rework the handling of SkolemInfo

The main purpose of this patch is to attach a SkolemInfo directly to
each SkolemTv. This fixes the large number of bugs which have
accumulated over the years where we failed to report errors due to
having "no skolem info" for particular type variables. Now the origin of
each type varible is stored on the type variable we can always report
accurately where it cames from.

Fixes #20969 #20732 #20680 #19482 #20232 #19752 #10946
  #19760 #20063 #13499 #14040

The main changes of this patch are:

* SkolemTv now contains a SkolemInfo field which tells us how the
  SkolemTv was created. Used when reporting errors.

* Enforce invariants relating the SkolemInfoAnon and level of an implication (ic_info, ic_tclvl)
  to the SkolemInfo and level of the type variables in ic_skols.
    * All ic_skols are TcTyVars -- Check is currently disabled
    * All ic_skols are SkolemTv
    * The tv_lvl of the ic_skols agrees with the ic_tclvl
    * The ic_info agrees with the SkolInfo of the implication.

  These invariants are checked by a debug compiler by
  checkImplicationInvariants.

* Completely refactor kcCheckDeclHeader_sig which kept
  doing my head in. Plus, it wasn't right because it wasn't skolemising
  the binders as it decomposed the kind signature.

  The new story is described in Note [kcCheckDeclHeader_sig].  The code
  is considerably shorter than before (roughly 240 lines turns into 150
  lines).

  It still has the same awkward complexity around computing arity as
  before, but that is a language design issue.
  See Note [Arity inference in kcCheckDeclHeader_sig]

* I added new type synonyms MonoTcTyCon and PolyTcTyCon, and used
  them to be clear which TcTyCons have "finished" kinds etc, and
  which are monomorphic. See Note [TcTyCon, MonoTcTyCon, and PolyTcTyCon]

* I renamed etaExpandAlgTyCon to splitTyConKind, becuase that's a
  better name, and it is very useful in kcCheckDeclHeader_sig, where
  eta-expansion isn't an issue.

* Kill off the nasty `ClassScopedTvEnv` entirely.

Co-authored-by: Simon Peyton Jones <simon.peytonjones at gmail.com>

- - - - -
0a1d0944 by Ben Gamari at 2022-01-29T14:52:55-05:00
Drop SPARC NCG

- - - - -
313afb3d by Ben Gamari at 2022-01-29T14:52:56-05:00
A few comment cleanups

- - - - -
d85a527f by Ben Gamari at 2022-01-29T14:52:56-05:00
Rip out SPARC register support

- - - - -
c6bede69 by Ben Gamari at 2022-01-29T14:52:56-05:00
rts: Rip out SPARC support

- - - - -
a67c2471 by Ben Gamari at 2022-01-29T14:52:56-05:00
Rip out remaining SPARC support

- - - - -
5771b690 by Ben Gamari at 2022-01-29T14:52:56-05:00
CmmToAsm: Drop RegPair

SPARC was its last and only user.

- - - - -
512ed3f1 by Ben Gamari at 2022-01-29T14:52:56-05:00
CmmToAsm: Make RealReg a newtype

Now that RegPair is gone we no longer need to pay for the additional
box.

- - - - -
88fea6aa by Ben Gamari at 2022-01-29T14:52:56-05:00
rts: Drop redundant #include <Arena.h>

- - - - -
ea2a4034 by Ben Gamari at 2022-01-29T14:52:56-05:00
CmmToAsm: Drop ncgExpandTop

This was only needed for SPARC's synthetic instructions.

- - - - -
88fce740 by Ben Gamari at 2022-01-29T14:54:04-05:00
rel-notes: Note dropping of SPARC support

- - - - -
eb956cf1 by Ben Gamari at 2022-01-30T06:27:19-05:00
testsuite: Force-enable caret diagnostics in T17786

Otherwise GHC realizes that it's not attached to a proper tty and will
disable caret diagnostics.

- - - - -
d07799ab by Ben Gamari at 2022-01-30T06:27:19-05:00
testsuite: Make T7275 more robust against CCid changes

The cost-center numbers are somewhat unstable; normalise them out.

- - - - -
c76c8050 by Ben Gamari at 2022-01-30T06:27:19-05:00
rts: Don't allocate closurePtrs# pointers on C stack

Previously `closurePtrs#` would allocate an aray of the size of the
closure being decoded on the C stack. This was ripe for overflowing the
C stack overflow. This resulted in `T12492` failing on Windows.

- - - - -
3af95f7a by Ben Gamari at 2022-01-30T06:27:19-05:00
testsuite/T4029: Don't depend on echo

On Windows the `cmd.exe` shell may be used to execute the command, which
will print `ECHO is on.` instead of a newline if you give it no
argument. Avoid this by rather using `printf`.

- - - - -
3531c478 by Ben Gamari at 2022-01-30T06:27:19-05:00
Use PATH_FMT instead of %s to format `pathchar *`

A few %s occurrences have snuck in over the past months.

- - - - -
ee5c4f9d by Zubin Duggal at 2022-01-31T16:51:55+05:30
Improve migration strategy for the XDG compliance change to the GHC application
directory.

We want to always use the old path (~/.ghc/..) if it exists.
But we never want to create the old path.
This ensures that the migration can eventually be completed once older GHC
versions are no longer in circulation.

Fixes #20684, #20669, #20660

- - - - -
60a54a8f by doyougnu at 2022-01-31T18:46:11-05:00
StgToCmm: decouple DynFlags, add StgToCmmConfig

StgToCmm: add Config, remove CgInfoDownwards

StgToCmm: runC api change to take StgToCmmConfig

StgToCmm: CgInfoDownad -> StgToCmmConfig

StgToCmm.Monad: update getters/setters/withers

StgToCmm: remove CallOpts in StgToCmm.Closure

StgToCmm: remove dynflag references

StgToCmm: PtrOpts removed

StgToCmm: add TMap to config, Prof - dynflags

StgToCmm: add omit yields to config

StgToCmm.ExtCode: remove redundant import

StgToCmm.Heap: remove references to dynflags

StgToCmm: codeGen api change, DynFlags -> Config

StgToCmm: remove dynflags in Env and StgToCmm

StgToCmm.DataCon: remove dynflags references

StgToCmm: remove dynflag references in DataCon

StgToCmm: add backend avx flags to config

StgToCmm.Prim: remove dynflag references

StgToCmm.Expr: remove dynflag references

StgToCmm.Bind: remove references to dynflags

StgToCmm: move DoAlignSanitisation to Cmm.Type

StgToCmm: remove PtrOpts in Cmm.Parser.y

DynFlags: update ipInitCode api

StgToCmm: Config Module is single source of truth

StgToCmm: Lazy config breaks IORef deadlock

testsuite: bump countdeps threshold

StgToCmm.Config: strictify fields except UpdFrame

Strictifying UpdFrameOffset causes the RTS build with stage1 to
deadlock. Additionally, before the deadlock performance of the RTS
is noticeably slower.

StgToCmm.Config: add field descriptions

StgToCmm: revert strictify on Module in config

testsuite: update CountDeps tests

StgToCmm: update comment, fix exports

Specifically update comment about loopification passed into dynflags
then stored into stgToCmmConfig. And remove getDynFlags from
Monad.hs exports

Types.Name: add pprFullName function

StgToCmm.Ticky: use pprFullname, fixup ExtCode imports

Cmm.Info: revert cmmGetClosureType removal

StgToCmm.Bind: use pprFullName, Config update comments

StgToCmm: update closureDescription api

StgToCmm: SAT altHeapCheck

StgToCmm: default render for Info table, ticky

Use default rendering contexts for info table and ticky ticky, which should be independent of command line input.

testsuite: bump count deps

pprFullName: flag for ticky vs normal style output

convertInfoProvMap: remove unused parameter

StgToCmm.Config: add backend flags to config

StgToCmm.Config: remove Backend from Config

StgToCmm.Prim: refactor Backend call sites

StgToCmm.Prim: remove redundant imports

StgToCmm.Config: refactor vec compatibility check

StgToCmm.Config: add allowQuotRem2 flag

StgToCmm.Ticky: print internal names with parens

StgToCmm.Bind: dispatch ppr based on externality

StgToCmm: Add pprTickyname, Fix ticky naming

Accidently removed the ctx for ticky SDoc output. The only relevant flag
is sdocPprDebug which was accidental set to False due to using
defaultSDocContext without altering the flag.

StgToCmm: remove stateful fields in config

fixup: config: remove redundant imports

StgToCmm: move Sequel type to its own module

StgToCmm: proliferate getCallMethod updated api

StgToCmm.Monad: add FCodeState to Monad Api

StgToCmm: add second reader monad to FCode

fixup: Prim.hs: missed a merge conflict

fixup: Match countDeps tests to HEAD

StgToCmm.Monad: withState -> withCgState

To disambiguate it from mtl withState. This withState shouldn't be
returning the new state as a value. However, fixing this means tackling
the knot tying in CgState and so is very difficult since it changes when
the thunk of the knot is forced which either leads to deadlock or to
compiler panic.

- - - - -
58eccdbc by Ben Gamari at 2022-01-31T18:46:47-05:00
codeGen: Fix two buglets in -fbounds-check logic

@Bodigrim noticed that the `compareByteArray#` bounds-checking logic had
flipped arguments and an off-by-one. For the sake of clarity I also
refactored occurrences of `cmmOffset` to rather use `cmmOffsetB`. I
suspect the former should be retired.

- - - - -
584f03fa by Simon Peyton Jones at 2022-01-31T18:47:23-05:00
Make typechecker trace less strict

Fixes #21011

- - - - -
60ac7300 by Elton at 2022-02-01T12:28:49-05:00
Use braces in TH case pprint (fixes #20893)

This patch ensures that the pretty printer formats `case` statements
using braces (instead of layout) to remain consistent with the
formatting of other statements (like `do`)

- - - - -
fdda93b0 by Elton at 2022-02-01T12:28:49-05:00
Use braces in TH LambdaCase and where clauses

This patch ensures that the pretty printer formats LambdaCase and where
clauses using braces (instead of layout) to remain consistent with the
formatting of other statements (like `do` and `case`)

- - - - -
06185102 by Ben Gamari at 2022-02-01T12:29:26-05:00
Consistently upper-case "Note ["

This was achieved with

    git ls-tree --name-only HEAD -r | xargs sed -i -e 's/note \[/Note \[/g'

- - - - -
88fba8a4 by Ben Gamari at 2022-02-01T12:29:26-05:00
Fix a few Note inconsistencies

- - - - -
05548a22 by Douglas Wilson at 2022-02-02T19:26:06-05:00
rts: Address failures to inline

- - - - -
074945de by Simon Peyton Jones at 2022-02-02T19:26:41-05:00
Two small improvements in the Simplifier

As #20941 describes, this patch implements a couple of small
fixes to the Simplifier.  They make a difference principally
with -O0, so few people will notice.  But with -O0 they can
reduce the number of Simplifer iterations.

* In occurrence analysis we avoid making x = (a,b) into a loop breaker
  because we want to be able to inline x, or (more likely) do
  case-elimination. But HEAD does not treat
      x = let y = blah in (a,b)
  in the same way.  We should though, because we are going to float
  that y=blah out of the x-binding.  A one-line fix in OccurAnal.

* The crucial function exprIsConApp_maybe uses getUnfoldingInRuleMatch
  (rightly) but the latter was deeply strange.  In HEAD, if
  rule-rewriting was off (-O0) we only looked inside stable
  unfoldings. Very stupid.  The patch simplifies.

* I also noticed that in simplStableUnfolding we were failing to
  delete the DFun binders from the usage.  So I added that.

Practically zero perf change across the board, except that we get more
compiler allocation in T3064 (which is compiled with -O0). There's a
good reason: we get better code.  But there are lots of other small
compiler allocation decreases:

Metrics: compile_time/bytes allocated
---------------------
                                   Baseline
               Test    Metric         value     New value Change
-----------------------------------------------------------------
  PmSeriesG(normal) ghc/alloc    44,260,817    44,184,920  -0.2%
  PmSeriesS(normal) ghc/alloc    52,967,392    52,891,632  -0.1%
  PmSeriesT(normal) ghc/alloc    75,498,220    75,421,968  -0.1%
  PmSeriesV(normal) ghc/alloc    52,341,849    52,265,768  -0.1%
     T10421(normal) ghc/alloc   109,702,291   109,626,024  -0.1%
    T10421a(normal) ghc/alloc    76,888,308    76,809,896  -0.1%
     T10858(normal) ghc/alloc   125,149,038   125,073,648  -0.1%
     T11276(normal) ghc/alloc    94,159,364    94,081,640  -0.1%
    T11303b(normal) ghc/alloc    40,230,059    40,154,368  -0.2%
     T11822(normal) ghc/alloc   107,424,540   107,346,088  -0.1%
     T12150(optasm) ghc/alloc    76,486,339    76,426,152  -0.1%
     T12234(optasm) ghc/alloc    55,585,046    55,507,352  -0.1%
     T12425(optasm) ghc/alloc    88,343,288    88,265,312  -0.1%
     T13035(normal) ghc/alloc    98,919,768    98,845,600  -0.1%
 T13253-spj(normal) ghc/alloc   121,002,153   120,851,040  -0.1%
     T16190(normal) ghc/alloc   290,313,131   290,074,152  -0.1%
     T16875(normal) ghc/alloc    34,756,121    34,681,440  -0.2%
    T17836b(normal) ghc/alloc    45,198,100    45,120,288  -0.2%
     T17977(normal) ghc/alloc    39,479,952    39,404,112  -0.2%
    T17977b(normal) ghc/alloc    37,213,035    37,137,728  -0.2%
     T18140(normal) ghc/alloc    79,430,588    79,350,680  -0.1%
     T18282(normal) ghc/alloc   128,303,182   128,225,384  -0.1%
     T18304(normal) ghc/alloc    84,904,713    84,831,952  -0.1%
     T18923(normal) ghc/alloc    66,817,241    66,731,984  -0.1%
     T20049(normal) ghc/alloc    86,188,024    86,107,920  -0.1%
      T5837(normal) ghc/alloc    35,540,598    35,464,568  -0.2%
      T6048(optasm) ghc/alloc    99,812,171    99,736,032  -0.1%
      T9198(normal) ghc/alloc    46,380,270    46,304,984  -0.2%

          geo. mean                                        -0.0%

Metric Increase:
    T3064

- - - - -
d2cce453 by Morrow at 2022-02-02T19:27:21-05:00
Fix @since annotation on Nat

- - - - -
6438fed9 by Simon Peyton Jones at 2022-02-02T19:27:56-05:00
Refactor the escaping kind check for data constructors

As #20929 pointed out, we were in-elegantly checking for escaping
kinds in `checkValidType`, even though that check was guaranteed
to succeed for type signatures -- it's part of kind-checking a type.

But for /data constructors/ we kind-check the pieces separately,
so we still need the check.

This MR is a pure refactor, moving the test from `checkValidType` to
`checkValidDataCon`.

No new tests; external behaviour doesn't change.

- - - - -
fb05e5ac by Andreas Klebinger at 2022-02-02T19:28:31-05:00
Replace sndOfTriple with sndOf3

I also cleaned up the imports slightly while I was at it.

- - - - -
fbc77d3a by Matthew Pickering at 2022-02-02T19:29:07-05:00
testsuite: Honour PERF_BASELINE_COMMIT when computing allowed metric changes

We now get all the commits between the PERF_BASELINE_COMMIT and HEAD and
check any of them for metric changes.

Fixes #20882

- - - - -
0a82ae0d by Simon Peyton Jones at 2022-02-02T23:49:58-05:00
More accurate unboxing

This patch implements a fix for #20817.  It ensures that

* The final strictness signature for a function accurately
  reflects the unboxing done by the wrapper
  See Note [Finalising boxity for demand signatures]
  and Note [Finalising boxity for let-bound Ids]

* A much better "layer-at-a-time" implementation of the
  budget for how many worker arguments we can have
  See Note [Worker argument budget]

  Generally this leads to a bit more worker/wrapper generation,
  because instead of aborting entirely if the budget is exceeded
  (and then lying about boxity), we unbox a bit.

Binary sizes in increase slightly (around 1.8%) because of the increase
in worker/wrapper generation.  The big effects are to GHC.Ix,
GHC.Show, GHC.IO.Handle.Internals. If we did a better job of dropping
dead code, this effect might go away.

Some nofib perf improvements:

        Program           Size    Allocs   Runtime   Elapsed  TotalMem
--------------------------------------------------------------------------------
            VSD          +1.8%     -0.5%     0.017     0.017      0.0%
         awards          +1.8%     -0.1%     +2.3%     +2.3%      0.0%
         banner          +1.7%     -0.2%     +0.3%     +0.3%      0.0%
           bspt          +1.8%     -0.1%     +3.1%     +3.1%      0.0%
          eliza          +1.8%     -0.1%     +1.2%     +1.2%      0.0%
         expert          +1.7%     -0.1%     +9.6%     +9.6%      0.0%
 fannkuch-redux          +1.8%     -0.4%     -9.3%     -9.3%      0.0%
          kahan          +1.8%     -0.1%    +22.7%    +22.7%      0.0%
       maillist          +1.8%     -0.9%    +21.2%    +21.6%      0.0%
       nucleic2          +1.7%     -5.1%     +7.5%     +7.6%      0.0%
         pretty          +1.8%     -0.2%     0.000     0.000      0.0%
reverse-complem          +1.8%     -2.5%    +12.2%    +12.2%      0.0%
           rfib          +1.8%     -0.2%     +2.5%     +2.5%      0.0%
            scc          +1.8%     -0.4%     0.000     0.000      0.0%
         simple          +1.7%     -1.3%    +17.0%    +17.0%     +7.4%
  spectral-norm          +1.8%     -0.1%     +6.8%     +6.7%      0.0%
         sphere          +1.7%     -2.0%    +13.3%    +13.3%      0.0%
            tak          +1.8%     -0.2%     +3.3%     +3.3%      0.0%
           x2n1          +1.8%     -0.4%     +8.1%     +8.1%      0.0%
--------------------------------------------------------------------------------
            Min          +1.1%     -5.1%    -23.6%    -23.6%      0.0%
            Max          +1.8%     +0.0%    +36.2%    +36.2%     +7.4%
 Geometric Mean          +1.7%     -0.1%     +6.8%     +6.8%     +0.1%

Compiler allocations in CI have a geometric mean of +0.1%; many small
decreases but there are three bigger increases (7%), all because we do
more worker/wrapper than before, so there is simply more code to
compile.  That's OK.

Perf benchmarks in perf/should_run improve in allocation by a geo mean
of -0.2%, which is good.  None get worse. T12996 improves by -5.8%

Metric Decrease:
    T12996
Metric Increase:
    T18282
    T18923
    T9630

- - - - -
d1ef6288 by Peter Trommler at 2022-02-02T23:50:34-05:00
Cmm: fix equality of expressions

Compare expressions and types when comparing `CmmLoad`s.
Fixes #21016

- - - - -
e59446c6 by Peter Trommler at 2022-02-02T23:50:34-05:00
Check type first then expression

- - - - -
b0e1ef4a by Matthew Pickering at 2022-02-03T14:44:17-05:00
Add failing test for #20791

The test produces different output on static vs dynamic GHC builds.

- - - - -
cae1fb17 by Matthew Pickering at 2022-02-03T14:44:17-05:00
Frontend01 passes with static GHC

- - - - -
e343526b by Matthew Pickering at 2022-02-03T14:44:17-05:00
Don't initialise plugins when there are no pipelines to run

- - - - -
abac45fc by Matthew Pickering at 2022-02-03T14:44:17-05:00
Mark prog003 as expected_broken on static way #20704

- - - - -
13300dfd by Matthew Pickering at 2022-02-03T14:44:17-05:00
Filter out -rtsopts in T16219 to make static/dynamic ways agree

- - - - -
d89439f2 by Matthew Pickering at 2022-02-03T14:44:17-05:00
T13168: Filter out rtsopts for consistency between dynamic and static ways

- - - - -
00180cdf by Matthew Pickering at 2022-02-03T14:44:17-05:00
Accept new output for T14335 test

This test was previously not run due to #20960

- - - - -
1accdcff by Matthew Pickering at 2022-02-03T14:44:17-05:00
Add flushes to plugin tests which print to stdout

Due to #20791 you need to explicitly flush as otherwise the output from
these tests doesn't make it to stdout.

- - - - -
d820f2e8 by Matthew Pickering at 2022-02-03T14:44:17-05:00
Remove ghc_plugin_way

Using ghc_plugin_way had the unintended effect of meaning certain tests
weren't run at all when ghc_dynamic=true, if you delete this modifier
then the tests work in both the static and dynamic cases.

- - - - -
aa5ef340 by Matthew Pickering at 2022-02-03T14:44:17-05:00
Unbreak T13168 on windows

Fixes #14276

- - - - -
84ab0153 by Matthew Pickering at 2022-02-03T14:44:53-05:00
Rewrite CallerCC parser using ReadP

This allows us to remove the dependency on parsec and hence transitively
on text.

Also added some simple unit tests for the parser and fixed two small
issues in the documentation.

Fixes #21033

- - - - -
4e6780bb by Matthew Pickering at 2022-02-03T14:45:28-05:00
ci: Add debian 11 jobs (validate/release/nightly)

Fixes #21002

- - - - -
eddaa591 by Ben Gamari at 2022-02-04T10:01:59-05:00
compiler: Introduce and use RoughMap for instance environments

Here we introduce a new data structure, RoughMap, inspired by the
previous `RoughTc` matching mechanism for checking instance matches.
This allows [Fam]InstEnv to be implemented as a trie indexed by these
RoughTc signatures, reducing the complexity of instance lookup and
FamInstEnv merging (done during the family instance conflict test)
from O(n) to O(log n).

The critical performance improvement currently realised by this patch is
in instance matching. In particular the RoughMap mechanism allows us to
discount many potential instances which will never match for constraints
involving type variables (see Note [Matching a RoughMap]). In realistic
code bases matchInstEnv was accounting for 50% of typechecker time due
to redundant work checking instances when simplifying instance contexts
when deriving instances. With this patch the cost is significantly
reduced.

The larger constants in InstEnv creation do mean that a few small
tests regress in allocations slightly. However, the runtime of T19703 is
reduced by a factor of 4. Moreover, the compilation time of the Cabal
library is slightly improved.

A couple of test cases are included which demonstrate significant
improvements in compile time with this patch.

This unfortunately does not fix the testcase provided in #19703 but does
fix #20933

-------------------------
Metric Decrease:
    T12425
Metric Increase:
    T13719
    T9872a
    T9872d
    hard_hole_fits
-------------------------

Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com>

- - - - -
62d670eb by Matthew Pickering at 2022-02-04T10:02:35-05:00
testsuite: Run testsuite dependency calculation before GHC is built

The main motivation for this patch is to allow tests to be added to the
testsuite which test things about the source tree without needing to
build GHC. In particular the notes linter can easily start failing and
by integrating it into the testsuite the  process of observing these
changes is caught by normal validation procedures rather than having to
run the linter specially.

With this patch I can run

```
./hadrian/build test --flavour=devel2  --only="uniques"
```

In a clean tree to run the checkUniques linter without having to build
GHC.

Fixes #21029

- - - - -
4bd52410 by Hécate Moonlight at 2022-02-04T16:14:10-05:00
Add the Ix class to Foreign C integral types

Related CLC proposal is here: https://github.com/haskell/core-libraries-committee/issues/30

- - - - -
de6d7692 by Ben Gamari at 2022-02-04T16:14:47-05:00
Drop dead code

- - - - -
b79206f1 by Ben Gamari at 2022-02-04T16:14:47-05:00
Add comments

- - - - -
58d7faac by Ben Gamari at 2022-02-04T16:14:47-05:00
cmm: Introduce cmmLoadBWord and cmmLoadGCWord

- - - - -
7217156c by Ben Gamari at 2022-02-04T16:14:47-05:00
Introduce alignment in CmmLoad

- - - - -
99ea5f2c by Ben Gamari at 2022-02-04T16:14:47-05:00
Introduce alignment to CmmStore

- - - - -
606b59a5 by Ben Gamari at 2022-02-04T16:14:47-05:00
Fix array primop alignment

- - - - -
1cf9616a by Ben Gamari at 2022-02-04T16:14:47-05:00
llvmGen: Handle unaligned loads/stores

This allows us to produce valid code for indexWord8ArrayAs*# on
platforms that lack unaligned memory access.

- - - - -
8c18feba by Ben Gamari at 2022-02-04T16:14:47-05:00
primops: Fix documentation of setByteArray#

Previously the documentation was subtly incorrect regarding the bounds
of the operation. Fix this and add a test asserting that a zero-length
operation is in fact a no-op.

- - - - -
88480e55 by nineonine at 2022-02-04T20:35:45-05:00
Fix unsound behavior of unlifted datatypes in ghci (#20194)

Previously, directly calling a function that pattern matches on an
unlifted data type which has at least two constructors in GHCi resulted
 in a segfault.

This happened due to unaccounted return frame info table pointer. The fix is
to pop the above mentioned frame info table pointer when unlifted things are
returned. See Note [Popping return frame for unlifted things]

authors: bgamari, nineonine

- - - - -
a5c7068c by Simon Peyton Jones at 2022-02-04T20:36:20-05:00
Add Outputable instance for Messages

c.f. #20980

- - - - -
bf495f72 by Simon Peyton Jones at 2022-02-04T20:36:20-05:00
Add a missing restoreLclEnv

The commit

  commit 18df4013f6eaee0e1de8ebd533f7e96c4ee0ff04
  Date:   Sat Jan 22 01:12:30 2022 +0000

    Define and use restoreLclEnv

omitted to change one setLclEnv to restoreLclEnv, namely
the one in GHC.Tc.Errors.warnRedundantConstraints.

This new commit fixes the omission.

- - - - -
6af8e71e by Simon Peyton Jones at 2022-02-04T20:36:20-05:00
Improve errors for non-existent labels

This patch fixes #17469, by improving matters when you use
non-existent field names in a record construction:
   data T = MkT { x :: Int }
   f v = MkT { y = 3 }

The check is now made in the renamer, in GHC.Rename.Env.lookupRecFieldOcc.

That in turn led to a spurious error in T9975a, which is fixed by
making GHC.Rename.Names.extendGlobalRdrEnvRn fail fast if it finds
duplicate bindings.  See Note [Fail fast on duplicate definitions]
in that module for more details.

This patch was originated and worked on by Alex D (@nineonine)

- - - - -
299acff0 by nineonine at 2022-02-05T19:21:49-05:00
Exit with failure when -e fails (fixes #18411 #9916 #17560)

- - - - -
549292eb by Matthew Pickering at 2022-02-05T19:22:25-05:00
Make implication tidying agree with Note [Tidying multiple names at once]

Note [Tidying multiple names at once] indicates that if multiple
variables have the same name then we shouldn't prioritise one of them
and instead rename them all to a1, a2, a3... etc

This patch implements that change, some error message changes as
expected.

Closes #20932

- - - - -
2e9248b7 by Ben Gamari at 2022-02-06T01:43:56-05:00
rts/m32: Accept any address within 4GB of program text

Previously m32 would assume that the program image was located near the
start of the address space and therefore assume that it wanted pages
in the bottom 4GB of address space. Instead we now check whether they
are within 4GB of whereever the program is loaded.

This is necessary on Windows, which now tends to place the image in high
memory. The eventual goal is to use m32 to allocate memory for linker
sections on Windows.

- - - - -
86589b89 by GHC GitLab CI at 2022-02-06T01:43:56-05:00
rts: Generalize mmapForLinkerMarkExecutable

Renamed to mprotectForLinker and allowed setting of arbitrary protection
modes.

- - - - -
88ef270a by GHC GitLab CI at 2022-02-06T01:43:56-05:00
rts/m32: Add consistency-checking infrastructure

This adds logic, enabled in the `-debug` RTS for checking the internal
consistency of the m32 allocator. This area has always made me a bit
nervous so this should help me sleep better at night in exchange for
very little overhead.

- - - - -
2d6f0b17 by Ben Gamari at 2022-02-06T01:43:56-05:00
rts/m32: Free large objects back to the free page pool

Not entirely convinced that this is worth doing.

- - - - -
e96f50be by GHC GitLab CI at 2022-02-06T01:43:56-05:00
rts/m32: Increase size of free page pool to 256 pages

- - - - -
fc083b48 by Ben Gamari at 2022-02-06T01:43:56-05:00
rts: Dump memory map on memory mapping failures

Fixes #20992.

- - - - -
633296bc by Ben Gamari at 2022-02-06T01:43:56-05:00
Fix macro redefinition warnings for PRINTF

* Move `PRINTF` macro from `Stats.h` to `Stats.c` as it's only needed in
  the latter.
* Undefine `PRINTF` at the end of `Messages.h` to avoid leaking it.

- - - - -
37d435d2 by John Ericson at 2022-02-06T01:44:32-05:00
Purge DynFlags from GHC.Stg

Also derive some more instances. GHC doesn't need them, but downstream
consumers may need to e.g. put stuff in maps.

- - - - -
886baa34 by Peter Trommler at 2022-02-06T10:58:18+01:00
RTS: Fix cabal specification

In 35bea01b xxhash.c was removed. Remove the extra-source-files
stanza referring to it.

- - - - -
27581d77 by Alex D at 2022-02-06T20:50:44-05:00
hadrian: remove redundant import
- - - - -
4ff19981 by John Ericson at 2022-02-07T11:04:43-05:00
GHC.HsToCore.Coverage: No more HscEnv, less DynFlags

Progress towards #20730

- - - - -
b09389a6 by John Ericson at 2022-02-07T11:04:43-05:00
Create `CoverageConfig`

As requested by @mpickering to collect the information we project from
`HscEnv`

- - - - -
ff867c46 by Greg Steuck at 2022-02-07T11:05:24-05:00
Avoid using removed utils/checkUniques in validate

Asked the question:
https://gitlab.haskell.org/ghc/ghc/-/merge_requests/7460/diffs#4061f4d17546e239dd10d78c6b48668c2a288e02_1_0

- - - - -
a9355e84 by sheaf at 2022-02-08T05:27:25-05:00
Allow HasField in quantified constraints

We perform validity checking on user-written HasField instances,
for example to disallow:

  data Foo a = Foo { fld :: Int }
  instance HasField "fld" (Foo a) Bool

However, these checks were also being made on quantified constraints,
e.g.

  data Bar where
    Bar :: (forall a. HasField s (Foo a) Int) => Proxy s -> Bar

This patch simply skips validity checking for quantified constraints,
in line with what we already do for equality constraints such as
Coercible.

Fixes #20989

- - - - -
6d77d3d8 by sheaf at 2022-02-08T05:28:05-05:00
Relax TyEq:N: allow out-of-scope newtype DataCon

The 'bad_newtype' assertion in GHC.Tc.Solver.Canonical.canEqCanLHSFinish
failed to account for the possibility that the newtype constructor
might not be in scope, in which case we don't provide any guarantees
about canonicalising away a newtype on the RHS of a representational
equality.

Fixes #21010

- - - - -
a893d2f3 by Matthew Pickering at 2022-02-08T05:28:42-05:00
Remove linter dependency on lint-submods

- - - - -
457a5b9c by Ben Gamari at 2022-02-08T05:28:42-05:00
notes-util: initial commit

- - - - -
1a943859 by Ben Gamari at 2022-02-08T05:28:42-05:00
gitlab-ci: Add lint-notes job

- - - - -
bc5cbce6 by Matthew Pickering at 2022-02-08T05:28:42-05:00
Add notes linter to testsuite

- - - - -
38c6e301 by Matthew Pickering at 2022-02-08T05:28:42-05:00
Fix some notes

- - - - -
c3aac0f8 by Matthew Pickering at 2022-02-08T05:28:42-05:00
Add suggestion mode to notes-util

- - - - -
5dd29aea by Cale Gibbard at 2022-02-08T05:29:18-05:00
`hscSimpleIface` drop fingerprint param and ret

`hscSimpleIface` does not depend on or modify the `Maybe Fingerprint` it
is given, only passes it through, so get rid of the extraneous passing.

Perhaps the intent was that there would be an iface fingerprint check of
some sort?  but this was never done. If/when we we want to do that, we
can add it back then.

- - - - -
4bcbd731 by Cale Gibbard at 2022-02-08T05:29:54-05:00
Document `hscIncrementalFrontend` and flip bool

- - - - -
b713db1e by John Ericson at 2022-02-08T05:30:29-05:00
StgToCmm: Get rid of GHC.Driver.Session imports

`DynFlags` is gone, but let's move a few trivial things around to get
rid of its module too.

- - - - -
f115c382 by Gleb Popov at 2022-02-08T05:31:05-05:00
Fix build on recent FreeBSD.

Recent FreeBSD versions gained the sched_getaffinity function, which made two
mutually exclusive #ifdef blocks to be enabled.

- - - - -
3320ab40 by Ben Gamari at 2022-02-08T10:42:04-05:00
rts/MemoryMap: Use mach_-prefixed type names

There appears to be some inconsistency in system-call type naming across
Darwin toolchains. Specifically:

 * the `address` argument to `mach_vm_region` apparently wants to be a
   `mach_vm_address_t *`, not a `vm_address_t *`

 * the `vmsize` argument to `mach_vm_region` wants to be a
   `mach_vm_size_t`, not a `vm_size_t`

- - - - -
b33f0cfa by Richard Eisenberg at 2022-02-08T10:42:41-05:00
Document that reifyRoles includes kind parameters

Close #21056

- - - - -
bd493ed6 by PHO at 2022-02-08T10:43:19-05:00
Don't try to build stage1 with -eventlog if stage0 doesn't provide it

Like -threaded, stage0 isn't guaranteed to have an event-logging RTS.

- - - - -
03c2de0f by Matthew Pickering at 2022-02-09T03:56:22-05:00
testsuite: Use absolute paths for config.libdir

Fixes #21052

- - - - -
ef294525 by Matthew Pickering at 2022-02-09T03:56:22-05:00
testsuite: Clean up old/redundant predicates

- - - - -
a39ed908 by Matthew Pickering at 2022-02-09T03:56:22-05:00
testsuite: Add missing dependency on ghcconfig

- - - - -
a172be07 by PHO at 2022-02-09T03:56:59-05:00
Implement System.Environment.getExecutablePath for NetBSD

and also use it from GHC.BaseDir.getBaseDir

- - - - -
62fa126d by PHO at 2022-02-09T03:57:37-05:00
Fix a portability issue in m4/find_llvm_prog.m4

`test A == B' is a Bash extension, which doesn't work on platforms where
/bin/sh is not Bash.

- - - - -
fd9981e3 by Ryan Scott at 2022-02-09T03:58:13-05:00
Look through untyped TH splices in tcInferAppHead_maybe

Previously, surrounding a head expression with a TH splice would defeat
`tcInferAppHead_maybe`, preventing some expressions from typechecking that
used to typecheck in previous GHC versions (see #21038 for examples). This is
simple enough to fix: just look through `HsSpliceE`s in `tcInferAppHead_maybe`.
I've added some additional prose to `Note [Application chains and heads]` in
`GHC.Tc.Gen.App` to accompany this change.

Fixes #21038.

- - - - -
00975981 by sheaf at 2022-02-09T03:58:53-05:00
Add test for #21037

  This program was rejected by GHC 9.2, but is accepted
  on newer versions of GHC. This patch adds a regression test.

  Closes #21037

- - - - -
fad0b2b0 by Ben Gamari at 2022-02-09T08:29:46-05:00
Rename -merge-objs flag to --merge-objs

For consistency with --make and friends.

- - - - -
1dbe5b2a by Matthew Pickering at 2022-02-09T08:30:22-05:00
driver: Filter out our own boot module in hptSomeThingsBelow

hptSomeThingsBelow would return a list of modules which contain the
.hs-boot file for a particular module. This caused some problems because
we would try and find the module in the HPT (but it's not there when
we're compiling the module itself).

Fixes #21058

- - - - -
2b1cced1 by Sylvain Henry at 2022-02-09T20:42:23-05:00
NCG: minor code factorization

- - - - -
e01ffec2 by Sylvain Henry at 2022-02-09T20:42:23-05:00
ByteCode: avoid out-of-bound read

Cf https://gitlab.haskell.org/ghc/ghc/-/issues/18431#note_287139

- - - - -
53c26e79 by Ziyang Liu at 2022-02-09T20:43:02-05:00
Include ru_name in toHsRule message

See #18147

- - - - -
3df06922 by Ben Gamari at 2022-02-09T20:43:39-05:00
rts: Rename MemoryMap.[ch] -> ReportMemoryMap.[ch]

- - - - -
e219ac82 by Ben Gamari at 2022-02-09T20:43:39-05:00
rts: Move mmapForLinker and friends to linker/MMap.c

They are not particularly related to linking.

- - - - -
30e205ca by Ben Gamari at 2022-02-09T20:43:39-05:00
rts/linker: Drop dead IA64 code

- - - - -
4d3a306d by Ben Gamari at 2022-02-09T20:43:39-05:00
rts/linker/MMap: Use MemoryAccess in mmapForLinker

- - - - -
1db4f1fe by Ben Gamari at 2022-02-09T20:43:39-05:00
linker: Don't use MAP_FIXED

As noted in #21057, we really shouldn't be using MAP_FIXED. I would much
rather have the process crash with a "failed to map" error than randomly
overwrite existing mappings.

Closes #21057.

- - - - -
1eeae25c by Ben Gamari at 2022-02-09T20:43:39-05:00
rts/mmap: Refactor mmapForLinker

Here we try to separate the policy decisions of where to place mappings
from the mechanism of creating the mappings. This makes things
significantly easier to follow.

- - - - -
ac2d18a7 by sheaf at 2022-02-09T20:44:18-05:00
Add some perf tests for coercions

  This patch adds some performance tests for programs that create
  large coercions. This is useful because the existing test coverage
  is not very representative of real-world situations. In particular,
  this adds a test involving an extensible records library, a common
  pain-point for users.

- - - - -
48f25715 by Andreas Klebinger at 2022-02-10T04:35:35-05:00
Add late cost centre support

This allows cost centres to be inserted after the core optimization
pipeline has run.

- - - - -
0ff70427 by Andreas Klebinger at 2022-02-10T04:36:11-05:00
Docs:Mention that safe calls don't keep their arguments alive.

- - - - -
1d3ed168 by Ben Gamari at 2022-02-10T04:36:46-05:00
PEi386: Drop Windows Vista fallback in addLibrarySearchPath

We no longer support Windows Vista.

- - - - -
2a6f2681 by Ben Gamari at 2022-02-10T04:36:46-05:00
linker/PEi386: Make addLibrarySearchPath long-path aware

Previously `addLibrarySearchPath` failed to normalise the added path to
UNC form before passing it to `AddDllDirectory`. Consequently, the call
was subject to the MAX_PATH restriction, leading to the failure of
`test-defaulting-plugin-fail`, among others. Happily, this also nicely
simplifies the implementation.

Closes #21059.

- - - - -
2a47ee9c by Daniel Gröber at 2022-02-10T19:18:58-05:00
ghc-boot: Simplify writePackageDb permissions handling

Commit ef8a3fbf1 ("ghc-boot: Fix metadata handling of writeFileAtomic")
introduced a somewhat over-engineered fix for #14017 by trying to preserve
the current permissions if the target file already exists.

The problem in the issue is simply that the package db cache file should be
world readable but isn't if umask is too restrictive. In fact the previous
fix only handles part of this problem. If the file isn't already there in a
readable configuration it wont make it so which isn't really ideal either.

Rather than all that we now simply always force all the read access bits to
allow access while leaving the owner at the system default as it's just not
our business to mess with it.

- - - - -
a1d97968 by Ben Gamari at 2022-02-10T19:19:34-05:00
Bump Cabal submodule

Adapts GHC to the factoring-out of `Cabal-syntax`.

Fixes #20991.

Metric Decrease:
    haddock.Cabal

- - - - -
89cf8caa by Morrow at 2022-02-10T19:20:13-05:00
Add metadata to integer-gmp.cabal

- - - - -
c995b7e7 by Matthew Pickering at 2022-02-10T19:20:48-05:00
eventlog: Fix event type of EVENT_IPE

This leads to corrupted eventlogs because the size of EVENT_IPE is
completely wrong.

Fixes a bug introduced in 2e29edb7421c21902b47d130d45f60d3f584a0de

- - - - -
59ba8fb3 by Matthew Pickering at 2022-02-10T19:20:48-05:00
eventlog: Fix event type of MEM_RETURN

This leads to corrupted eventlogs because the size of EVENT_MEM_RETURN is
completely wrong.

Fixes a bug introduced in 2e29edb7421c21902b47d130d45f60d3f584a0de

- - - - -
19413d09 by Matthew Pickering at 2022-02-10T19:20:48-05:00
eventlog: Delete misleading comment in gen_event_types.py

Not all events start with CapNo and there's not logic I could see which
adds this to the length.

- - - - -
e06f49c0 by Matthew Pickering at 2022-02-10T19:20:48-05:00
eventlog: Fix size of TICKY_COUNTER_BEGIN_SAMPLE

- - - - -
2f99255b by Matthew Pickering at 2022-02-10T19:21:24-05:00
Fix copy-pasto in prof-late-ccs docs

- - - - -
19deb002 by Matthew Pickering at 2022-02-10T19:21:59-05:00
Refine tcSemigroupWarnings to work in ghc-prim

ghc-prim doesn't depend on base so can't have any Monoid or Semigroup
instances. However, attempting to load these definitions ran into issues
when the interface for `GHC.Base` did exist as that would try and load
the interface for `GHC.Types` (which is the module we are trying to
compile and has no interface).

The fix is to just not do this check when we are compiling a module in
ghc-prim.

Fixes #21069

- - - - -
34dec6b7 by sheaf at 2022-02-11T17:55:34-05:00
Decrease the size of the LargeRecord test

  This test was taking too long to run, so this patch makes it smaller.

-------------------------
Metric Decrease:
    LargeRecord
-------------------------

- - - - -
9cab90d9 by Matthew Pickering at 2022-02-11T22:27:19-05:00
Make sure all platforms have a release job

The release bindists are currently a mixture of validate and release
builds. This is bad because the validate builds don't have profiling
libraries. The fix is to make sure there is a release job for each
platform we want to produce a release for.t

Fixes #21066

- - - - -
4bce3575 by Matthew Pickering at 2022-02-11T22:27:54-05:00
testsuite: Make sure all tests trigger ghc rebuild

I made a mistake when implementing #21029 which meant that certain tests
didn't trigger a GHC recompilation. By adding the `test:ghc` target to
the default settings all tests will now depend on this target unless
explicitly opting out via the no_deps modifier.

- - - - -
90a26f8b by Sylvain Henry at 2022-02-11T22:28:34-05:00
Fix documentation about Word64Rep/Int64Rep (#16964)

- - - - -
0e93023e by Andreas Klebinger at 2022-02-12T13:59:41+00:00
Tag inference work.

This does three major things:
* Enforce the invariant that all strict fields must contain tagged
pointers.
* Try to predict the tag on bindings in order to omit tag checks.
* Allows functions to pass arguments unlifted (call-by-value).

The former is "simply" achieved by wrapping any constructor allocations with
a case which will evaluate the respective strict bindings.

The prediction is done by a new data flow analysis based on the STG
representation of a program. This also helps us to avoid generating
redudant cases for the above invariant.

StrictWorkers are created by W/W directly and SpecConstr indirectly.
See the Note [Strict Worker Ids]

Other minor changes:

* Add StgUtil module containing a few functions needed by, but
  not specific to the tag analysis.

-------------------------
Metric Decrease:
	T12545
	T18698b
	T18140
	T18923
        LargeRecord
Metric Increase:
        LargeRecord
	ManyAlternatives
	ManyConstructors
	T10421
	T12425
	T12707
	T13035
	T13056
	T13253
	T13253-spj
	T13379
	T15164
	T18282
	T18304
	T18698a
	T1969
	T20049
	T3294
	T4801
	T5321FD
	T5321Fun
	T783
	T9233
	T9675
	T9961
	T19695
	WWRec
-------------------------

- - - - -
744f8a11 by Greg Steuck at 2022-02-12T17:13:55-05:00
Only check the exit code in derefnull & divbyzero tests on OpenBSD

- - - - -
eeead9fc by Ben Gamari at 2022-02-13T03:26:14-05:00
rts/Adjustor: Ensure that allocateExecPage succeeded

Previously we failed to handle the case that `allocateExecPage` failed.

- - - - -
afdfaff0 by Ben Gamari at 2022-02-13T03:26:14-05:00
rts: Drop DEC Alpha adjustor implementation

The last Alpha chip was produced in 2004.

- - - - -
191dfd2d by Ben Gamari at 2022-02-13T03:26:14-05:00
rts/adjustor: Split Windows path out of NativeAmd64

- - - - -
be591e27 by Ben Gamari at 2022-02-13T03:26:14-05:00
rts: Initial commit of AdjustorPool

- - - - -
d6d48b16 by Ben Gamari at 2022-02-13T03:26:14-05:00
Introduce initAdjustors

- - - - -
eab37902 by Ben Gamari at 2022-02-13T03:26:14-05:00
adjustors/NativeAmd64: Use AdjustorPool

- - - - -
974e73af by Ben Gamari at 2022-02-13T03:26:14-05:00
adjustors/NativeAmd64Mingw: Use AdjustorPool

- - - - -
95fab83f by Ben Gamari at 2022-02-13T03:26:14-05:00
configure: Fix result reporting of adjustors method check

- - - - -
ef5cf55d by nikshalark at 2022-02-13T03:26:16-05:00
(#21044) Documented arithmetic functions in base.

Didn't get it right the ninth time. Now everything's formatted correctly.

- - - - -
acb482cc by Takenobu Tani at 2022-02-16T05:27:17-05:00
Relax load_load_barrier for aarch64

This patch relaxes the instruction for load_load_barrier().
Current load_load_barrier() implements full-barrier with `dmb sy`.
It's too strong to order load-load instructions.
We can relax it by using `dmb ld`.

If current load_load_barrier() is used for full-barriers
(load/store - load/store barrier), this patch is not suitable.

See also linux-kernel's smp_rmb() implementation:
  https://github.com/torvalds/linux/blob/v5.14/arch/arm64/include/asm/barrier.h#L90

Hopefully, it's better to use `dmb ishld` rather than `dmb ld`
to improve performance. However, I can't validate effects on
a real many-core Arm machine.

- - - - -
84eaa26f by Oleg Grenrus at 2022-02-16T05:27:56-05:00
Add test for #20562

- - - - -
2c28620d by Adam Sandberg Ericsson at 2022-02-16T05:28:32-05:00
rts: remove struct StgRetry, it is never used

- - - - -
74bf9bb5 by Adam Sandberg Ericsson at 2022-02-16T05:28:32-05:00
rts: document some closure types

- - - - -
316312ec by nineonine at 2022-02-16T05:29:08-05:00
ghci: fix -ddump-stg-cg (#21052)

The pre-codegen Stg AST dump was not available in ghci because it
was performed in 'doCodeGen'. This was now moved to 'coreToStg' area.

- - - - -
a6411d74 by Adam Sandberg Ericsson at 2022-02-16T05:29:43-05:00
docs: mention -fprof-late-ccs in the release notes

And note which compiler version it was added in.

- - - - -
4127e86d by Adam Sandberg Ericsson at 2022-02-16T05:29:43-05:00
docs: fix release notes formatting

- - - - -
4e6c8019 by Matthew Pickering at 2022-02-17T05:25:28-05:00
Always define __GLASGOW_HASKELL_PATCHLEVEL1/2__ macros

As #21076 reports if you are using `-Wcpp-undef` then you get warnings
when using the `MIN_VERSION_GLASGOW_HASKELL` macro because
__GLASGOW_HASKELL_PATCHLEVEL2__ is very rarely explicitliy set (as
version numbers are not 4 components long).

This macro was introduced in 3549c952b535803270872adaf87262f2df0295a4
and it seems the bug has existed ever since.

Fixes #21076

- - - - -
67dd5724 by Ben Gamari at 2022-02-17T05:26:03-05:00
rts/AdjustorPool: Silence unused function warning

bitmap_get is only used in the DEBUG RTS configuration.

Fixes #21079.

- - - - -
4b04f7e1 by Zubin Duggal at 2022-02-20T13:56:15-05:00
Track object file dependencies for TH accurately (#20604)

`hscCompileCoreExprHook` is changed to return a list of `Module`s required
by a splice. These modules are accumulated in the TcGblEnv (tcg_th_needed_mods).
Dependencies on the object files of these modules are recording in the
interface.

The data structures in `LoaderState` are replaced with more efficient versions
to keep track of all the information required. The
MultiLayerModulesTH_Make allocations increase slightly but runtime is
faster.

Fixes #20604

-------------------------
Metric Increase:
    MultiLayerModulesTH_Make
-------------------------

- - - - -
92ab3ff2 by sheaf at 2022-02-20T13:56:55-05:00
Use diagnostics for "missing signature" errors

  This patch makes the "missing signature" errors from
  "GHC.Rename.Names" use the diagnostic infrastructure.
  This encompasses missing type signatures for top-level bindings
  and pattern synonyms, as well as missing kind signatures for
  type constructors.

  This patch also renames TcReportMsg to TcSolverReportMsg,
  and adds a few convenience functions to compute whether such a
  TcSolverReportMsg is an expected/actual message.

- - - - -
845284a5 by sheaf at 2022-02-20T13:57:34-05:00
Generically: remove redundant Semigroup constraint

  This patch removes a redundant Semigroup constraint on the Monoid
  instance for Generically. This constraint can cause trouble when
  one wants to derive a Monoid instance via Generically through a type
  that doesn't itself have a Semigroup instance, for example:

    data Point2D a = Point2D !a !a

    newtype Vector2D a = Vector2D { tip :: Point2D a }
      deriving ( Semigroup, Monoid )
        via Generically ( Point2D ( Sum a ) )

  In this case, we should not require there to be an instance

    Semigroup ( Point2D ( Sum a ) )

  as all we need is an instance for the generic representation of
  Point2D ( Sum a ), i.e. Semigroup ( Rep ( Point2D ( Sum a) ) () ).

- - - - -
6b468f7f by Ben Gamari at 2022-02-20T13:58:10-05:00
Bump time submodule to 1.12.1

- - - - -
2f0ceecc by Zubin Duggal at 2022-02-20T19:06:19+00:00
hadrian: detect if 'main' is not a haskell file and add it to appropriate list of sources

- - - - -
7ce1b694 by Zubin Duggal at 2022-02-21T11:18:58+00:00
Reinstallable GHC

This patch allows ghc and its dependencies to be built using a normal
invocation of cabal-install. Each componenent which relied on generated
files or additional configuration now has a Setup.hs file.

There are also various fixes to the cabal files to satisfy
cabal-install.

There is a new hadrian command which will build a stage2 compiler and
then a stage3 compiler by using cabal.

```
./hadrian/build build-cabal
```

There is also a new CI job which tests running this command.

For the 9.4 release we will upload all the dependent executables to
hackage and then end users will be free to build GHC and GHC executables
via cabal.

There are still some unresolved questions about how to ensure soundness
when loading plugins into a reinstalled GHC (#20742) which will be
tighted up in due course.

Fixes #19896

- - - - -
78fbc3a3 by Matthew Pickering at 2022-02-21T15:14:28-05:00
hadrian: Enable late-ccs when building profiled_ghc

- - - - -
2b890c89 by Matthew Pickering at 2022-02-22T15:59:33-05:00
testsuite: Don't print names of all fragile tests on all runs

This information about fragile tests is pretty useless but annoying on
CI where you have to scroll up a long way to see the actual issues.

- - - - -
0b36801f by sheaf at 2022-02-22T16:00:14-05:00
Forbid standalone instances for built-in classes

  `check_special_inst_head` includes logic that disallows hand-written
  instances for built-in classes such as Typeable, KnownNat
  and KnownSymbol.
  However, it also allowed standalone deriving declarations. This was
  because we do want to allow standalone deriving instances with
  Typeable as they are harmless, but we certainly don't want to allow
  instances for e.g. KnownNat.

  This patch ensures that we don't allow derived instances for
  KnownNat, KnownSymbol (and also KnownChar, which was previously
  omitted entirely).

  Fixes #21087

- - - - -
ace66dec by Krzysztof Gogolewski at 2022-02-22T16:30:59-05:00
Remove -Wunticked-promoted-constructors from -Wall

Update manual; explain ticks as optional disambiguation
rather than the preferred default.

This is a part of #20531.

- - - - -
558c7d55 by Hugo at 2022-02-22T16:31:01-05:00
docs: fix error in annotation guide code snippet

- - - - -
a599abba by Richard Eisenberg at 2022-02-23T08:16:07-05:00
Kill derived constraints

Co-authored by: Sam Derbyshire

Previously, GHC had three flavours of constraint:
Wanted, Given, and Derived. This removes Derived constraints.

Though serving a number of purposes, the most important role
of Derived constraints was to enable better error messages.
This job has been taken over by the new RewriterSets, as explained
in Note [Wanteds rewrite wanteds] in GHC.Tc.Types.Constraint.

Other knock-on effects:
 - Various new Notes as I learned about under-described bits of GHC

 - A reshuffling around the AST for implicit-parameter bindings,
   with better integration with TTG.

 - Various improvements around fundeps. These were caused by the
   fact that, previously, fundep constraints were all Derived,
   and Derived constraints would get dropped. Thus, an unsolved
   Derived didn't stop compilation. Without Derived, this is no
   longer possible, and so we have to be considerably more careful
   around fundeps.

 - A nice little refactoring in GHC.Tc.Errors to center the work
   on a new datatype called ErrorItem. Constraints are converted
   into ErrorItems at the start of processing, and this allows for
   a little preprocessing before the main classification.

 - This commit also cleans up the behavior in generalisation around
   functional dependencies. Now, if a variable is determined by
   functional dependencies, it will not be quantified. This change
   is user facing, but it should trim down GHC's strange behavior
   around fundeps.

 - Previously, reportWanteds did quite a bit of work, even on an empty
   WantedConstraints. This commit adds a fast path.

 - Now, GHC will unconditionally re-simplify constraints during
   quantification. See Note [Unconditionally resimplify constraints when
   quantifying], in GHC.Tc.Solver.

Close #18398.
Close #18406.
Solve the fundep-related non-confluence in #18851.
Close #19131.
Close #19137.
Close #20922.
Close #20668.
Close #19665.

-------------------------
Metric Decrease:
    LargeRecord
    T9872b
    T9872b_defer
    T9872d
    TcPlugin_RewritePerf
-------------------------

- - - - -
2ed22ba1 by Matthew Pickering at 2022-02-23T08:16:43-05:00
Introduce predicate for when to enable source notes (needSourceNotes)

There were situations where we were using debugLevel == 0 as a proxy for
whether to retain source notes but -finfo-table-map also enables and
needs source notes so we should act consistently in both cases.

Ticket #20847

- - - - -
37deb893 by Matthew Pickering at 2022-02-23T08:16:43-05:00
Use SrcSpan from the binder as initial source estimate

There are some situations where we end up with no source notes in useful
positions in an expression. In this case we currently fail to provide
any source information about where an expression came from.

This patch improves the initial estimate by using the position from the
top-binder as the guess for the location of the whole inner expression.
It provides quite a course estimate but it's better than nothing.

Ticket #20847

- - - - -
59b7f764 by Cheng Shao at 2022-02-23T08:17:24-05:00
Don't emit foreign exports initialiser code for empty CAF list

- - - - -
c7f32f76 by John Ericson at 2022-02-23T13:58:36-05:00
Prepare rechecking logic for new type in a few ways

Combine `MustCompile and `NeedsCompile` into a single case.
`CompileReason` is put inside to destinguish the two. This makes a
number of things easier.

`Semigroup RecompileRequired` is no longer used, to make sure we skip
doing work where possible. `recompThen` is very similar, but helps
remember.

`checkList` is rewritten with `recompThen`.

- - - - -
e60d8df8 by John Ericson at 2022-02-23T13:58:36-05:00
Introduce `MaybeValidated` type to remove invalid states

The old return type `(RecompRequired, Maybe _)`, was confusing
because it was inhabited by values like `(UpToDate, Nothing)` that made
no sense.

The new type ensures:

 - you must provide a value if it is up to date.

 - you must provide a reason if you don't provide a value.

it is used as the return value of:

 - `checkOldIface`
 - `checkByteCode`
 - `checkObjects`

- - - - -
f07b13e3 by Sylvain Henry at 2022-02-23T13:59:23-05:00
NCG: refactor X86 codegen

Preliminary work done to make working on #5444 easier.

Mostly make make control-flow easier to follow:

* renamed genCCall into genForeignCall

* split genForeignCall into the part dispatching on PrimTarget (genPrim) and
  the one really generating code for a C call (cf ForeignTarget and genCCall)

* made genPrim/genSimplePrim only dispatch on MachOp: each MachOp now
  has its own code generation function.

* out-of-line primops are not handled in a partial `outOfLineCmmOp`
  anymore but in the code generation functions directly. Helper
  functions have been introduced (e.g. genLibCCall) for code sharing.

* the latter two bullets make code generated for primops that are only
  sometimes out-of-line (e.g. Pdep or Memcpy) and the logic to select
  between inline/out-of-line much more localized

* avoided passing is32bit as an argument as we can easily get it from NatM
  state when we really need it

* changed genCCall type to avoid it being partial (it can't handle
  PrimTarget)

* globally removed 12 calls to `panic` thanks to better control flow and
  types ("parse, don't validate" ftw!).

- - - - -
6fa7591e by Sylvain Henry at 2022-02-23T13:59:23-05:00
NCG: refactor the way registers are handled

* add getLocalRegReg to avoid allocating a CmmLocal just to call
  getRegisterReg

* 64-bit registers: in the general case we must always use the virtual
  higher part of the register, so we might as well always return it with
  the lower part. The only exception is to implement 64-bit to 32-bit
  conversions. We now have to explicitly discard the higher part when
  matching on Reg64/RegCode64 datatypes instead of explicitly fetching
  the higher part from the lower part: much safer default.

- - - - -
bc8de322 by Sylvain Henry at 2022-02-23T13:59:23-05:00
NCG: inline some 64-bit primops on x86/32-bit (#5444)

Several 64-bit operation were implemented with FFI calls on 32-bit
architectures but we can easily implement them with inline assembly
code.

Also remove unused hs_int64ToWord64 and hs_word64ToInt64 C functions.

- - - - -
7b7c6b95 by Matthew Pickering at 2022-02-23T14:00:00-05:00
Simplify/correct implementation of getModuleInfo

- - - - -
6215b04c by Matthew Pickering at 2022-02-23T14:00:00-05:00
Remove mg_boot field from ModuleGraph

It was unused in the compiler so I have removed it to streamline
ModuleGraph.

- - - - -
818ff2ef by Matthew Pickering at 2022-02-23T14:00:01-05:00
driver: Remove needsTemplateHaskellOrQQ from ModuleGraph

The idea of the needsTemplateHaskellOrQQ query is to check if any of the
modules in a module graph need Template Haskell then enable -dynamic-too
if necessary. This is quite imprecise though as it will enable
-dynamic-too for all modules in the module graph even if only one module
uses template haskell, with multiple home units, this is obviously even
worse.

With -fno-code we already have similar logic to enable code generation
just for the modules which are dependeded on my TemplateHaskell modules
so we use the same code path to decide whether to enable -dynamic-too
rather than using this big hammer.

This is part of the larger overall goal of moving as much statically
known configuration into the downsweep as possible in order to have
fully decided the build plan and all the options before starting to
build anything.

I also included a fix to #21095, a long standing bug with with the logic
which is supposed to enable the external interpreter if we don't have
the internal interpreter.

Fixes #20696 #21095

- - - - -
b6670af6 by Matthew Pickering at 2022-02-23T14:00:40-05:00
testsuite: Normalise output of ghci011 and T7627

The outputs of these tests vary on the order interface files are loaded
so we normalise the output to correct for these inconsequential
differences.

Fixes #21121

- - - - -
9ed3bc6e by Peter Trommler at 2022-02-23T14:01:16-05:00
testsuite: Fix ipeMap test

Pointers to closures must be untagged before use.
Produce closures of different types so we get different info tables.

Fixes #21112

- - - - -
7d426148 by Ziyang Liu at 2022-02-24T04:53:34-05:00
Allow `return` in more cases in ApplicativeDo

The doc says that the last statement of an ado-block can be one of
`return E`, `return $ E`, `pure E` and `pure $ E`. But `return`
is not accepted in a few cases such as:

```haskell
-- The ado-block only has one statement
x :: F ()
x = do
  return ()

-- The ado-block only has let-statements besides the `return`
y :: F ()
y = do
  let a = True
  return ()
```

These currently require `Monad` instances. This MR fixes it.
Normally `return` is accepted as the last statement because it is
stripped in constructing an `ApplicativeStmt`, but this cannot be
done in the above cases, so instead we replace `return` by `pure`.

A similar but different issue (when the ado-block contains `BindStmt`
or `BodyStmt`, the second last statement cannot be `LetStmt`, even if
the last statement uses `pure`) is fixed in !6786.

- - - - -
a5ea7867 by John Ericson at 2022-02-24T20:23:49-05:00
Clarify laws of TestEquality

It is unclear what `TestEquality` is for. There are 3 possible choices.

Assuming

```haskell
data Tag a where
    TagInt1 :: Tag Int
    TagInt2 :: Tag Int
```

Weakest -- type param equality semi-decidable
---------------------------------------------

`Just Refl` merely means the type params are equal, the values being compared might not be.
`Nothing` means the type params may or may not be not equal.

```haskell
instance TestEquality Tag where
    testEquality TagInt1 TagInt1 = Nothing -- oopsie is allowed
    testEquality TagInt1 TagInt2 = Just Refl
    testEquality TagInt2 TagInt1 = Just Refl
    testEquality TagInt2 TagInt2 = Just Refl
```

This option is better demonstrated with a different type:
```haskell
data Tag' a where
    TagInt1 :: Tag Int
    TagInt2 :: Tag a
```
```haskell
instance TestEquality Tag' where
    testEquality TagInt1 TagInt1 = Just Refl
    testEquality TagInt1 TagInt2 = Nothing -- can't be sure
    testEquality TagInt2 TagInt1 = Nothing -- can't be sure
    testEquality TagInt2 TagInt2 = Nothing -- can't be sure
```

Weaker -- type param equality decidable
---------------------------------------

`Just Refl` merely means the type params are equal, the values being compared might not be.
`Nothing` means the type params are not equal.

```haskell
instance TestEquality Tag where
    testEquality TagInt1 TagInt1 = Just Refl
    testEquality TagInt1 TagInt2 = Just Refl
    testEquality TagInt2 TagInt1 = Just Refl
    testEquality TagInt2 TagInt2 = Just Refl
```

Strong -- Like `Eq`
-------------------

`Just Refl` means the type params are equal, and the values are equal according to `Eq`.

```haskell
instance TestEquality Tag where
    testEquality TagInt1 TagInt1 = Just Refl
    testEquality TagInt2 TagInt2 = Just Refl
    testEquality _ _ = Nothing
```

Strongest -- unique value concrete type
---------------------------------------

`Just Refl` means the type params are equal, and the values are equal, and the class assume if the type params are equal the values must also be equal. In other words, the type is a singleton type when the type parameter is a closed term.

```haskell
-- instance TestEquality -- invalid instance because two variants for `Int`
```
------

The discussion in
https://github.com/haskell/core-libraries-committee/issues/21 has
decided on the "Weaker" option (confusingly formerly called the
"Weakest" option). So that is what is implemented.

- - - - -
06c18990 by Zubin Duggal at 2022-02-24T20:24:25-05:00
TH: fix pretty printing of GADTs with multiple constuctors (#20842)

- - - - -
6555b68c by Matthew Pickering at 2022-02-24T20:25:06-05:00
Move linters into the tree

This MR moves the GHC linters into the tree, so that they can be run directly using Hadrian.

* Query all files tracked by Git instead of using changed files, so that we can run the exact same linting step locally and in a merge request.
* Only check that the changelogs don't contain TBA when RELEASE=YES.
* Add hadrian/lint script, which runs all the linting steps.
* Ensure the hlint job exits with a failure if hlint is not installed (otherwise we were ignoring the failure). Given that hlint doesn't seem to be available in CI at the moment, I've temporarily allowed failure in the hlint job.
* Run all linting tests in CI using hadrian.

- - - - -
b99646ed by Matthew Pickering at 2022-02-24T20:25:06-05:00
Add rule for generating HsBaseConfig.h

If you are running the `lint:{base/compiler}` command locally then this
improves the responsiveness because we don't re-run configure everytime
if the header file already exists.

- - - - -
d0deaaf4 by Matthew Pickering at 2022-02-24T20:25:06-05:00
Suggestions due to hlint

It turns out this job hasn't been running for quite a while (perhaps
ever) so there are quite a few failures when running the linter locally.

- - - - -
70bafefb by nineonine at 2022-02-24T20:25:42-05:00
ghci: show helpful error message when loading module with SIMD vector operations (#20214)

Previously, when trying to load module with SIMD vector operations, ghci would panic
in 'GHC.StgToByteCode.findPushSeq'. Now, a more helpful message is displayed.

- - - - -
8ed3d5fd by Matthew Pickering at 2022-02-25T10:24:12+00:00
Remove test-bootstrap and cabal-reinstall jobs from fast-ci [skip ci]

- - - - -
8387dfbe by Mario Blažević at 2022-02-25T21:09:41-05:00
template-haskell: Fix two prettyprinter issues

Fix two issues regarding printing numeric literals.

Fixing #20454.

- - - - -
4ad8ce0b by sheaf at 2022-02-25T21:10:22-05:00
GHCi: don't normalise partially instantiated types

  This patch skips performing type normalisation when we haven't
  fully instantiated the type. That is, in tcRnExpr
  (used only for :type in GHCi), skip normalisation if
  the result type responds True to isSigmaTy.

  Fixes #20974

- - - - -
f35aca4d by Ben Gamari at 2022-02-25T21:10:57-05:00
rts/adjustor: Always place adjustor templates in data section

@nrnrnr points out that on his machine ld.lld rejects text relocations.
Generalize the Darwin text-relocation avoidance logic to account for
this.

- - - - -
cddb040a by Andreas Klebinger at 2022-02-25T21:11:33-05:00
Ticky: Gate tag-inference dummy ticky-counters behind a flag.

Tag inference included a way to collect stats about avoided tag-checks.
This was dony by emitting "dummy" ticky entries with counts corresponding
to predicted/unpredicated tag checks.

This behaviour for ticky is now gated behind -fticky-tag-checks.

I also documented ticky-LNE in the process.

- - - - -
948bf2d0 by Ben Gamari at 2022-02-25T21:12:09-05:00
Fix comment reference to T4818

- - - - -
9c3edeb8 by Ben Gamari at 2022-02-25T21:12:09-05:00
simplCore: Correctly extend in-scope set in rule matching

Note [Matching lets] in GHC.Core.Rules claims the following:

> We use GHC.Core.Subst.substBind to freshen the binding, using an
> in-scope set that is the original in-scope variables plus the
> rs_bndrs (currently floated let-bindings).

However, previously the implementation didn't actually do extend the
in-scope set with rs_bndrs. This appears to be a regression which was
introduced by 4ff4d434e9a90623afce00b43e2a5a1ccbdb4c05.

Moreover, the originally reasoning was subtly wrong: we must rather use
the in-scope set from rv_lcl, extended with rs_bndrs, not that of
`rv_fltR`

Fixes #21122.

- - - - -
7f9f49c3 by sheaf at 2022-02-25T21:12:47-05:00
Derive some stock instances for OverridingBool

  This patch adds some derived instances to
  `GHC.Data.Bool.OverridingBool`. It also changes the order of the
  constructors, so that the derived `Ord` instance matches the
  behaviour for `Maybe Bool`.

  Fixes #20326

- - - - -
140438a8 by nineonine at 2022-02-25T21:13:23-05:00
Add test for #19271

- - - - -
ac9f4606 by sheaf at 2022-02-25T21:14:04-05:00
Allow qualified names in COMPLETE pragmas

  The parser didn't allow qualified constructor names to appear
  in COMPLETE pragmas. This patch fixes that.

  Fixes #20551

- - - - -
677c6c91 by Sylvain Henry at 2022-02-25T21:14:44-05:00
Testsuite: remove arch conditional in T8832

Taken from !3658

- - - - -
ad04953b by Sylvain Henry at 2022-02-25T21:15:23-05:00
Allow hscGenHardCode to not return CgInfos

This is a minor change in preparation for the JS backend: CgInfos aren't
mandatory and the JS backend won't return them.

- - - - -
929c280f by Sylvain Henry at 2022-02-25T21:15:24-05:00
Derive Enum instances for CCallConv and Safety

This is used by the JS backend for serialization.

- - - - -
75e4e090 by Sebastian Graf at 2022-02-25T21:15:59-05:00
base: Improve documentation of `throwIO` (#19854)

Now it takes a better account of precise vs. imprecise exception semantics.

Fixes #19854.

- - - - -
61a203ba by Matthew Pickering at 2022-02-26T02:06:51-05:00
Make typechecking unfoldings from interfaces lazier

The old logic was unecessarily strict in loading unfoldings because when
reading the unfolding we would case on the result of attempting to load
the template before commiting to which type of unfolding we were
producing. Hence trying to inspect any of the information about an
unfolding would force the template to be loaded.

This also removes a potentially hard to discover bug where if the
template failed to be typechecked for some reason then we would just not
return an unfolding. Instead we now panic so these bad situations which
should never arise can be identified.

- - - - -
2be74460 by Matthew Pickering at 2022-02-26T02:06:51-05:00
Use a more up-to-date snapshot of the current rules in the simplifier

As the prescient (now deleted) note warns in simplifyPgmIO we have to be a bit careful
about when we gather rules from the EPS so that we get the rules for
imported bindings.

```
  -- Get any new rules, and extend the rule base
  -- See Note [Overall plumbing for rules] in GHC.Core.Rules
  -- We need to do this regularly, because simplification can
  -- poke on IdInfo thunks, which in turn brings in new rules
  -- behind the scenes.  Otherwise there's a danger we'll simply
  -- miss the rules for Ids hidden inside imported inlinings
```

Given the previous commit, the loading of unfoldings is now even more
delayed so we need to be more careful to read the EPS rule base closer to the point
where we decide to try rules.

Without this fix GHC performance regressed by a noticeably amount
because the `zip` rule was not brought into scope eagerly enough which
led to a further series of unfortunate events in the simplifer which
tipped `substTyWithCoVars` over the edge of the size threshold, stopped
it being inlined and increased allocations by 10% in some cases.

Furthermore, this change is noticeably in the testsuite as it changes
T19790 so that the `length` rules from GHC.List fires earlier.

-------------------------
Metric Increase:
    T9961
-------------------------

- - - - -
b8046195 by Matthew Pickering at 2022-02-26T02:06:52-05:00
Improve efficiency of extending a RuleEnv with a new RuleBase

Essentially we apply the identity:

> lookupNameEnv n (plusNameEnv_C (++) rb1 rb2)
>   = lookupNameEnv n rb1 ++ lookupNameEnv n rb2

The latter being more efficient as we don't construct an intermediate
map.

This is now quite important as each time we try and apply rules we need
to combine the current EPS RuleBase with the HPT and ModGuts rule bases.

- - - - -
033e9f0f by sheaf at 2022-02-26T02:07:30-05:00
Error on anon wildcards in tcAnonWildCardOcc

  The code in tcAnonWildCardOcc assumed that it could never encounter
  anonymous wildcards in illegal positions, because the renamer would
  have ruled them out. However, it's possible to sneak past the checks
  in the renamer by using Template Haskell. It isn't possible to simply
  pass on additional information when renaming Template Haskell
  brackets, because we don't know in advance in what context the bracket
  will be spliced in (see test case T15433b). So we accept that we might
  encounter these bogus wildcards in the typechecker and throw the
  appropriate error.

  This patch also migrates the error messages for illegal wildcards in
  types to use the diagnostic infrastructure.

  Fixes #15433

- - - - -
32d8fe3a by sheaf at 2022-02-26T14:15:33+01:00
Core Lint: ensure primops can be eta-expanded

This patch adds a check to Core Lint, checkCanEtaExpand,
which ensures that primops and other wired-in functions with
no binding such as unsafeCoerce#, oneShot, rightSection...
can always be eta-expanded, by checking that the remaining
argument types have a fixed RuntimeRep.

Two subtleties came up:

  - the notion of arity in Core looks through newtypes, so we may
    need to unwrap newtypes in this check,
  - we want to avoid calling hasNoBinding on something whose unfolding
    we are in the process of linting, as this would cause a loop;
    to avoid this we add some information to the Core Lint environment
    that holds this information.

Fixes #20480

- - - - -
0a80b436 by Peter Trommler at 2022-02-26T17:21:59-05:00
testsuite: Require LLVM for T15155l

- - - - -
38cb920e by Oleg Grenrus at 2022-02-28T07:14:04-05:00
Add Monoid a => Monoid (STM a) instance

- - - - -
d734ef8f by Hécate Moonlight at 2022-02-28T07:14:42-05:00
Make modules in base stable.

fix #18963

- - - - -
fbf005e9 by Sven Tennie at 2022-02-28T19:16:01-05:00
Fix some hlint issues in ghc-heap

This does not fix all hlint issues as the criticised index and
length expressions seem to be fine in context.

- - - - -
adfddf7d by Matthew Pickering at 2022-02-28T19:16:36-05:00
hadrian: Suggest to the user to run ./configure if missing a setting

If a setting is missing from the configuration file it's likely the user
needs to reconfigure.

Fixes #20476

- - - - -
4f0208e5 by Andreas Klebinger at 2022-02-28T19:17:12-05:00
CLabel cleanup:

Remove these smart constructors for these reasons:
* mkLocalClosureTableLabel : Does the same as the non-local variant.
* mkLocalClosureLabel      : Does the same as the non-local variant.
* mkLocalInfoTableLabel    : Decide if we make a local label based on the name
                             and just use mkInfoTableLabel everywhere.

- - - - -
065419af by Matthew Pickering at 2022-02-28T19:17:47-05:00
linking: Don't pass --hash-size and --reduce-memory-overhead to ld

These flags were added to help with the high linking cost of the old
split-objs mode. Now we are using split-sections these flags appear to
make no difference to memory usage or time taken to link.

I tested various configurations linking together the ghc library with
-split-sections enabled.

| linker | time (s) |
| ------ | ------   |
| gold   | 0.95     |
| ld     | 1.6      |
| ld (hash-size = 31, reduce-memory-overheads) | 1.6 |
| ldd    | 0.47     |

Fixes #20967

- - - - -
3e65ef05 by Teo Camarasu at 2022-02-28T19:18:27-05:00
template-haskell: fix typo in docstring for Overlap

- - - - -
80f9133e by Teo Camarasu at 2022-02-28T19:18:27-05:00
template-haskell: fix docstring for Bytes

It seems like a commented out section of code was accidentally included
in the docstring for a field.

- - - - -
54774268 by Matthew Pickering at 2022-03-01T16:23:10-05:00
Fix longstanding issue with moduleGraphNodes - no hs-boot files case

In the case when we tell moduleGraphNodes to drop hs-boot files the idea
is to collapse hs-boot files into their hs file nodes. In the old code

* nodeDependencies changed edges from IsBoot to NonBoot
* moduleGraphNodes just dropped boot file nodes

The net result is that any dependencies of the hs-boot files themselves
were dropped. The correct thing to do is

* nodeDependencies changes edges from IsBoot to NonBoot
* moduleGraphNodes merges dependencies of IsBoot and NonBoot nodes.

The result is a properly quotiented dependency graph which contains no
hs-boot files nor hs-boot file edges.

Why this didn't cause endless issues when compiling with boot files, we
will never know.

- - - - -
c84dc506 by Matthew Pickering at 2022-03-01T16:23:10-05:00
driver: Properly add an edge between a .hs and its hs-boot file

As noted in #21071 we were missing adding this edge so there were
situations where the .hs file would get compiled before the .hs-boot
file which leads to issues with -j.

I fixed this properly by adding the edge in downsweep so the definition
of nodeDependencies can be simplified to avoid adding this dummy edge
in.

There are plenty of tests which seem to have these redundant boot files
anyway so no new test. #21094 tracks the more general issue of
identifying redundant hs-boot and SOURCE imports.

- - - - -
7aeb6d29 by sheaf at 2022-03-01T16:23:51-05:00
Core Lint: collect args through floatable ticks

We were not looking through floatable ticks when collecting arguments in
Core Lint, which caused `checkCanEtaExpand` to fail on something like:

```haskell
reallyUnsafePtrEquality
  = \ @a ->
      (src<loc> reallyUnsafePtrEquality#)
        @Lifted @a @Lifted @a
```

We fix this by using `collectArgsTicks tickishFloatable` instead of
`collectArgs`, to be consistent with the behaviour of eta expansion
outlined in Note [Eta expansion and source notes] in GHC.Core.Opt.Arity.

Fixes #21152.

- - - - -
75caafaa by Matthew Pickering at 2022-03-02T01:14:59-05:00
Ticky profiling improvements.

This adds a number of changes to ticky-ticky profiling.

When an executable is profiled with IPE profiling it's now possible to
associate id-related ticky counters to their source location.
This works by emitting the info table address as part of the counter
which can be looked up in the IPE table.

Add a `-ticky-ap-thunk` flag. This flag prevents the use of some standard thunks
which are precompiled into the RTS. This means reduced cache locality
and increased code size. But it allows better attribution of execution
cost to specific source locations instead of simple attributing it to
the standard thunk.

ticky-ticky now uses the `arg` field to emit additional information
about counters in json format. When ticky-ticky is used in combination
with the eventlog eventlog2html can be used to generate a html table
from the eventlog similar to the old text output for ticky-ticky.

- - - - -
aeea6bd5 by doyougnu at 2022-03-02T01:15:39-05:00
StgToCmm.cgTopBinding: no isNCG, use binBlobThresh

This is a one line change. It is a fixup from MR!7325, was pointed out
in review of MR!7442, specifically: https://gitlab.haskell.org/ghc/ghc/-/merge_requests/7442#note_406581

The change removes isNCG check from cgTopBinding. Instead it changes the
type of binBlobThresh in DynFlags from Word to Maybe Word, where a Just
0 or a Nothing indicates an infinite threshold and thus the disable
CmmFileEmbed case in the original check.

This improves the cohesion of the module because more NCG related
Backend stuff is moved into, and checked in, StgToCmm.Config. Note, that
the meaning of a Just 0 or a Nothing in binBlobThresh is indicated in a
comment next to its field in GHC.StgToCmm.Config.

DynFlags: binBlobThresh: Word -> Maybe Word

StgToCmm.Config: binBlobThesh add not ncg check

DynFlags.binBlob: move Just 0 check to dflags init

StgToCmm.binBlob: only check isNCG, Just 0 check to dflags

StgToCmm.Config: strictify binBlobThresh

- - - - -
b27b2af3 by sheaf at 2022-03-02T14:08:36-05:00
Introduce ConcreteTv metavariables

  This patch introduces a new kind of metavariable, by adding the
  constructor `ConcreteTv` to `MetaInfo`. A metavariable with
  `ConcreteTv` `MetaInfo`, henceforth a concrete metavariable, can only
  be unified with a type that is concrete (that is, a type that answers
  `True` to `GHC.Core.Type.isConcrete`).

  This solves the problem of dangling metavariables in `Concrete#`
  constraints: instead of emitting `Concrete# ty`, which contains a
  secret existential metavariable, we simply emit a primitive equality
  constraint `ty ~# concrete_tv` where `concrete_tv` is a fresh concrete
  metavariable.

  This means we can avoid all the complexity of canonicalising
  `Concrete#` constraints, as we can just re-use the existing machinery
  for `~#`.

  To finish things up, this patch then removes the `Concrete#` special
  predicate, and instead introduces the special predicate `IsRefl#`
  which enforces that a coercion is reflexive.
  Such a constraint is needed because the canonicaliser is quite happy
  to rewrite an equality constraint such as `ty ~# concrete_tv`, but
  such a rewriting is not handled by the rest of the compiler currently,
  as we need to make use of the resulting coercion, as outlined in the
  FixedRuntimeRep plan.

  The big upside of this approach (on top of simplifying the code)
  is that we can now selectively implement PHASE 2 of FixedRuntimeRep,
  by changing individual calls of `hasFixedRuntimeRep_MustBeRefl` to
  `hasFixedRuntimeRep` and making use of the obtained coercion.

- - - - -
81b7c436 by Matthew Pickering at 2022-03-02T14:09:13-05:00
Make -dannot-lint not panic on let bound type variables

After certain simplifier passes we end up with let bound type variables
which are immediately inlined in the next pass. The core diff utility
implemented by -dannot-lint failed to take these into account and
paniced.

Progress towards #20965

- - - - -
f596c91a by sheaf at 2022-03-02T14:09:51-05:00
Improve out-of-order inferred type variables

  Don't instantiate type variables for :type in
  `GHC.Tc.Gen.App.tcInstFun`, to avoid inconsistently instantianting
  `r1` but not `r2` in the type

    forall {r1} (a :: TYPE r1) {r2} (b :: TYPE r2). ...

  This fixes #21088.

  This patch also changes the primop pretty-printer to ensure
  that we put all the inferred type variables first. For example,
  the type of reallyUnsafePtrEquality# is now

    forall {l :: Levity} {k :: Levity}
           (a :: TYPE (BoxedRep l))
           (b :: TYPE (BoxedRep k)).
      a -> b -> Int#

  This means we avoid running into issue #21088 entirely with
  the types of primops. Users can still write a type signature where
  the inferred type variables don't come first, however.

  This change to primops had a knock-on consequence, revealing that
  we were sometimes performing eta reduction on keepAlive#.
  This patch updates tryEtaReduce to avoid eta reducing functions
  with no binding, bringing it in line with tryEtaReducePrep,
  and thus fixing #21090.

- - - - -
1617fed3 by Richard Eisenberg at 2022-03-02T14:10:28-05:00
Make inert_cycle_breakers into a stack.

Close #20231.

- - - - -
c8652a0a by Richard Eisenberg at 2022-03-02T14:11:03-05:00
Make Constraint not *apart* from Type.

More details in Note [coreView vs tcView]

Close #21092.

- - - - -
91a10cb0 by doyougnu at 2022-03-02T14:11:43-05:00
GenStgAlt 3-tuple synonym --> Record type

This commit alters GenStgAlt from a type synonym to a Record with field
accessors. In pursuit of #21078, this is not a required change but cleans
up several areas for nicer code in the upcoming js-backend, and in GHC
itself.

GenStgAlt: 3-tuple -> record

Stg.Utils: GenStgAlt 3-tuple -> record

Stg.Stats: StgAlt 3-tuple --> record

Stg.InferTags.Rewrite: StgAlt 3-tuple -> record

Stg.FVs: GenStgAlt 3-tuple -> record

Stg.CSE: GenStgAlt 3-tuple -> record

Stg.InferTags: GenStgAlt 3-tuple --> record

Stg.Debug: GenStgAlt 3-tuple --> record

Stg.Lift.Analysis: GenStgAlt 3-tuple --> record

Stg.Lift: GenStgAlt 3-tuple --> record

ByteCode.Instr: GenStgAlt 3-tuple --> record

Stg.Syntax: add GenStgAlt helper functions

Stg.Unarise: GenStgAlt 3-tuple --> record

Stg.BcPrep: GenStgAlt 3-tuple --> record

CoreToStg: GenStgAlt 3-tuple --> record

StgToCmm.Expr: GenStgAlt 3-tuple --> record

StgToCmm.Bind: GenStgAlt 3-tuple --> record

StgToByteCode: GenStgAlt 3-tuple --> record

Stg.Lint: GenStgAlt 3-tuple --> record

Stg.Syntax: strictify GenStgAlt

GenStgAlt: add haddock, some cleanup

fixup: remove calls to pure, single ViewPattern

StgToByteCode: use case over viewpatterns

- - - - -
73864f00 by Matthew Pickering at 2022-03-02T14:12:19-05:00
base: Remove default method from bitraversable

The default instance leads to an infinite loop.
bisequenceA is defined in terms of bisquence which is defined in terms
of bitraverse.

```
bitraverse f g
= (defn of bitraverse)
bisequenceA . bimap f g
= (defn of bisequenceA)
bitraverse id id . bimap f g
= (defn of bitraverse)
...
```

Any instances defined without an explicitly implementation are currently
broken, therefore removing it will alert users to an issue in their
code.

CLC issue: https://github.com/haskell/core-libraries-committee/issues/47

Fixes #20329 #18901

- - - - -
9579bf35 by Matthew Pickering at 2022-03-02T14:12:54-05:00
ci: Add check to CI to ensure compiler uses correct BIGNUM_BACKEND

- - - - -
c48a7c3a by Sylvain Henry at 2022-03-03T07:37:12-05:00
Use Word64# primops in Word64 Num instance

Taken froù!3658

- - - - -
ce65d0cc by Matthew Pickering at 2022-03-03T07:37:48-05:00
hadrian: Correctly set whether we have a debug compiler when running tests

For example, running the `slow-validate` flavour would incorrectly run
the T16135 test which would fail with an assertion error, despite the
fact that is should be skipped when we have a debug compiler.

- - - - -
e0c3e757 by Matthew Pickering at 2022-03-03T13:48:41-05:00
docs: Add note to unsafeCoerce function that you might want to use coerce [skip ci]

Fixes #15429

- - - - -
559d4cf3 by Matthew Pickering at 2022-03-03T13:49:17-05:00
docs: Add note to RULES documentation about locally bound variables [skip ci]

Fixes #20100

- - - - -
c534b3dd by Matthew Pickering at 2022-03-03T13:49:53-05:00
Replace ad-hoc CPP with constant from GHC.Utils.Constant

Fixes #21154

- - - - -
de56cc7e by Krzysztof Gogolewski at 2022-03-04T12:44:26-05:00
Update documentation of LiberalTypeSynonyms

We no longer require LiberalTypeSynonyms to use 'forall' or an unboxed
tuple in a synonym.

I also removed that kind checking before expanding synonyms "could be changed".
This was true when type synonyms were thought of macros, but with
the extensions such as SAKS or matchability I don't see it changing.

- - - - -
c0a39259 by Simon Jakobi at 2022-03-04T12:45:01-05:00
base: Mark GHC.Bits not-home for haddock

Most (all) of the exports are re-exported from
the preferable Data.Bits.

- - - - -
3570eda5 by Sylvain Henry at 2022-03-04T12:45:42-05:00
Fix comments about Int64/Word64 primops

- - - - -
6f84ee33 by Artem Pelenitsyn at 2022-03-05T01:06:47-05:00
remove MonadFail instances of ST

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

The instances had `fail` implemented in terms of `error`, whereas the
idea of the `MonadFail` class is that the `fail` method should be
implemented in terms of the monad itself.

- - - - -
584cd5ae by sheaf at 2022-03-05T01:07:25-05:00
Don't allow Float#/Double# literal patterns

  This patch does the following two things:

    1. Fix the check in Core Lint to properly throw an error when it
       comes across Float#/Double# literal patterns. The check
       was incorrect before, because it expected the type to be
       Float/Double instead of Float#/Double#.

    2. Add an error in the parser when the user writes a floating-point
       literal pattern such as `case x of { 2.0## -> ... }`.

  Fixes #21115

- - - - -
706deee0 by Greg Steuck at 2022-03-05T17:44:10-08:00
Make T20214 terminate promptly be setting input to /dev/null

It was hanging and timing out on OpenBSD before.

- - - - -
14e90098 by Simon Peyton Jones at 2022-03-07T14:05:41-05:00
Always generalise top-level bindings

Fix #21023 by always generalising top-level binding; change
the documentation of -XMonoLocalBinds to match.

- - - - -
c9c31c3c by Matthew Pickering at 2022-03-07T14:06:16-05:00
hadrian: Add little flavour transformer to build stage2 with assertions

This can be useful to build a `perf+assertions` build or even better
`default+no_profiled_libs+omit_pragmas+assertions`.

- - - - -
89c14a6c by Matthew Pickering at 2022-03-07T14:06:16-05:00
ci: Convert all deb10 make jobs into hadrian jobs

This is the first step in converting all the CI configs to use hadrian
rather than make. (#21129)

The metrics increase due to hadrian using --hyperlinked-source for
haddock builds. (See #21156)

-------------------------
Metric Increase:
    haddock.Cabal
    haddock.base
    haddock.compiler
-------------------------

- - - - -
7bfae2ee by Matthew Pickering at 2022-03-07T14:06:16-05:00
Replace use of BIN_DIST_PREP_TAR_COMP with BIN_DIST_NAME

And adds a check to make sure we are not accidently settings
BIN_DIST_PREP_TAR_COMP when using hadrian.

- - - - -
5b35ca58 by Matthew Pickering at 2022-03-07T14:06:16-05:00
Fix gen_contents_index logic for hadrian bindist

- - - - -
273bc133 by Krzysztof Gogolewski at 2022-03-07T14:06:52-05:00
Fix reporting constraints in pprTcSolverReportMsg

'no_instance_msg' and 'no_deduce_msg' were omitting the first wanted.

- - - - -
5874a30a by Simon Jakobi at 2022-03-07T14:07:28-05:00
Improve setBit for Natural

Previously the default definition was used, which involved allocating
intermediate Natural values.

Fixes #21173.

- - - - -
7a02aeb8 by Matthew Pickering at 2022-03-07T14:08:03-05:00
Remove leftover trace in testsuite

- - - - -
6ce6c250 by Andreas Klebinger at 2022-03-07T23:48:56-05:00
Expand and improve the Note [Strict Worker Ids].

I've added an explicit mention of the invariants surrounding those. As well as adding
more direct cross references to the Strict Field Invariant.

- - - - -
d0f892fe by Ryan Scott at 2022-03-07T23:49:32-05:00
Delete GenericKind_ in favor of GenericKind_DC

When deriving a `Generic1` instance, we need to know what the last type
variable of a data type is. Previously, there were two mechanisms to determine
this information:

* `GenericKind_`, where `Gen1_` stored the last type variable of a data type
   constructor (i.e., the `tyConTyVars`).
* `GenericKind_DC`, where `Gen1_DC` stored the last universally quantified
  type variable in a data constructor (i.e., the `dataConUnivTyVars`).

These had different use cases, as `GenericKind_` was used for generating
`Rep(1)` instances, while `GenericKind_DC` was used for generating `from(1)`
and `to(1)` implementations. This was already a bit confusing, but things went
from confusing to outright wrong after !6976. This is because after !6976,
the `deriving` machinery stopped using `tyConTyVars` in favor of
`dataConUnivTyVars`. Well, everywhere with the sole exception of
`GenericKind_`, which still continued to use `tyConTyVars`. This lead to
disaster when deriving a `Generic1` instance for a GADT family instance, as
the `tyConTyVars` do not match the `dataConUnivTyVars`. (See #21185.)

The fix is to stop using `GenericKind_` and replace it with `GenericKind_DC`.
For the most part, this proves relatively straightforward. Some highlights:

* The `forgetArgVar` function was deleted entirely, as it no longer proved
  necessary after `GenericKind_`'s demise.
* The substitution that maps from the last type variable to `Any` (see
  `Note [Generating a correctly typed Rep instance]`) had to be moved from
  `tc_mkRepTy` to `tc_mkRepFamInsts`, as `tc_mkRepTy` no longer has access to
  the last type variable.

Fixes #21185.

- - - - -
a60ddffd by Matthew Pickering at 2022-03-08T22:51:37+00:00
Move bootstrap and cabal-reinstall test jobs to nightly

CI is creaking under the pressure of too many jobs so attempt to reduce
the strain by removing a couple of jobs.

- - - - -
7abe3288 by Matthew Pickering at 2022-03-09T10:24:15+00:00
Add 10 minute timeout to linters job

- - - - -
3cf75ede by Matthew Pickering at 2022-03-09T10:24:16+00:00
Revert "hadrian: Correctly set whether we have a debug compiler when running tests"

Needing the arguments for "GHC/Utils/Constant.hs" implies a dependency
on the previous stage compiler. Whilst we work out how to get around
this I will just revert this commit (as it only affects running the
testsuite in debug way).

This reverts commit ce65d0cceda4a028f30deafa3c39d40a250acc6a.

- - - - -
18b9ba56 by Matthew Pickering at 2022-03-09T11:07:23+00:00
ci: Fix save_cache function

Each interation of saving the cache would copy the whole `cabal` store
into a subfolder in the CACHE_DIR rather than copying the contents of
the cabal store into the cache dir. This resulted in a cache which
looked like:

```
/builds/ghc/ghc/cabal-cache/cabal/cabal/cabal/cabal/cabal/cabal/cabal/cabal/cabal/cabal/
```

So it would get one layer deeper every CI run and take longer and longer
to compress.

- - - - -
bc684dfb by Ben Gamari at 2022-03-10T03:20:07-05:00
mr-template: Mention timeframe for review
- - - - -
7f5f4ede by Vladislav Zavialov at 2022-03-10T03:20:43-05:00
Bump submodules: containers, exceptions

GHC Proposal #371 requires TypeOperators to use type equality a~b.
This submodule update pulls in the appropriate forward-compatibility
changes in 'libraries/containers' and 'libraries/exceptions'

- - - - -
8532b8a9 by Matthew Pickering at 2022-03-10T03:20:43-05:00
Add an inline pragma to lookupVarEnv

The containers bump reduced the size of the Data.IntMap.Internal.lookup
function so that it no longer experienced W/W. This means that the size
of lookupVarEnv increased over the inlining threshold and it wasn't
inlined into the hot code path in substTyVar.

See containers#821, #21159 and !7638 for some more explanation.

-------------------------
Metric Decrease:
    LargeRecord
    T12227
    T13386
    T15703
    T18223
    T5030
    T8095
    T9872a
    T9872b
    T9872c
    TcPlugin_RewritePerf
-------------------------

- - - - -
844cf1e1 by Matthew Pickering at 2022-03-10T03:20:43-05:00
Normalise output of T10970 test

The output of this test changes each time the containers submodule
version updates. It's easier to apply the version normaliser so that
the test checks that there is a version number, but not which one it is.

- - - - -
24b6af26 by Ryan Scott at 2022-03-11T19:56:28-05:00
Refactor tcDeriving to generate tyfam insts before any bindings

Previously, there was an awful hack in `genInst` (now called `genInstBinds`
after this patch) where we had to return a continutation rather than directly
returning the bindings for a derived instance. This was done for staging
purposes, as we had to first infer the instance contexts for derived instances
and then feed these contexts into the continuations to ensure the generated
instance bindings had accurate instance contexts.
`Note [Staging of tcDeriving]` in `GHC.Tc.Deriving` described this confusing
state of affairs.

The root cause of this confusing design was the fact that `genInst` was trying
to generate instance bindings and associated type family instances for derived
instances simultaneously. This really isn't possible, however: as
`Note [Staging of tcDeriving]` explains, one needs to have access to the
associated type family instances before one can properly infer the instance
contexts for derived instances. The use of continuation-returning style was an
attempt to circumvent this dependency, but it did so in an awkward way.

This patch detangles this awkwardness by splitting up `genInst` into two
functions: `genFamInsts` (for associated type family instances) and
`genInstBinds` (for instance bindings). Now, the `tcDeriving` function calls
`genFamInsts` and brings all the family instances into scope before calling
`genInstBinds`. This removes the need for the awkward continuation-returning
style seen in the previous version of `genInst`, making the code easier to
understand.

There are some knock-on changes as well:

1. `hasStockDeriving` now needs to return two separate functions: one that
   describes how to generate family instances for a stock-derived instance,
   and another that describes how to generate the instance bindings. I factored
   out this pattern into a new `StockGenFns` data type.
2. While documenting `StockGenFns`, I realized that there was some
   inconsistency regarding which `StockGenFns` functions needed which
   arguments. In particular, the function in `GHC.Tc.Deriv.Generics` which
   generates `Rep(1)` instances did not take a `SrcSpan` like other `gen_*`
   functions did, and it included an extra `[Type]` argument that was entirely
   redundant. As a consequence, I refactored the code in
   `GHC.Tc.Deriv.Generics` to more closely resemble other `gen_*` functions.
   A happy result of all this is that all `StockGenFns` functions now take
   exactly the same arguments, which makes everything more uniform.

This is purely a refactoring that should not have any effect on user-observable
behavior. The new design paves the way for an eventual fix for #20719.

- - - - -
62caaa9b by Ben Gamari at 2022-03-11T19:57:03-05:00
gitlab-ci: Use the linters image in hlint job

As the `hlint` executable is only available in the linters image.

Fixes #21146.

- - - - -
4abd7eb0 by Matthew Pickering at 2022-03-11T19:57:38-05:00
Remove partOfGhci check in the loader

This special logic has been part of GHC ever since template haskell was
introduced in 9af77fa423926fbda946b31e174173d0ec5ebac8.

It's hard to believe in any case that this special logic pays its way at
all. Given

* The list is out-of-date, which has potential to lead to miscompilation
  when using "editline", which was removed in 2010 (46aed8a4).
* The performance benefit seems negligable as each load only happens
  once anyway and packages specified by package flags are preloaded into
  the linker state at the start of compilation.

Therefore we just remove this logic.

Fixes #19791

- - - - -
c40cbaa2 by Andreas Klebinger at 2022-03-11T19:58:14-05:00
Improve -dtag-inference-checks checks.

FUN closures don't get tagged when evaluated. So no point in checking their
tags.

- - - - -
ab00d23b by Simon Jakobi at 2022-03-11T19:58:49-05:00
Improve clearBit and complementBit for Natural

Also optimize bigNatComplementBit#.

Fixes #21175, #21181, #21194.

- - - - -
a6d8facb by Sebastian Graf at 2022-03-11T19:59:24-05:00
gitignore all (build) directories headed by _

- - - - -
524795fe by Sebastian Graf at 2022-03-11T19:59:24-05:00
Demand: Document why we need three additional equations of multSubDmd

- - - - -
6bdcd557 by Cheng Shao at 2022-03-11T20:00:01-05:00
CmmToC: make 64-bit word splitting for 32-bit targets respect target endianness

This used to been broken for little-endian targets.

- - - - -
9e67c69e by Cheng Shao at 2022-03-11T20:00:01-05:00
CmmToC: fix Double# literal payload for 32-bit targets

Contrary to the legacy comment, the splitting didn't happen and we
ended up with a single StgWord64 literal in the output code! Let's
just do the splitting here.

- - - - -
1eee2e28 by Cheng Shao at 2022-03-11T20:00:01-05:00
CmmToC: use __builtin versions of memcpyish functions to fix type mismatch

Our memcpyish primop's type signatures doesn't match the C type
signatures. It's not a problem for typical archs, since their C ABI
permits dropping the result, but it doesn't work for wasm. The
previous logic would cast the memcpyish function pointer to an
incorrect type and perform an indirect call, which results in a
runtime trap on wasm.

The most straightforward fix is: don't emit EFF_ for memcpyish
functions. Since we don't want to include extra headers in .hc to
bring in their prototypes, we can just use the __builtin versions.

- - - - -
9d8d4837 by Cheng Shao at 2022-03-11T20:00:01-05:00
CmmToC: emit __builtin_unreachable() when CmmSwitch doesn't contain fallback case

Otherwise the C compiler may complain "warning: non-void function does
not return a value in all control paths [-Wreturn-type]".

- - - - -
27da5540 by Cheng Shao at 2022-03-11T20:00:01-05:00
CmmToC: make floatToWord32/doubleToWord64 faster

Use castFloatToWord32/castDoubleToWord64 in base to perform the
reinterpret cast.

- - - - -
c98e8332 by Cheng Shao at 2022-03-11T20:00:01-05:00
CmmToC: fix -Wunused-value warning in ASSIGN_BaseReg

When ASSIGN_BaseReg is a no-op, we shouldn't generate any C code,
otherwise C compiler complains a bunch of -Wunused-value warnings when
doing unregisterised codegen.

- - - - -
5932247c by Ben Gamari at 2022-03-11T20:00:36-05:00
users guide: Eliminate spurious \spxentry mentions

We were failing to pass the style file to `makeindex`, as is done by
the mklatex configuration generated by Sphinx.

Fixes #20913.

- - - - -
e40cf4ef by Simon Jakobi at 2022-03-11T20:01:11-05:00
ghc-bignum: Tweak integerOr

The result of ORing two BigNats is always greater or equal to the
larger of the two. Therefore it is safe to skip the magnitude checks of
integerFromBigNat#.

- - - - -
cf081476 by Vladislav Zavialov at 2022-03-12T07:02:40-05:00
checkUnboxedLitPat: use non-fatal addError

This enables GHC to report more parse errors in a single pass.

- - - - -
7fe07143 by Andreas Klebinger at 2022-03-12T07:03:16-05:00
Rename -fprof-late-ccs to -fprof-late

- - - - -
88a94541 by Sylvain Henry at 2022-03-12T07:03:56-05:00
Hadrian: avoid useless allocations in trackArgument

Cf ticky report before the change:

    Entries      Alloc    Alloc'd  Non-void Arguments      STG Name
--------------------------------------------------------------------------------
     696987   29044128          0   1 L                    main:Target.trackArgument_go5{v r24kY} (fun)

- - - - -
2509d676 by Sylvain Henry at 2022-03-12T07:04:36-05:00
Hadrian: avoid allocating in stageString (#19209)

- - - - -
c062fac0 by Sylvain Henry at 2022-03-12T07:04:36-05:00
Hadrian: remove useless imports

Added for no reason in 7ce1b694f7be7fbf6e2d7b7eb0639e61fbe358c6

- - - - -
c82fb934 by Sylvain Henry at 2022-03-12T07:05:16-05:00
Hadrian: avoid allocations in WayUnit's Read instance (#19209)

- - - - -
ed04aed2 by Sylvain Henry at 2022-03-12T07:05:16-05:00
Hadrian: use IntSet Binary instance for Way (#19209)

- - - - -
ad835531 by Simon Peyton Jones at 2022-03-13T18:12:12-04:00
Fix bug in weak loop-breakers in OccurAnal

Note [Weak loop breakers] explains why we need to track variables free
in RHS of rules.  But we need to do this for /inactive/ rules as well
as active ones, unlike the rhs_fv_env stuff.

So we now have two fields in node Details, one for free vars of
active rules, and one for free vars of all rules.

This was shown up by #20820, which is now fixed.

- - - - -
76b94b72 by Sebastian Graf at 2022-03-13T18:12:48-04:00
Worker/wrapper: Preserve float barriers (#21150)

Issue #21150 shows that worker/wrapper allocated a worker function for a
function with multiple calls that said "called at most once" when the first
argument was absent. That's bad!

This patch makes it so that WW preserves at least one non-one-shot value lambda
(see `Note [Preserving float barriers]`) by passing around `void#` in place of
absent arguments.

Fixes #21150.

Since the fix is pretty similar to `Note [Protecting the last value argument]`,
I put the logic in `mkWorkerArgs`. There I realised (#21204) that
`-ffun-to-thunk` is basically useless with `-ffull-laziness`, so I deprecated
the flag, simplified and split into `needsVoidWorkerArg`/`addVoidWorkerArg`.
SpecConstr is another client of that API.

Fixes #21204.

Metric Decrease:
    T14683

- - - - -
97db789e by romes at 2022-03-14T11:36:39-04:00
Fix up Note [Bind free vars]

Move GHC-specific comments from Language.Haskell.Syntax.Binds to
GHC.Hs.Binds

It looks like the Note was deleted but there were actually two copies of
it. L.H.S.B no longer references it, and GHC.Hs.Binds keeps an updated
copy. (See #19252)

There are other duplicated notes -- they will be fixed in the next
commit

- - - - -
135888dd by romes at 2022-03-14T11:36:39-04:00
TTG Pull AbsBinds and ABExport out of the main AST

AbsBinds and ABExport both depended on the typechecker, and were thus
removed from the main AST Expr.

CollectPass now has a new function `collectXXHsBindsLR` used for the new
HsBinds extension point

Bumped haddock submodule to work with AST changes.

The removed Notes from Language.Haskell.Syntax.Binds were duplicated
(and not referenced) and the copies in GHC.Hs.Binds are kept (and
referenced there). (See #19252)

- - - - -
106413f0 by sheaf at 2022-03-14T11:37:21-04:00
Add two coercion optimisation perf tests

- - - - -
8eadea67 by sheaf at 2022-03-14T15:08:24-04:00
Fix isLiftedType_maybe and handle fallout

As #20837 pointed out, `isLiftedType_maybe` returned `Just False` in
many situations where it should return `Nothing`, because it didn't
take into account type families or type variables.

In this patch, we fix this issue. We rename `isLiftedType_maybe` to
`typeLevity_maybe`, which now returns a `Levity` instead of a boolean.
We now return `Nothing` for types with kinds of the form
`TYPE (F a1 ... an)` for a type family `F`, as well as
`TYPE (BoxedRep l)` where `l` is a type variable.

This fix caused several other problems, as other parts of the compiler
were relying on `isLiftedType_maybe` returning a `Just` value, and were
now panicking after the above fix. There were two main situations in
which panics occurred:

  1. Issues involving the let/app invariant. To uphold that invariant,
     we need to know whether something is lifted or not. If we get an
     answer of `Nothing` from `isLiftedType_maybe`, then we don't know
     what to do. As this invariant isn't particularly invariant, we
     can change the affected functions to not panic, e.g. by behaving
     the same in the `Just False` case and in the `Nothing` case
     (meaning: no observable change in behaviour compared to before).

  2. Typechecking of data (/newtype) constructor patterns. Some programs
     involving patterns with unknown representations were accepted, such
     as T20363. Now that we are stricter, this caused further issues,
     culminating in Core Lint errors. However, the behaviour was
     incorrect the whole time; the incorrectness only being revealed by
     this change, not triggered by it.

     This patch fixes this by overhauling where the representation
     polymorphism involving pattern matching are done. Instead of doing
     it in `tcMatches`, we instead ensure that the `matchExpected`
     functions such as `matchExpectedFunTys`, `matchActualFunTySigma`,
     `matchActualFunTysRho` allow return argument pattern types which
     have a fixed RuntimeRep (as defined in Note [Fixed RuntimeRep]).
     This ensures that the pattern matching code only ever handles types
     with a known runtime representation. One exception was that
     patterns with an unknown representation type could sneak in via
     `tcConPat`, which points to a missing representation-polymorphism
     check, which this patch now adds.

     This means that we now reject the program in #20363, at least until
     we implement PHASE 2 of FixedRuntimeRep (allowing type families in
     RuntimeRep positions). The aforementioned refactoring, in which
     checks have been moved to `matchExpected` functions, is a first
     step in implementing PHASE 2 for patterns.

Fixes #20837

- - - - -
8ff32124 by Sebastian Graf at 2022-03-14T15:09:01-04:00
DmdAnal: Don't unbox recursive data types (#11545)

As `Note [Demand analysis for recursive data constructors]` describes, we now
refrain from unboxing recursive data type arguments, for two reasons:

 1. Relating to run/alloc perf: Similar to
    `Note [CPR for recursive data constructors]`, it seldomly improves run/alloc
    performance if we just unbox a finite number of layers of a potentially huge
    data structure.
 2. Relating to ghc/alloc perf: Inductive definitions on single-product
    recursive data types like the one in T11545 will (diverge, and) have very
    deep demand signatures before any other abortion mechanism in Demand
    analysis is triggered. That leads to great and unnecessary churn on Demand
    analysis when ultimately we will never make use of any nested strictness
    information anyway.

Conclusion: Discard nested demand and boxity information on such recursive types
with the help of `Note [Detecting recursive data constructors]`.

I also implemented `GHC.Types.Unique.MemoFun.memoiseUniqueFun` in order to avoid
the overhead of repeated calls to `GHC.Core.Opt.WorkWrap.Utils.isRecDataCon`.
It's nice and simple and guards against some smaller regressions in T9233 and
T16577.

ghc/alloc performance-wise, this patch is a very clear win:

                               Test    Metric          value      New value Change
---------------------------------------------------------------------------------------
                LargeRecord(normal) ghc/alloc  6,141,071,720  6,099,871,216  -0.7%
MultiLayerModulesTH_OneShot(normal) ghc/alloc  2,740,973,040  2,705,146,640  -1.3%
                     T11545(normal) ghc/alloc    945,475,492     85,768,928 -90.9% GOOD
                     T13056(optasm) ghc/alloc    370,245,880    326,980,632 -11.7% GOOD
                     T18304(normal) ghc/alloc     90,933,944     76,998,064 -15.3% GOOD
                     T9872a(normal) ghc/alloc  1,800,576,840  1,792,348,760  -0.5%
                     T9872b(normal) ghc/alloc  2,086,492,432  2,073,991,848  -0.6%
                     T9872c(normal) ghc/alloc  1,750,491,240  1,737,797,832  -0.7%
       TcPlugin_RewritePerf(normal) ghc/alloc  2,286,813,400  2,270,957,896  -0.7%

                          geo. mean                                          -2.9%

No noteworthy change in run/alloc either.

NoFib results show slight wins, too:

--------------------------------------------------------------------------------
        Program         Allocs    Instrs
--------------------------------------------------------------------------------
    constraints          -1.9%     -1.4%
          fasta          -3.6%     -2.7%
reverse-complem          -0.3%     -0.9%
       treejoin          -0.0%     -0.3%
--------------------------------------------------------------------------------
            Min          -3.6%     -2.7%
            Max          +0.1%     +0.1%
 Geometric Mean          -0.1%     -0.1%

Metric Decrease:
    T11545
    T13056
    T18304

- - - - -
ab618309 by Vladislav Zavialov at 2022-03-15T18:34:38+03:00
Export (~) from Data.Type.Equality (#18862)

* Users can define their own (~) type operator
* Haddock can display documentation for the built-in (~)
* New transitional warnings implemented:
    -Wtype-equality-out-of-scope
    -Wtype-equality-requires-operators

Updates the haddock submodule.

- - - - -
577135bf by Aaron Allen at 2022-03-16T02:27:48-04:00
Convert Diagnostics in GHC.Tc.Gen.Foreign

Converts all uses of 'TcRnUnknownMessage' to proper diagnostics.

- - - - -
c1fed9da by Aaron Allen at 2022-03-16T02:27:48-04:00
Suggest FFI extensions as hints (#20116)

- Use extension suggestion hints instead of suggesting extensions in the
error message body for several FFI errors.
- Adds a test case for `TcRnForeignImportPrimExtNotSet`

- - - - -
a33d1045 by Zubin Duggal at 2022-03-16T02:28:24-04:00
TH: allow negative patterns in quotes (#20711)

We still don't allow negative overloaded patterns. Earler all negative patterns
were treated as negative overloaded patterns. Now, we expliclty check the
extension field to see if the pattern is actually a negative overloaded pattern

- - - - -
1575c4a5 by Sebastian Graf at 2022-03-16T02:29:03-04:00
Demand: Let `Boxed` win in `lubBoxity` (#21119)

Previously, we let `Unboxed` win in `lubBoxity`, which is unsoundly optimistic
in terms ob Boxity analysis. "Unsoundly" in the sense that we sometimes unbox
parameters that we better shouldn't unbox. Examples are #18907 and T19871.absent.

Until now, we thought that this hack pulled its weight becuase it worked around
some shortcomings of the phase separation between Boxity analysis and CPR
analysis. But it is a gross hack which caused regressions itself that needed all
kinds of fixes and workarounds. See for example #20767. It became impossible to
work with in !7599, so I want to remove it.

For example, at the moment, `lubDmd B dmd` will not unbox `dmd`,
but `lubDmd A dmd` will. Given that `B` is supposed to be the bottom element of
the lattice, it's hardly justifiable to get a better demand when `lub`bing with
`A`.

The consequence of letting `Boxed` win in `lubBoxity` is that we *would* regress
 #2387, #16040 and parts of #5075 and T19871.sumIO, until Boxity and CPR
are able to communicate better. Fortunately, that is not the case since I could
tweak the other source of optimism in Boxity analysis that is described in
`Note [Unboxed demand on function bodies returning small products]` so that
we *recursively* assume unboxed demands on function bodies returning small
products. See the updated Note.

`Note [Boxity for bottoming functions]` describes why we need bottoming
functions to have signatures that say that they deeply unbox their arguments.
In so doing, I had to tweak `finaliseArgBoxities` so that it will never unbox
recursive data constructors. This is in line with our handling of them in CPR.
I updated `Note [Which types are unboxed?]` to reflect that.

In turn we fix #21119, #20767, #18907, T19871.absent and get a much simpler
implementation (at least to think about). We can also drop the very ad-hoc
definition of `deferAfterPreciseException` and its Note in favor of the
simple, intuitive definition we used to have.

Metric Decrease:
    T16875
    T18223
    T18698a
    T18698b
    hard_hole_fits
Metric Increase:
    LargeRecord
    MultiComponentModulesRecomp
    T15703
    T8095
    T9872d

Out of all the regresions, only the one in T9872d doesn't vanish in a perf
build, where the compiler is bootstrapped with -O2 and thus SpecConstr.
Reason for regressions:

  * T9872d is due to `ty_co_subst` taking its `LiftingContext` boxed.
    That is because the context is passed to a function argument, for
    example in `liftCoSubstTyVarBndrUsing`.
  * In T15703, LargeRecord and T8095, we get a bit more allocations in
    `expand_syn` and `piResultTys`, because a `TCvSubst` isn't unboxed.
    In both cases that guards against reboxing in some code paths.
  * The same is true for MultiComponentModulesRecomp, where we get less unboxing
    in `GHC.Unit.Finder.$wfindInstalledHomeModule`. In a perf build, allocations
    actually *improve* by over 4%!

Results on NoFib:

--------------------------------------------------------------------------------
        Program         Allocs    Instrs
--------------------------------------------------------------------------------
         awards          -0.4%     +0.3%
      cacheprof          -0.3%     +2.4%
            fft          -1.5%     -5.1%
       fibheaps          +1.2%     +0.8%
          fluid          -0.3%     -0.1%
            ida          +0.4%     +0.9%
   k-nucleotide          +0.4%     -0.1%
     last-piece         +10.5%    +13.9%
           lift          -4.4%     +3.5%
        mandel2         -99.7%    -99.8%
           mate          -0.4%     +3.6%
         parser          -1.0%     +0.1%
         puzzle         -11.6%     +6.5%
reverse-complem          -3.0%     +2.0%
            scs          -0.5%     +0.1%
         sphere          -0.4%     -0.2%
      wave4main          -8.2%     -0.3%
--------------------------------------------------------------------------------
Summary excludes mandel2 because of excessive bias
            Min         -11.6%     -5.1%
            Max         +10.5%    +13.9%
 Geometric Mean          -0.2%     +0.3%
--------------------------------------------------------------------------------

Not bad for a bug fix.

The regression in `last-piece` could become a win if SpecConstr would work on
non-recursive functions. The regression in `fibheaps` is due to
`Note [Reboxed crud for bottoming calls]`, e.g., #21128.

- - - - -
bb779b90 by sheaf at 2022-03-16T02:29:42-04:00
Add a regression test for #21130

This problem was due to a bug in cloneWanted, which was incorrectly
creating a coercion hole to hold an evidence variable.

This bug was introduced by 8bb52d91 and fixed in 81740ce8.

Fixes #21130

- - - - -
0f0e2394 by Tamar Christina at 2022-03-17T10:16:37-04:00
linker: Initial Windows C++ exception unwinding support

- - - - -
36d20d4d by Tamar Christina at 2022-03-17T10:16:37-04:00
linker: Fix ADDR32NB relocations on Windows

- - - - -
8a516527 by Tamar Christina at 2022-03-17T10:16:37-04:00
testsuite: properly escape string paths

- - - - -
1a0dd008 by sheaf at 2022-03-17T10:17:13-04:00
Hadrian: account for change in late-ccs flag

The late cost centre flag was renamed from -fprof-late-ccs
to -fprof-late in 7fe07143, but this change hadn't been
propagated to Hadrian.

- - - - -
8561c1af by romes at 2022-03-18T05:10:58-04:00
TTG: Refactor HsBracket

- - - - -
19163397 by romes at 2022-03-18T05:10:58-04:00
Type-checking untyped brackets

When HsExpr GhcTc, the HsBracket constructor should hold a HsBracket
GhcRn, rather than an HsBracket GhcTc.

We make use of the HsBracket p extension constructor (XBracket
(XXBracket p)) to hold an HsBracket GhcRn when the pass is GhcTc

See !4782 https://gitlab.haskell.org/ghc/ghc/-/merge_requests/4782

- - - - -
310890a5 by romes at 2022-03-18T05:10:58-04:00
Separate constructors for typed and untyped brackets

Split HsBracket into HsTypedBracket and HsUntypedBracket.

Unfortunately, we still cannot get rid of

    instance XXTypedBracket GhcTc = HsTypedBracket GhcRn

despite no longer requiring it for typechecking, but rather because the
TH desugarer works on GhcRn rather than GhcTc (See GHC.HsToCore.Quote)

- - - - -
4a2567f5 by romes at 2022-03-18T05:10:58-04:00
TTG: Refactor bracket for desugaring during tc

When desugaring a bracket we want to desugar /renamed/ rather than
/typechecked/ code; So in (HsExpr GhcTc) tree, we must
have a (HsExpr GhcRn) for the quotation itself.

This commit reworks the TTG refactor on typed and untyped brackets by
storing the /renamed/ code in the bracket field extension rather than in
the constructor extension in `HsQuote` (previously called
`HsUntypedBracket`)

See Note [The life cycle of a TH quotation] and https://gitlab.haskell.org/ghc/ghc/-/merge_requests/4782

- - - - -
b056adc8 by romes at 2022-03-18T05:10:58-04:00
TTG: Make HsQuote GhcTc isomorphic to NoExtField

An untyped bracket `HsQuote p` can never be constructed with
`p ~ GhcTc`. This is because we don't typecheck `HsQuote` at all.

That's OK, because we also never use `HsQuote GhcTc`.

To enforce this at the type level we make `HsQuote GhcTc` isomorphic
to `NoExtField` and impossible to construct otherwise, by using TTG field
extensions to make all constructors, except for `XQuote` (which takes `NoExtField`),
unconstructable, with `DataConCantHappen`

This is explained more in detail in Note [The life cycle of a TH quotation]

Related discussion: https://gitlab.haskell.org/ghc/ghc/-/merge_requests/4782

- - - - -
ac3b2e7d by romes at 2022-03-18T05:10:58-04:00
TTG: TH brackets finishing touches

Rewrite the critical notes and fix outdated ones,

use `HsQuote GhcRn` (in `HsBracketTc`) for desugaring regardless of the
bracket being typed or untyped,

remove unused `EpAnn` from `Hs*Bracket GhcRn`,

zonkExpr factor out common brackets code,

ppr_expr factor out common brackets code,

and fix tests,

to finish MR https://gitlab.haskell.org/ghc/ghc/-/merge_requests/4782.

-------------------------
Metric Decrease:
    hard_hole_fits
-------------------------

- - - - -
d147428a by Ben Gamari at 2022-03-18T05:11:35-04:00
codeGen: Fix signedness of jump table indexing

Previously while constructing the jump table index we would
zero-extend the discriminant before subtracting the start of the
jump-table. This goes subtly wrong in the case of a sub-word, signed
discriminant, as described in the included Note. Fix this in both the
PPC and X86 NCGs.

Fixes #21186.

- - - - -
435a3d5d by Ben Gamari at 2022-03-18T05:11:35-04:00
testsuite: Add test for #21186

- - - - -
e9d8de93 by Zubin Duggal at 2022-03-19T07:35:49-04:00
TH: Fix pretty printing of newtypes with operators and GADT syntax (#20868)

The pretty printer for regular data types already accounted for these,
and had some duplication with the newtype pretty printer.

Factoring the logic out into a common function and using it for both
newtypes and data declarations is enough to fix the bug.

- - - - -
244da9eb by sheaf at 2022-03-19T07:36:24-04:00
List GHC.Event.Internal in base.cabal on Windows

GHC.Event.Internal was not listed in base.cabal on Windows. This caused
undefined reference errors. This patch adds it back, by moving it out
of the OS-specific logic in base.cabal.

Fixes #21245.
- - - - -
d1c03719 by Andreas Klebinger at 2022-03-19T07:37:00-04:00
Compact regions: Maintain tags properly

Fixes #21251

- - - - -
d45bb701 by romes at 2022-03-19T07:37:36-04:00
Remove dead code HsDoRn

- - - - -
c842611f by nineonine at 2022-03-20T21:16:06-04:00
Revamp derived Eq instance code generation (#17240)

This patch improves code generation for derived Eq instances.
The idea is to use 'dataToTag' to evaluate both arguments.
This allows to 'short-circuit' when tags do not match.
Unfortunately, inner evals are still present when we branch
on tags. This is due to the way 'dataToTag#' primop
evaluates its argument in the code generator. #21207 was
created to explore further optimizations.

Metric Decrease:
    LargeRecord

- - - - -
52ffd38c by Sylvain Henry at 2022-03-20T21:16:46-04:00
Avoid some SOURCE imports

- - - - -
b91798be by Zubin Duggal at 2022-03-23T13:39:39-04:00
hi haddock: Lex and store haddock docs in interface files

Names appearing in Haddock docstrings are lexed and renamed like any other names
appearing in the AST. We currently rename names irrespective of the namespace,
so both type and constructor names corresponding to an identifier will appear in
the docstring. Haddock will select a given name as the link destination based on
its own heuristics.

This patch also restricts the limitation of `-haddock` being incompatible with
`Opt_KeepRawTokenStream`.

The export and documenation structure is now computed in GHC and serialised in
.hi files. This can be used by haddock to directly generate doc pages without
reparsing or renaming the source. At the moment the operation of haddock
is not modified, that's left to a future patch.

Updates the haddock submodule with the minimum changes needed.

- - - - -
78db231f by Cheng Shao at 2022-03-23T13:40:17-04:00
configure: bump LlvmMaxVersion to 14

LLVM 13.0.0 is released in Oct 2021, and latest head validates against
LLVM 13 just fine if LlvmMaxVersion is bumped.

- - - - -
b06e5dd8 by Adam Sandberg Ericsson at 2022-03-23T13:40:54-04:00
docs: clarify the eventlog format documentation a little bit

- - - - -
4dc62498 by Matthew Pickering at 2022-03-23T13:41:31-04:00
Fix behaviour of -Wunused-packages in ghci

Ticket #21110 points out that -Wunused-packages behaves a bit unusually
in GHCi. Now we define the semantics for -Wunused-packages in
interactive mode as follows:

* If you use -Wunused-packages on an initial load then the warning is reported.
* If you explicitly set -Wunused-packages on the command line then the
  warning is displayed (until it is disabled)
* If you then subsequently modify the set of available targets by using
  :load or :cd (:cd unloads everything) then the warning is (silently)
  turned off.

This means that every :r the warning is printed if it's turned on (but you did ask for it).

Fixes #21110

- - - - -
fed05347 by Ben Gamari at 2022-03-23T13:42:07-04:00
rts/adjustor: Place adjustor templates in data section on all OSs

In !7604 we started placing adjustor templates in the data section on
Linux as some toolchains there reject relocations in the text section.
However, it turns out that OpenBSD also exhibits this restriction.

Fix this by *always* placing adjustor templates in the data section.

Fixes #21155.

- - - - -
db32bb8c by Zubin Duggal at 2022-03-23T13:42:44-04:00
Improve error message when warning about unsupported LLVM version (#20958)

Change the wording to make it clear that the upper bound is non-inclusive.

- - - - -
f214349a by Ben Gamari at 2022-03-23T13:43:20-04:00
rts: Untag function field in scavenge_PAP_payload

Previously we failed to untag the function closure when scavenging the
payload of a PAP, resulting in an invalid closure pointer being passed
to scavenge_large_bitmap and consequently #21254. Fix this.

Fixes #21254

- - - - -
e6d0e287 by Ben Gamari at 2022-03-23T13:43:20-04:00
rts: Don't mark object code in markCAFs unless necessary

Previously `markCAFs` would call `markObjectCode` even in non-major GCs.
This is problematic since `prepareUnloadCheck` is not called in such
GCs, meaning that the section index has not been updated.

Fixes #21254

- - - - -
1a7cf096 by Sylvain Henry at 2022-03-23T13:44:05-04:00
Avoid redundant imports of GHC.Driver.Session

Remove GHC.Driver.Session imports that weren't considered as redundant
because of the reexport of PlatformConstants. Also remove this reexport
as modules using this datatype should import GHC.Platform instead.

- - - - -
e3f60577 by Sylvain Henry at 2022-03-23T13:44:05-04:00
Reverse dependency between StgToCmm and Runtime.Heap.Layout

- - - - -
e6585ca1 by Sylvain Henry at 2022-03-23T13:44:46-04:00
Define filterOut with filter

filter has fusion rules that filterOut lacks

- - - - -
c58d008c by Ryan Scott at 2022-03-24T06:10:43-04:00
Fix and simplify DeriveAnyClass's context inference using SubTypePredSpec

As explained in `Note [Gathering and simplifying constraints for DeriveAnyClass]`
in `GHC.Tc.Deriv.Infer`, `DeriveAnyClass` infers instance contexts by emitting
implication constraints. Previously, these implication constraints were
constructed by hand. This is a terribly trick thing to get right, as it
involves a delicate interplay of skolemisation, metavariable instantiation, and
`TcLevel` bumping. Despite much effort, we discovered in #20719 that the
implementation was subtly incorrect, leading to valid programs being rejected.

While we could scrutinize the code that manually constructs implication
constraints and repair it, there is a better, less error-prone way to do
things. After all, the heart of `DeriveAnyClass` is generating code which
fills in each class method with defaults, e.g., `foo = $gdm_foo`. Typechecking
this sort of code is tantamount to calling `tcSubTypeSigma`, as we much ensure
that the type of `$gdm_foo` is a subtype of (i.e., more polymorphic than) the
type of `foo`. As an added bonus, `tcSubTypeSigma` is a battle-tested function
that handles skolemisation, metvariable instantiation, `TcLevel` bumping, and
all other means of tricky bookkeeping correctly.

With this insight, the solution to the problems uncovered in #20719 is simple:
use `tcSubTypeSigma` to check if `$gdm_foo`'s type is a subtype of `foo`'s
type. As a side effect, `tcSubTypeSigma` will emit exactly the implication
constraint that we were attempting to construct by hand previously. Moreover,
it does so correctly, fixing #20719 as a consequence.

This patch implements the solution thusly:

* The `PredSpec` data type (previously named `PredOrigin`) is now split into
  `SimplePredSpec`, which directly stores a `PredType`, and `SubTypePredSpec`,
  which stores the actual and expected types in a subtype check.
  `SubTypePredSpec` is only used for `DeriveAnyClass`; all other deriving
  strategies use `SimplePredSpec`.
* Because `tcSubTypeSigma` manages the finer details of type variable
  instantiation and constraint solving under the hood, there is no longer any
  need to delicately split apart the method type signatures in
  `inferConstraintsAnyclass`. This greatly simplifies the implementation of
  `inferConstraintsAnyclass` and obviates the need to store skolems,
  metavariables, or given constraints in a `ThetaSpec` (previously named
  `ThetaOrigin`). As a bonus, this means that `ThetaSpec` now simply becomes a
  synonym for a list of `PredSpec`s, which is conceptually much simpler than it
  was before.
* In `simplifyDeriv`, each `SubTypePredSpec` results in a call to
  `tcSubTypeSigma`. This is only performed for its side effect of emitting
  an implication constraint, which is fed to the rest of the constraint solving
  machinery in `simplifyDeriv`. I have updated
  `Note [Gathering and simplifying constraints for DeriveAnyClass]` to explain
  this in more detail.

To make the changes in `simplifyDeriv` more manageable, I also performed some
auxiliary refactoring:

* Previously, every iteration of `simplifyDeriv` was skolemising the type
  variables at the start, simplifying, and then performing a reverse
  substitution at the end to un-skolemise the type variables. This is not
  necessary, however, since we can just as well skolemise once at the
  beginning of the `deriving` pipeline and zonk the `TcTyVar`s after
  `simplifyDeriv` is finished. This patch does just that, having been made
  possible by prior work in !7613. I have updated `Note [Overlap and deriving]`
  in `GHC.Tc.Deriv.Infer` to explain this, and I have also left comments on
  the relevant data structures (e.g., `DerivEnv` and `DerivSpec`) to explain
  when things might be `TcTyVar`s or `TyVar`s.
* All of the aforementioned cleanup allowed me to remove an ad hoc
  deriving-related in `checkImplicationInvariants`, as all of the skolems in
  a `tcSubTypeSigma`–produced implication constraint should now be `TcTyVar`
  at the time the implication is created.
* Since `simplifyDeriv` now needs a `SkolemInfo` and `UserTypeCtxt`, I have
  added `ds_skol_info` and `ds_user_ctxt` fields to `DerivSpec` to store these.
  Similarly, I have also added a `denv_skol_info` field to `DerivEnv`, which
  ultimately gets used to initialize the `ds_skol_info` in a `DerivSpec`.

Fixes #20719.

- - - - -
21680fb0 by Sebastian Graf at 2022-03-24T06:11:19-04:00
WorkWrap: Handle partial FUN apps in `isRecDataCon` (#21265)

Partial FUN apps like `(->) Bool` aren't detected by `splitFunTy_maybe`.
A silly oversight that is easily fixed by replacing `splitFunTy_maybe` with a
guard in the `splitTyConApp_maybe` case.

But fortunately, Simon nudged me into rewriting the whole `isRecDataCon`
function in a way that makes it much shorter and hence clearer which DataCons
are actually considered as recursive.

Fixes #21265.

- - - - -
a2937e2b by Matthew Pickering at 2022-03-24T17:13:22-04:00
Add test for T21035

This test checks that you are allowed to explicitly supply object files
for dependencies even if you haven't got the shared object for that
library yet.

Fixes #21035

- - - - -
1756d547 by Matthew Pickering at 2022-03-24T17:13:58-04:00
Add check to ensure we are not building validate jobs for releases

- - - - -
99623358 by Matthew Pickering at 2022-03-24T17:13:58-04:00
hadrian: Correct generation of hsc2hs wrapper

If you inspect the inside of a wrapper script for hsc2hs you will see
that the cflag and lflag values are concatenated incorrectly.

```
HSC2HS_EXTRA="--cflag=-U__i686--lflag=-fuse-ld=gold"
```

It should instead be

```
HSC2HS_EXTRA="--cflag=-U__i686 --lflag=-fuse-ld=gold"
```

Fixes #21221

- - - - -
fefd4e31 by Matthew Pickering at 2022-03-24T17:13:59-04:00
testsuite: Remove library dependenices from T21119

These dependencies would affect the demand signature depending on
various rules and so on.

Fixes #21271

- - - - -
5ff690b8 by Matthew Pickering at 2022-03-24T17:13:59-04:00
ci: Generate jobs for all normal builds and use hadrian for all builds

This commit introduces a new script (.gitlab/gen_ci.hs) which generates
a yaml file (.gitlab/jobs.yaml) which contains explicit descriptions for
all the jobs we want to run. The jobs are separated into three
categories:

* validate - jobs run on every MR
* nightly  - jobs run once per day on the master branch
* release  - jobs for producing release artifacts

The generation script is a Haskell program which includes a DSL for
specifying the different jobs. The hope is that it's easier to reason
about the different jobs and how the variables are merged together
rather than the unclear and opaque yaml syntax. The goal is to fix
issues like #21190 once and for all..

The `.gitlab/jobs.yaml` can be generated by running the `.gitlab/generate_jobs`
script. You have to do this manually.

Another consequence of this patch is that we use hadrian for all the
validate, nightly and release builds on all platforms.

- - - - -
1d673aa2 by Christiaan Baaij at 2022-03-25T11:35:49-04:00
Add the OPAQUE pragma

A new pragma, `OPAQUE`, that ensures that every call of a named
function annotated with an `OPAQUE` pragma remains a call of that
named function, not some name-mangled variant.

Implements GHC proposal 0415:
https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0415-opaque-pragma.rst

This commit also updates the haddock submodule to handle the newly
introduced lexer tokens corresponding to the OPAQUE pragma.

- - - - -
83f5841b by Bodigrim at 2022-03-25T11:36:31-04:00
Add instance Lift ByteArray

- - - - -
7cc1184a by Matthew Pickering at 2022-03-25T11:37:07-04:00
Make -ddump-rn-ast and -ddump-tc-ast work in GHCi

Fixes #17830

- - - - -
940feaf3 by Sylvain Henry at 2022-03-25T11:37:47-04:00
Modularize Tidy (#17957)

- Factorize Tidy options into TidyOpts datatype. Initialize it in
  GHC.Driver.Config.Tidy
- Same thing for StaticPtrOpts
- Perform lookups of unpackCString[Utf8]# once in initStaticPtrOpts
  instead of for every use of mkStringExprWithFS

- - - - -
25101813 by Takenobu Tani at 2022-03-28T01:16:02-04:00
users-guide: Correct markdown for profiling

This patch corrects some markdown.

[skip ci]

- - - - -
c832ae93 by Matthew Pickering at 2022-03-28T01:16:38-04:00
hadrian: Flag cabal flag handling

This patch basically deletes some ad-hoc handling of Cabal Flags and
replaces it with a correct query of the LocalBuildInfo. The flags in the
local build info can be modified by users by passing hadrian options

For example (!4331)

```
*.genapply.cabal.configure.opts += --flags=unregisterised
```

And all the flags specified by the `Cabal Flags` builder were already
passed to configure properly using `--flags`.

- - - - -
a9f3a5c6 by Ben Gamari at 2022-03-28T01:16:38-04:00
Disable text's dependency on simdutf by default

Unfortunately we are simply not currently in a good position to robustly
ship binary distributions which link against C++ code like simdutf.

Fixes #20724.

- - - - -
eff86e8a by Richard Eisenberg at 2022-03-28T01:17:14-04:00
Add Red Herring to Note [What might equal later?]

Close #21208.

- - - - -
12653be9 by jberryman at 2022-03-28T01:17:55-04:00
Document typed splices inhibiting unused bind detection (#16524)
- - - - -
4aeade15 by Adam Sandberg Ericsson at 2022-03-28T01:18:31-04:00
users-guide: group ticky-ticky profiling under one heading

- - - - -
cc59648a by Sylvain Henry at 2022-03-28T01:19:12-04:00
Hadrian: allow testsuite to run with cross-compilers (#21292)

- - - - -
89cb1315 by Matthew Pickering at 2022-03-28T01:19:48-04:00
hadrian: Add show target to bindist makefile

Some build systems use "make show" to query facts about the bindist, for
example:

```
make show VALUE=ProjectVersion > version
```

to determine the ProjectVersion

- - - - -
8229885c by Alan Zimmerman at 2022-03-28T19:23:28-04:00
EPA: let stmt with semicolon has wrong anchor

The code

   let ;x =1

Captures the semicolon annotation, but did not widen the anchor in the
ValBinds.

Fix that.

Closes #20247

- - - - -
2c12627c by Ryan Scott at 2022-03-28T19:24:04-04:00
Consistently attach SrcSpans to sub-expressions in TH splices

Before, `GHC.ThToHs` was very inconsistent about where various sub-expressions
would get the same `SrcSpan` from the original TH splice location or just a
generic `noLoc` `SrcSpan`. I have ripped out all uses of `noLoc` in favor of
the former instead, and I have added a
`Note [Source locations within TH splices]` to officially enshrine this
design choice.

Fixes #21299.

- - - - -
789add55 by Zubin Duggal at 2022-03-29T13:07:22-04:00
Fix all invalid haddock comments in the compiler

Fixes #20935 and #20924

- - - - -
967dad03 by Zubin Duggal at 2022-03-29T13:07:22-04:00
hadrian: Build lib:GHC with -haddock and -Winvalid-haddock (#21273)

- - - - -
ad09a5f7 by sheaf at 2022-03-29T13:08:05-04:00
Hadrian: make DDEBUG separate from debugged RTS

This patchs separates whether -DDEBUG is enabled (i.e. whether debug
assertions are enabled) from whether we are using the debugged RTS
(i.e. GhcDebugged = YES).

This means that we properly skip tests which have been marked with
`when(compiler_debugged(), skip)`.

Fixes #21113, #21153 and #21234

- - - - -
840a6811 by Matthew Pickering at 2022-03-29T13:08:42-04:00
RTS: Zero gc_cpu_start and gc_cpu_end after accounting

When passed a combination of `-N` and `-qn` options the cpu time for
garbage collection was being vastly overcounted because the counters
were not being zeroed appropiately.

When -qn1 is passed, only 1 of the N avaiable GC threads is chosen to
perform work, the rest are idle. At the end of the GC period, stat_endGC
traverses all the GC threads and adds up the elapsed time from each of
them. For threads which didn't participate in this GC, the value of the
cpu time should be zero, but before this patch, the counters were not
zeroed and hence we would count the same elapsed time on many subsequent
iterations (until the thread participated in a GC again).

The most direct way to zero these fields is to do so immediately after
the value is added into the global counter, after which point they are
never used again.

We also tried another approach where we would zero the counter in
yieldCapability but there are some (undiagnosed) siations where a
capbility would not pass through yieldCapability before the GC ended and
the same double counting problem would occur.

Fixes #21082

- - - - -
dda46e2d by Matthew Pickering at 2022-03-29T13:09:18-04:00
Add test for T21306

Fixes #21306

- - - - -
f07c7766 by Jakob Brünker at 2022-03-30T03:10:33-04:00
Give parsing plugins access to errors

Previously, when the parser produced non-fatal errors (i.e. it produced
errors but the 'PState' is 'POk'), compilation would be aborted before
the 'parsedResultAction' of any plugin was invoked. This commit changes
that, so that such that 'parsedResultAction' gets collections of
warnings and errors as argument, and must return them after potentially
modifying them.

Closes #20803

- - - - -
e5dfde75 by Ben Gamari at 2022-03-30T03:11:10-04:00
Fix reference to Note [FunBind vs PatBind]

This Note was renamed in 2535a6716202253df74d8190b028f85cc6d21b72 yet
this occurrence was not updated.

- - - - -
21894a63 by Krzysztof Gogolewski at 2022-03-30T03:11:45-04:00
Refactor: make primtypes independent of PrimReps

Previously, 'pcPrimTyCon', the function used to define a primitive type,
was taking a PrimRep, only to convert it to a RuntimeRep. Now it takes
a RuntimeRep directly.

Moved primRepToRuntimeRep to GHC.Types.RepType. It is now
located next to its inverse function runtimeRepPrimRep.
Now GHC.Builtin.Types.Prim no longer mentions PrimRep, and GHC.Types.RepType
no longer imports GHC.Builtin.Types.Prim.

Removed unused functions `primRepsToRuntimeRep` and `mkTupleRep`.

Removed Note [PrimRep and kindPrimRep] - it was never referenced,
didn't belong to Types.Prim, and Note [Getting from RuntimeRep to
PrimRep] is more comprehensive.

- - - - -
43da2963 by Matthew Pickering at 2022-03-30T09:55:49+01:00
Fix mention of non-existent "rehydrateIface" function [skip ci]

Fixes #21303

- - - - -
6793a20f by gershomb at 2022-04-01T10:33:46+01:00
Remove wrong claim about naturality law.

This docs change removes a longstanding confusion in the Traversable
docs. The docs say "(The naturality law is implied by parametricity and
thus so is the purity law [1, p15].)". However if one reads the
reference a different "natural" law is implied by parametricity. The
naturality law given as a law here is imposed. Further, the reference
gives examples which violate both laws -- so they cannot be implied by
parametricity. This PR just removes the wrong claim.

- - - - -
5beeff46 by Ben Gamari at 2022-04-01T10:34:39+01:00
Refactor handling of global initializers

GHC uses global initializers for a number of things including
cost-center registration, info-table provenance registration, and setup
of foreign exports. Previously, the global initializer arrays which
referenced these initializers would live in the object file of the C
stub, which would then be merged into the main object file of the
module.

Unfortunately, this approach is no longer tenable with the move to
Clang/LLVM on Windows (see #21019). Specifically, lld's PE backend does
not support object merging (that is, the -r flag). Instead we are now
rather packaging a module's object files into a static library. However,
this is problematic in the case of initializers as there are no
references to the C stub object in the archive, meaning that the linker
may drop the object from the final link.

This patch refactors our handling of global initializers to instead
place initializer arrays within the object file of the module to which
they belong. We do this by introducing a Cmm data declaration containing
the initializer array in the module's Cmm stream. While the initializer
functions themselves remain in separate C stub objects, the reference
from the module's object ensures that they are not dropped from the
final link.

In service of #21068.

- - - - -
3e6fe71b by Matthew Pickering at 2022-04-01T10:35:41+01:00
Fix remaining issues in eventlog types (gen_event_types.py)

*  The size of End concurrent mark phase looks wrong and, it used to be 4 and now it's 0.
*  The size of Task create is wrong, used to be 18 and now 14.
*  The event ticky-ticky entry counter begin sample has the wrong name
*  The event ticky-ticky entry counter being sample has the wrong size, was 0 now 32.

Closes #21070

- - - - -
7847f47a by Ben Gamari at 2022-04-01T10:35:41+01:00
users-guide: Fix a few small issues in eventlog format descriptions

The CONC_MARK_END event description didn't mention its payload.
Clarify the meaning of the CREATE_TASK's payload.

- - - - -
acfd5a4c by Matthew Pickering at 2022-04-01T10:35:53+01:00
ci: Regenerate jobs.yaml

It seems I forgot to update this to reflect the current state of
gen_ci.hs

- - - - -
a952dd80 by Matthew Pickering at 2022-04-01T10:35:59+01:00
ci: Attempt to fix windows cache issues

It appears that running the script directly does nothing (no info is
printed about saving the cache).

- - - - -
fb65e6e3 by Adrian Ratiu at 2022-04-01T10:49:52+01:00
fp_prog_ar.m4: take AR var into consideration

In ChromeOS and Gentoo we want the ability to use LLVM ar
instead of GNU ar even though both are installed, thus we
pass (for eg) AR=llvm-ar to configure.

Unfortunately GNU ar always gets picked regardless of the
AR setting because the check does not consider the AR var
when setting fp_prog_ar, hence this fix.

- - - - -
1daaefdf by Greg Steuck at 2022-04-01T10:50:16+01:00
T13366 requires c++ & c++abi libraries on OpenBSD

Fixes this failure:

=====> 1 of 1 [0, 0, 0]
T13366(normal) 1 of 1 [0, 0, 0] Compile failed (exit code 1) errors were:

<no location info>: error:
    user specified .o/.so/.DLL could not be loaded (File not found)
Whilst trying to load:  (dynamic) stdc++
Additional directories searched: (none)

*** unexpected failure for T13366(normal)

- - - - -
18e6c85b by Jakob Bruenker at 2022-04-01T10:54:28+01:00
new datatypes for parsedResultAction

Previously, the warnings and errors were given and returned as a tuple
(Messages PsWarnings, Messages PsErrors). Now, it's just PsMessages.

This, together with the HsParsedModule the parser plugin gets and
returns, has been wrapped up as ParsedResult.

- - - - -
9727e592 by Morrow at 2022-04-01T10:55:12+01:00
Clarify that runghc interprets the input program

- - - - -
f589dea3 by sheaf at 2022-04-01T10:59:58+01:00
Unify RuntimeRep arguments in ty_co_match

The `ty_co_match` function ignored the implicit RuntimeRep coercions
that occur in a `FunCo`. Even though a comment explained that this
should be fine, #21205 showed that it could result in discarding a
RuntimeRep coercion, and thus discarding an important cast entirely.

With this patch, we first match the kinds in `ty_co_match`.

Fixes #21205

-------------------------
Metric Increase:
    T12227
    T18223
-------------------------

- - - - -
6f4dc372 by Andreas Klebinger at 2022-04-01T11:01:35+01:00
Export MutableByteArray from Data.Array.Byte

This implements CLC proposal #49

- - - - -
5df9f5e7 by ARATA Mizuki at 2022-04-01T11:02:35+01:00
Add test cases for #20640

Closes #20640

- - - - -
8334ff9e by Krzysztof Gogolewski at 2022-04-01T11:03:16+01:00
Minor cleanup

- Remove unused functions exprToCoercion_maybe, applyTypeToArg,
  typeMonoPrimRep_maybe, runtimeRepMonoPrimRep_maybe.
- Replace orValid with a simpler check
- Use splitAtList in applyTysX
- Remove calls to extra_clean in the testsuite; it does not do anything.

Metric Decrease:
    T18223

- - - - -
b2785cfc by Eric Lindblad at 2022-04-01T11:04:07+01:00
hadrian typos

- - - - -
418e6fab by Eric Lindblad at 2022-04-01T11:04:12+01:00
two typos

- - - - -
dd7c7c99 by Phil de Joux at 2022-04-01T11:04:56+01:00
Add tests and docs on plugin args and order.

- - - - -
3e209a62 by MaxHearnden at 2022-04-01T11:05:19+01:00
Change may not to might not
- - - - -
b84380d3 by Matthew Pickering at 2022-04-01T11:07:27+01:00
hadrian: Remove linters-common from bindist

Zubin observed that the bindists contains the utility library
linters-common. There are two options:

1. Make sure only the right files are added into the bindist.. a bit
   tricky due to the non-trivial structure of the lib directory.
2. Remove the bad files once they get copied in.. a bit easier

So I went for option 2 but we perhaps should go for option 1 in the
future.

Fixes #21203

- - - - -
ba9904c1 by Zubin Duggal at 2022-04-01T11:07:31+01:00
hadrian: allow testing linters with out of tree compilers

- - - - -
26547759 by Matthew Pickering at 2022-04-01T11:07:35+01:00
hadrian: Introduce CheckProgram datatype to replace a 7-tuple

- - - - -
df65d732 by Jakob Bruenker at 2022-04-01T11:08:28+01:00
Fix panic when pretty printing HsCmdLam

When pretty printing a HsCmdLam with more than one argument, GHC
panicked because of a missing case. This fixes that.

Closes #21300

- - - - -
ad6cd165 by John Ericson at 2022-04-01T11:10:06+01:00
hadrian: Remove vestigial -this-unit-id support check

This has been dead code since 400ead81e80f66ad7b1260b11b2a92f25ccc3e5a.

- - - - -
8ca7ab81 by Matthew Pickering at 2022-04-01T11:10:23+01:00
hadrian: Fix race involving empty package databases

There was a small chance of a race occuring between the small window of

1. The first package (.conf) file get written into the database
2. hadrian calling "ghc-pkg recache" to refresh the package.conf file

In this window the package database would contain rts.conf but not a
package.cache file, and therefore if ghc was invoked it would error
because it was missing.

To solve this we call "ghc-pkg recache" at when the database is created
by shake by writing the stamp file into the database folder. This also
creates the package.cache file and so avoids the possibility of this
race.

- - - - -
cc4ec64b by Matthew Pickering at 2022-04-01T11:11:05+01:00
hadrian: Add assertion that in/out tree args are the same

There have been a few instances where this calculation was incorrect, so
we add a non-terminal assertion when now checks they the two
computations indeed compute the same thing.

Fixes #21285

- - - - -
691508d8 by Matthew Pickering at 2022-04-01T11:13:10+01:00
hlint: Ignore suggestions in generated HaddockLex file

With the make build system this file ends up in the compiler/
subdirectory so is linted. With hadrian, the file ends up in _build so
it's not linted.

Fixes #21313

- - - - -
f8f152e7 by Krzysztof Gogolewski at 2022-04-01T11:14:08+01:00
Change GHC.Prim to GHC.Exts in docs and tests

Users are supposed to import GHC.Exts rather than GHC.Prim.
Part of #18749.

- - - - -
f8fc6d2e by Matthew Pickering at 2022-04-01T11:15:24+01:00
driver: Improve -Wunused-packages error message (and simplify implementation)

In the past I improved the part of -Wunused-packages which found which
packages were used. Now I improve the part which detects which ones were
specified. The key innovation is to use the explicitUnits field from
UnitState which has the result of resolving the package flags, so we
don't need to mess about with the flag arguments from DynFlags anymore.

The output now always includes the package name and version (and the
flag which exposed it).

```
    The following packages were specified via -package or -package-id flags,
    but were not needed for compilation:
      - bytestring-0.11.2.0 (exposed by flag -package bytestring)
      - ghc-9.3 (exposed by flag -package ghc)
      - process-1.6.13.2 (exposed by flag -package process)
```

Fixes #21307

- - - - -
5e5a12d9 by Matthew Pickering at 2022-04-01T11:15:32+01:00
driver: In oneshot mode, look for interface files in hidir

How things should work:

*  -i is the search path for source files
*  -hidir explicitly sets the search path for interface files and the output location for interface files.
*  -odir sets the search path and output location for object files.

Before in one shot mode we would look for the interface file in the
search locations given by `-i`, but then set the path to be in the
`hidir`, so in unusual situations the finder could find an interface
file in the `-i` dir but later fail because it tried to read the
interface file from the `-hidir`.

A bug identified by #20569

- - - - -
950f58e7 by Matthew Pickering at 2022-04-01T11:15:36+01:00
docs: Update documentation interaction of search path, -hidir and -c mode.

As noted in #20569 the documentation for search path was wrong because
it seemed to indicate that `-i` dirs were important when looking for
interface files in `-c` mode, but they are not important if `-hidir` is
set.

Fixes #20569

- - - - -
d85c7dcb by sheaf at 2022-04-01T11:17:56+01:00
Keep track of promotion ticks in HsOpTy

This patch adds a PromotionFlag field to HsOpTy, which is used
in pretty-printing and when determining whether to emit warnings
with -fwarn-unticked-promoted-constructors.

This allows us to correctly report tick-related warnings for things
like:

  type A = Int : '[]
  type B = [Int, Bool]

Updates haddock submodule

Fixes #19984

- - - - -
32070e6c by Jakob Bruenker at 2022-04-01T20:31:08+02:00
Implement \cases (Proposal 302)

This commit implements proposal 302: \cases - Multi-way lambda
expressions.

This adds a new expression heralded by \cases, which works exactly like
\case, but can match multiple apats instead of a single pat.

Updates submodule haddock to support the ITlcases token.

Closes #20768

- - - - -
c6f77f39 by sheaf at 2022-04-01T20:33:05+02:00
Add a regression test for #21323

This bug was fixed at some point between GHC 9.0 and GHC 9.2;
this patch simply adds a regression test.

- - - - -
3596684e by Jakob Bruenker at 2022-04-01T20:33:05+02:00
Fix error when using empty case in arrow notation

It was previously not possible to use -XEmptyCase in Arrow notation,
since GHC would print "Exception: foldb of empty list".

This is now fixed.

Closes #21301

- - - - -
9a325b59 by Ben Gamari at 2022-04-01T20:33:05+02:00
users-guide: Fix various markup issues

- - - - -
aefb1e6d by sheaf at 2022-04-01T20:36:01+02:00
Ensure implicit parameters are lifted

`tcExpr` typechecked implicit parameters by introducing a metavariable
of kind `TYPE kappa`, without enforcing that `kappa ~ LiftedRep`.
This patch instead creates a metavariable of kind `Type`.

Fixes #21327

- - - - -
ed62dc66 by Ben Gamari at 2022-04-05T11:44:51-04:00
gitlab-ci: Disable cabal-install store caching on Windows

For reasons that remain a mystery, cabal-install seems to consistently
corrupt its cache on Windows. Disable caching for now.

Works around #21347.

- - - - -
5ece5c5a by Ryan Scott at 2022-04-06T13:00:51-04:00
Add /linters/*/dist-install/ to .gitignore

Fixes #21335.

[ci skip]

- - - - -
410c76ee by Ben Gamari at 2022-04-06T13:01:28-04:00
Use static archives as an alternative to object merging

Unfortunately, `lld`'s COFF backend does not currently support object
merging. With ld.bfd having broken support for high image-load base
addresses, it's necessary to find an alternative. Here I introduce
support in the driver for generating static archives, which we use on
Windows instead of object merging.

Closes #21068.

- - - - -
400666c8 by Ben Gamari at 2022-04-06T13:01:28-04:00
rts/linker: Catch archives masquerading as object files

Check the file's header to catch static archive bearing the `.o`
extension, as may happen on Windows after the Clang refactoring.

See #21068

- - - - -
694d39f0 by Ben Gamari at 2022-04-06T13:01:28-04:00
driver: Make object merging optional

On Windows we don't have a linker which supports object joining (i.e.
the `-r` flag). Consequently, `-pgmlm` is now a `Maybe`.

See #21068.

- - - - -
41fcb5cd by Ben Gamari at 2022-04-06T13:01:28-04:00
hadrian: Refactor handling of ar flags

Previously the setup was quite fragile as it had to assume which
arguments were file arguments and which were flags.

- - - - -
3ac80a86 by Ben Gamari at 2022-04-06T13:01:28-04:00
hadrian: Produce ar archives with L modifier on Windows

Since object files may in fact be archive files, we must ensure that
their contents are merged rather than constructing an
archive-of-an-archive.

See #21068.

- - - - -
295c35c5 by Ben Gamari at 2022-04-06T13:01:28-04:00
Add a Note describing lack of object merging on Windows

See #21068.

- - - - -
d2ae0a3a by Ben Gamari at 2022-04-06T13:01:28-04:00
Build ar archives with -L when "joining" objects

Since there may be .o files which are in fact archives.

- - - - -
babb47d2 by Zubin Duggal at 2022-04-06T13:02:04-04:00
Add warnings for file header pragmas that appear in the body of a module (#20385)

Once we are done parsing the header of a module to obtain the options, we
look through the rest of the tokens in order to determine if they contain any
misplaced file header pragmas that would usually be ignored, potentially
resulting in bad error messages.

The warnings are reported immediately so that later errors don't shadow
over potentially helpful warnings.

Metric Increase:
  T13719

- - - - -
3f31825b by Ben Gamari at 2022-04-06T13:02:40-04:00
rts/AdjustorPool: Generalize to allow arbitrary contexts

Unfortunately the i386 adjustor logic needs this.

- - - - -
9b645ee1 by Ben Gamari at 2022-04-06T13:02:40-04:00
adjustors/i386: Use AdjustorPool

In !7511 (closed) I introduced a new allocator for adjustors,
AdjustorPool, which eliminates the address space fragmentation issues
which adjustors can introduce. In that work I focused on amd64 since
that was the platform where I observed issues.

However, in #21132 we noted that the size of adjustors is also a cause
of CI fragility on i386. In this MR I port i386 to use AdjustorPool.
Sadly the complexity of the i386 adjustor code does cause require a bit
of generalization which makes the code a bit more opaque but such is the
world.

Closes #21132.

- - - - -
c657a616 by Ben Gamari at 2022-04-06T13:03:16-04:00
hadrian: Clean up flavour transformer definitions

Previously the `ipe` and `omit_pragmas` transformers were hackily
defined using the textual key-value syntax. Fix this.

- - - - -
9ce273b9 by Ben Gamari at 2022-04-06T13:03:16-04:00
gitlab-ci: Drop dead HACKAGE_INDEX_STATE variable

- - - - -
01845375 by Ben Gamari at 2022-04-06T13:03:16-04:00
gitlab/darwin: Factor out bindists

This makes it a bit easier to bump them.

- - - - -
c41c478e by Ben Gamari at 2022-04-06T13:03:16-04:00
Fix a few new warnings when booting with GHC 9.2.2

-Wuni-incomplete-patterns and apparent improvements in the pattern match
checker surfaced these.

- - - - -
6563cd24 by Ben Gamari at 2022-04-06T13:03:16-04:00
gitlab-ci: Bump bootstrap compiler to 9.2.2

This is necessary to build recent `text` commits.

Bumps Hackage index state for a hashable which builds with GHC 9.2.

- - - - -
a62e983e by Ben Gamari at 2022-04-06T13:03:16-04:00
Bump text submodule to current `master`

Addresses #21295.

- - - - -
88d61031 by Vladislav Zavialov at 2022-04-06T13:03:53-04:00
Refactor OutputableBndrFlag instances

The matching on GhcPass introduced by 95275a5f25a is not necessary.
This patch reverts it to make the code simpler.

- - - - -
f601f002 by GHC GitLab CI at 2022-04-06T15:18:26-04:00
rts: Eliminate use of nested functions

This is a gcc-specific extension.

- - - - -
d4c5f29c by Ben Gamari at 2022-04-06T15:18:26-04:00
driver: Drop hacks surrounding windres invocation

Drop hack for #1828, among others as they appear to be unnecessary when
using `llvm-windres`.

- - - - -
6be2c5a7 by Ben Gamari at 2022-04-06T15:18:26-04:00
Windows/Clang: Build system adaptation

* Bump win32-tarballs to 0.7
* Move Windows toolchain autoconf logic into separate file
* Use clang and LLVM utilities as described in #21019
* Disable object merging as lld doesn't support -r
* Drop --oformat=pe-bigobj-x86-64 arguments from ld flags as LLD detects
  that the output is large on its own.
* Drop gcc wrapper since Clang finds its root fine on its own.

- - - - -
c6fb7aff by Ben Gamari at 2022-04-06T15:18:26-04:00
testsuite: Test that we can build bigobj PE objects

- - - - -
79851c07 by Ben Gamari at 2022-04-06T15:18:26-04:00
Drop -static-libgcc

This flag is not applicable when Clang is used.

- - - - -
1f8a8264 by Ben Gamari at 2022-04-06T15:18:26-04:00
testsuite: Port T16514 to C

Previously this test was C++ which made it a bit of a portability
problem.

- - - - -
d7e650d1 by Ben Gamari at 2022-04-06T15:18:26-04:00
testsuite: Mark Windows as a libc++ platform

- - - - -
d7886c46 by Ben Gamari at 2022-04-06T15:18:26-04:00
testsuite: Mark T9405 as fixed on Windows

I have not seen it fail since moving to clang.

Closes #12714.

- - - - -
4c3fbb4e by Ben Gamari at 2022-04-06T15:18:26-04:00
testsuite: Mark FloatFnInverses as fixed

The new toolchain has fixed it.

Closes #15670.

- - - - -
402c36ba by Ben Gamari at 2022-04-06T15:18:26-04:00
testsuite: Rework T13606 to avoid gcc dependence

Previously we used libgcc_s's import library in T13606. However, now that
we ship with clang we no longer have this library. Instead we now use gdi32.

- - - - -
9934ad54 by Ben Gamari at 2022-04-06T15:18:26-04:00
testsuite: Clean up tests depending on C++ std lib

- - - - -
12fcdef2 by Ben Gamari at 2022-04-06T15:18:26-04:00
testsuite: Split T13366 into two tests

Split up the C and C++ uses since the latter is significantly more
platform-dependent.

- - - - -
3c08a198 by Ben Gamari at 2022-04-06T15:18:26-04:00
testsuite: Fix mk-big-obj

I'm a bit unclear on how this previously worked as it attempted
to build an executable without defining `main`.

- - - - -
7e97cc23 by Ben Gamari at 2022-04-06T15:18:26-04:00
testsuite: Provide module definitions in T10955dyn

Otherwise the linker will export all symbols, including those provided
by the RTS, from the produced shared object. Consequently, attempting
to link against multiple objects simultaneously will cause the linker
to complain that RTS symbols are multiply defined. Avoid this
by limiting the DLL exports with a module definition file.

- - - - -
9a248afa by Ben Gamari at 2022-04-06T15:18:26-04:00
testsuite: Mark test-defaulting-plugin as fragile on Windows

Currently llvm-ar does not handle long file paths, resulting in
occassional failures of these tests and #21293.

- - - - -
39371aa4 by Ben Gamari at 2022-04-06T15:18:26-04:00
testsuite/driver: Treat framework failures of fragile tests as non-fatal

Previously we would report framework failures of tests marked as fragile
as failures. Now we rather treat them as fragile test failures, which
are not fatal to the testsuite run. Noticed while investigating #21293.

- - - - -
a1e6661d by Ben Gamari at 2022-04-06T15:18:32-04:00
Bump Cabal submodule

- Disable support for library-for-ghci on Windows as described
  in #21068.
- Teach Cabal to use `ar -L` when available

- - - - -
f7b0f63c by Ben Gamari at 2022-04-06T15:18:37-04:00
Bump process submodule

Fixes missing TEST_CC_OPTS in testsuite tests.

- - - - -
109cee19 by Ben Gamari at 2022-04-06T15:18:37-04:00
hadrian: Disable ghci libraries when object merging is not available

- - - - -
c22fba5c by Ben Gamari at 2022-04-06T15:18:37-04:00
Bump bytestring submodule

- - - - -
6e2744cc by Ben Gamari at 2022-04-06T15:18:37-04:00
Bump text submodule

- - - - -
32333747 by Ben Gamari at 2022-04-06T15:18:37-04:00
hadrian: Build wrappers using ghc rather than cc

- - - - -
59787ba5 by Ben Gamari at 2022-04-06T15:18:37-04:00
linker/PEi386: More descriptive error message

- - - - -
5e3c3c4f by Ben Gamari at 2022-04-06T15:18:37-04:00
testsuite: Mark TH_spliceE5_prof as unbroken on Windows

It was previously failing due to #18721 and now passes with the new
toolchain.

Closes #18721.

- - - - -
9eb0a9d9 by GHC GitLab CI at 2022-04-06T15:23:48-04:00
rts/PEi386: Move some debugging output to -DL

- - - - -
ce874595 by Ben Gamari at 2022-04-06T15:24:01-04:00
nativeGen/x86: Use %rip-relative addressing

On Windows with high-entropy ASLR we must use %rip-relative addressing
to avoid overflowing the signed 32-bit immediate size of x86-64.
Since %rip-relative addressing comes essentially for free and can make
linking significantly easier, we use it on all platforms.

- - - - -
52deee64 by Ben Gamari at 2022-04-06T15:24:01-04:00
Generate LEA for label expressions

- - - - -
105a0056 by Ben Gamari at 2022-04-06T15:24:01-04:00
Refactor is32BitLit to take Platform rather than Bool

- - - - -
ec4526b5 by Ben Gamari at 2022-04-06T15:24:01-04:00
Don't assume that labels are 32-bit on Windows

- - - - -
ffdbe457 by Ben Gamari at 2022-04-06T15:24:01-04:00
nativeGen: Note signed-extended nature of MOV

- - - - -
bfb79697 by Ben Gamari at 2022-04-06T15:30:56-04:00
rts: Move __USE_MINGW_ANSI_STDIO definition to PosixSource.h

It's easier to ensure that this is included first than Rts.h

- - - - -
5ad143fd by Ben Gamari at 2022-04-06T15:30:56-04:00
rts: Fix various #include issues

This fixes various violations of the newly-added RTS includes linter.

- - - - -
a59a66a8 by Ben Gamari at 2022-04-06T15:30:56-04:00
testsuite: Lint RTS #includes

Verifies two important properties of #includes in the RTS:

 * That system headers don't appear inside of a `<BeginPrivate.h>` block
   as this can hide system library symbols, resulting in very
   hard-to-diagnose linker errors

 * That no headers precede `Rts.h`, ensuring that __USE_MINGW_ANSI_STDIO
   is set correctly before system headers are included.

- - - - -
42bf7528 by GHC GitLab CI at 2022-04-06T16:25:04-04:00
rts/PEi386: Fix memory leak

Previously we would leak the section information of the `.bss`
section.

- - - - -
d286a55c by Ben Gamari at 2022-04-06T16:25:25-04:00
rts/linker: Preserve information about symbol types

As noted in #20978, the linker would previously handle overflowed
relocations by creating a jump island. While this is fine in the case of
code symbols, it's very much not okay in the case of data symbols. To
fix this we must keep track of whether each symbol is code or data and
relocate them appropriately. This patch takes the first step in this
direction, adding a symbol type field to the linker's symbol table. It
doesn't yet change relocation behavior to take advantage of this
knowledge.

Fixes #20978.

- - - - -
e689e9d5 by Ben Gamari at 2022-04-06T16:25:25-04:00
rts/PEi386: Fix relocation overflow behavior

This fixes handling of overflowed relocations on PEi386 targets:

 * Refuse to create jump islands for relocations of data symbols
 * Correctly handle the `__imp___acrt_iob_func` symbol, which is an new
   type of symbol: `SYM_TYPE_INDIRECT_DATA`

- - - - -
655e7d8f by GHC GitLab CI at 2022-04-06T16:25:25-04:00
rts: Mark anything that might have an info table as data

Tables-next-to-code mandates that we treat symbols with info tables like
data since we cannot relocate them using a jump island.

See #20983.

- - - - -
7e8cc293 by Ben Gamari at 2022-04-06T16:25:25-04:00
rts/PEi386: Rework linker

This is a significant rework of the PEi386 linker, making the linker
compatible with high image base addresses. Specifically, we now use the
m32 allocator instead of `HeapAllocate`.

In addition I found a number of latent bugs in our handling of import
libraries and relocations. I've added quite a few comments describing
what I've learned about Windows import libraries while fixing these.

Thanks to Tamar Christina (@Phyx) for providing the address space search
logic, countless hours of help while debugging, and his boundless
Windows knowledge.

Co-Authored-By: Tamar Christina <tamar at zhox.com>

- - - - -
ff625218 by Ben Gamari at 2022-04-06T16:25:25-04:00
rts/PEi386: Move allocateBytes to MMap.c

- - - - -
f562b5ca by Ben Gamari at 2022-04-06T16:25:25-04:00
rts/PEi386: Avoid accidentally-quadratic allocation cost

We now preserve the address that we last mapped, allowing us to resume
our search and avoiding quadratic allocation costs. This fixes the
runtime of T10296a, which allocates many adjustors.

- - - - -
3247b7db by Ben Gamari at 2022-04-06T16:25:25-04:00
Move msvcrt dep out of base

- - - - -
fa404335 by Ben Gamari at 2022-04-06T16:25:25-04:00
rts/linker: More descriptive debug output

- - - - -
140f338f by Ben Gamari at 2022-04-06T16:25:25-04:00
rts/PathUtils: Define pathprintf in terms of snwprintf on Windows

swprintf deviates from usual `snprintf` semantics in that it does not
guarantee reasonable behavior when the buffer is NULL (that is,
returning the number of bytes that would have been emitted).

- - - - -
eb60565b by Ben Gamari at 2022-04-06T16:25:25-04:00
rts/linker: Report archive member index

- - - - -
209fd61b by Ben Gamari at 2022-04-06T16:25:25-04:00
rts/linker: Split up object resolution and initialization

Previously the RTS linker would call initializers during the
"resolve" phase of linking. However, this is problematic in the
case of cyclic dependencies between objects. In particular, consider
the case where we have a situation where a static library
contains a set of recursive objects:

 * object A has depends upon symbols in object B
 * object B has an initializer that depends upon object A
 * we try to load object A

The linker would previously:

 1. start resolving object A
 2. encounter the reference to object B, loading it resolve object B
 3. run object B's initializer
 4. the initializer will attempt to call into object A,
    which hasn't been fully resolved (and therefore protected)

Fix this by moving constructor execution to a new linking
phase, which follows resolution.

Fix #21253.

- - - - -
8e8a1021 by Ben Gamari at 2022-04-06T16:25:25-04:00
rts/linker/LoadArchive: Fix leaking file handle

Previously `isArchive` could leak a `FILE` handle if the `fread`
returned a short read.

- - - - -
429ea5d9 by sheaf at 2022-04-07T07:55:52-04:00
Remove Fun pattern from Typeable COMPLETE set

GHC merge request !963 improved warnings in the presence of
COMPLETE annotations. This allows the removal of the Fun pattern
from the complete set.

Doing so expectedly causes some redundant pattern match warnings,
in particular in GHC.Utils.Binary.Typeable and Data.Binary.Class
from the binary library; this commit addresses that.

Updates binary submodule

Fixes #20230

- - - - -
54b18824 by Alan Zimmerman at 2022-04-07T07:56:28-04:00
EPA: handling of con_bndrs in mkGadtDecl

Get rid of unnnecessary case clause that always matched.

Closes #20558

- - - - -
9c838429 by Ben Gamari at 2022-04-07T09:38:53-04:00
testsuite: Mark T10420 as broken on Windows

Due to #21322.

- - - - -
50739d2b by Ben Gamari at 2022-04-07T09:42:42-04:00
rts: Refactor and fix printf attributes on clang

Clang on Windows does not understand the `gnu_printf` attribute; use
`printf` instead.

- - - - -
9eeaeca4 by Ben Gamari at 2022-04-07T09:42:42-04:00
rts: Add missing newline in error message

- - - - -
fcef9a17 by Ben Gamari at 2022-04-07T09:42:42-04:00
configure: Make environ decl check more robust

Some platforms (e.g. Windows/clang64) declare `environ` in `<stdlib.h>`,
not `<unistd.h>`

- - - - -
8162b4f3 by Ben Gamari at 2022-04-07T09:42:42-04:00
rts: Adjust RTS symbol table on Windows for ucrt

- - - - -
633280d7 by Ben Gamari at 2022-04-07T09:43:21-04:00
testsuite: Fix exit code of bounds checking tests on Windows

`abort` exits with 255, not 134, on Windows.

- - - - -
cab4dc01 by Ben Gamari at 2022-04-07T09:43:31-04:00
testsuite: Update expected output from T5435 tests on Windows

I'll admit, I don't currently see *why* this output is reordered
but it is a fairly benign difference and I'm out of time to investigate.

- - - - -
edf5134e by Ben Gamari at 2022-04-07T09:43:35-04:00
testsuite: Mark T20918 as broken on Windows

Our toolchain on Windows doesn't currently have Windows support.

- - - - -
d0ddeff3 by Ben Gamari at 2022-04-07T09:43:39-04:00
testsuite: Mark linker unloading tests as broken on Windows

Due to #20354.

We will need to investigate this prior the release.

- - - - -
5a86da2b by Ben Gamari at 2022-04-07T09:43:43-04:00
testsuite: Mark T9405 as broken on Windows

Due to #21361.

- - - - -
4aa86dcf by Ben Gamari at 2022-04-07T09:44:18-04:00
Merge branches 'wip/windows-high-codegen', 'wip/windows-high-linker', 'wip/windows-clang-2' and 'wip/lint-rts-includes' into wip/windows-clang-join

- - - - -
7206f055 by Ben Gamari at 2022-04-07T09:45:07-04:00
rts/CloneStack: Ensure that Rts.h is #included first

As is necessary on Windows.

- - - - -
9cfcb27b by Ben Gamari at 2022-04-07T09:45:07-04:00
rts: Fallback to ucrtbase not msvcrt

Since we have switched to Clang the toolchain now links against
ucrt rather than msvcrt.

- - - - -
d6665d85 by Ben Gamari at 2022-04-07T09:46:25-04:00
Accept spurious perf test shifts on Windows

Metric Decrease:
    T16875
Metric Increase:
    T12707
    T13379
    T3294
    T4801
    T5321FD
    T5321Fun
    T783

- - - - -
83363c8b by Simon Peyton Jones at 2022-04-07T12:57:21-04:00
Use prepareBinding in tryCastWorkerWrapper

As #21144 showed, tryCastWorkerWrapper was calling prepareRhs, and
then unconditionally floating the bindings, without the checks of
doFloatFromRhs.   That led to floating an unlifted binding into
a Rec group.

This patch refactors prepareBinding to make these checks,
and do them uniformly across all calls.  A nice improvement.

Other changes
* Instead of passing around a RecFlag and a TopLevelFlag; and sometimes
  a (Maybe SimplCont) for join points, define a new Simplifier-specific
  data type BindContext:
      data BindContext = BC_Let  TopLevelFlag RecFlag
                       | BC_Join SimplCont
  and use it consistently.

* Kill off completeNonRecX by inlining it.  It was only called in
  one place.

* Add a wrapper simplImpRules for simplRules.

Compile time on T9630 drops by 4.7%; little else changes.

Metric Decrease:
    T9630

- - - - -
02279a9c by Vladislav Zavialov at 2022-04-07T12:57:59-04:00
Rename [] to List (#21294)

This patch implements a small part of GHC Proposal #475.
The key change is in GHC.Types:

	- data [] a = [] | a : [a]
	+ data List a = [] | a : List a

And the rest of the patch makes sure that List is pretty-printed as []
in various contexts.

Updates the haddock submodule.

- - - - -
08480d2a by Simon Peyton Jones at 2022-04-07T12:58:36-04:00
Fix the free-var test in validDerivPred

The free-var test (now documented as (VD3)) was too narrow,
affecting only class predicates.  #21302 demonstrated that
this wasn't enough!

Fixes #21302.

Co-authored-by: Ryan Scott <ryan.gl.scott at gmail.com>

- - - - -
b3d6d23d by Andreas Klebinger at 2022-04-07T12:59:12-04:00
Properly explain where INLINE pragmas can appear.

Fixes #20676

- - - - -
23ef62b3 by Ben Gamari at 2022-04-07T14:28:28-04:00
rts: Fix off-by-one in snwprintf usage

- - - - -
b2dbcc7d by Simon Jakobi at 2022-04-08T03:00:38-04:00
Improve seq[D]VarSet

Previously, the use of size[D]VarSet would involve a traversal of the
entire underlying IntMap. Since IntMaps are already spine-strict,
this is unnecessary.

- - - - -
64ac20a7 by sheaf at 2022-04-08T03:01:16-04:00
Add test for #21338

This no-skolem-info bug was fixed by the no-skolem-info patch
that will be part of GHC 9.4. This patch adds a regression test for
the issue reported in issue #21338.

Fixes #21338.

- - - - -
c32c4db6 by Ben Gamari at 2022-04-08T03:01:53-04:00
rts: Move __USE_MINGW_ANSI_STDIO definition to PosixSource.h

It's easier to ensure that this is included first than Rts.h

- - - - -
56f85d62 by Ben Gamari at 2022-04-08T03:01:53-04:00
rts: Fix various #include issues

This fixes various violations of the newly-added RTS includes linter.

- - - - -
cb1f31f5 by Ben Gamari at 2022-04-08T03:01:53-04:00
testsuite: Lint RTS #includes

Verifies two important properties of #includes in the RTS:

 * That system headers don't appear inside of a `<BeginPrivate.h>` block
   as this can hide system library symbols, resulting in very
   hard-to-diagnose linker errors

 * That no headers precede `Rts.h`, ensuring that __USE_MINGW_ANSI_STDIO
   is set correctly before system headers are included.

- - - - -
c44432db by Krzysztof Gogolewski at 2022-04-08T03:02:29-04:00
Fixes to 9.4 release notes

- Mention -Wforall-identifier
- Improve description of withDict
- Fix formatting

- - - - -
777365f1 by sheaf at 2022-04-08T09:43:35-04:00
Correctly report SrcLoc of redundant constraints

We were accidentally dropping the source location information in
certain circumstances when reporting redundant constraints. This patch
makes sure that we set the TcLclEnv correctly before reporting the
warning.

Fixes #21315

- - - - -
af300a43 by Vladislav Zavialov at 2022-04-08T09:44:11-04:00
Reject illegal quote mark in data con declarations (#17865)

* Non-fatal (i.e. recoverable) parse error
* Checking infix constructors
* Extended the regression test

- - - - -
56254e6b by Ben Gamari at 2022-04-08T09:59:46-04:00
Merge remote-tracking branch 'origin/master'

- - - - -
6e2c3b7c by Matthew Pickering at 2022-04-08T13:55:15-04:00
driver: Introduce HomeModInfoCache abstraction

The HomeModInfoCache is a mutable cache which is updated incrementally
as the driver completes, this makes it robust to exceptions including
(SIGINT)

The interface for the cache is described by the `HomeMOdInfoCache` data
type:

```
data HomeModInfoCache = HomeModInfoCache { hmi_clearCache :: IO [HomeModInfo]
                                         , hmi_addToCache :: HomeModInfo -> IO () }
```

The first operation clears the cache and returns its contents. This is
designed so it's harder to end up in situations where the cache is
retained throughout the execution of upsweep.

The second operation allows a module to be added to the cache.

The one slightly nasty part is in `interpretBuildPlan` where we have to
be careful to ensure that the cache writes happen:

1. In parralel
2. Before the executation continues after upsweep.

This requires some simple, localised MVar wrangling.

Fixes #20780

- - - - -
85f4a3c9 by Andreas Klebinger at 2022-04-08T13:55:50-04:00
Add flag -fprof-manual which controls if GHC should honour manual cost centres.

This allows disabling of manual control centres in code a user doesn't control like
libraries.

Fixes #18867

- - - - -
3415981c by Vladislav Zavialov at 2022-04-08T13:56:27-04:00
HsUniToken for :: in GADT constructors (#19623)

One more step towards the new design of EPA.

Updates the haddock submodule.

- - - - -
23f95735 by sheaf at 2022-04-08T13:57:07-04:00
Docs: datacon eta-expansion, rep-poly checks

The existing notes weren't very clear on how the eta-expansion of
data constructors that occurs in tcInferDataCon/dsConLike interacts
with the representation polymorphism invariants. So we explain with
a few more details how we ensure that the representation-polymorphic
lambdas introduced by tcInferDataCon/dsConLike don't end up causing
problems, by checking they are properly instantiated and then relying
on the simple optimiser to perform beta reduction.

A few additional changes:

  - ConLikeTc just take type variables instead of binders, as we
    never actually used the binders.
  - Removed the FRRApp constructor of FRROrigin; it was no longer used
    now that we use ExpectedFunTyOrigin.
  - Adds a bit of documentation to the constructors
    of ExpectedFunTyOrigin.

- - - - -
d4480490 by Matthew Pickering at 2022-04-08T13:57:43-04:00
ci: Replace "always" with "on_success" to stop build jobs running before hadrian-ghci has finished

See https://docs.gitlab.com/ee/ci/yaml/#when

* always means, always run not matter what
* on_success means, run if the dependencies have built successfully

- - - - -
0736e949 by Vladislav Zavialov at 2022-04-08T13:58:19-04:00
Disallow (->) as a data constructor name (#16999)

The code was misusing isLexCon, which was never meant for validation.
In fact, its documentation states the following:

	Use these functions to figure what kind of name a 'FastString'
	represents; these functions do /not/ check that the identifier
	is valid.

Ha! This sign can't stop me because I can't read.

The fix is to use okConOcc instead. The other checks (isTcOcc or
isDataOcc) seem superfluous, so I also removed those.

- - - - -
e58d5eeb by Simon Peyton Jones at 2022-04-08T13:58:55-04:00
Tiny documentation wibble

This commit
   commit 83363c8b04837ee871a304cf85207cf79b299fb0
   Author: Simon Peyton Jones <simon.peytonjones at gmail.com>
   Date:   Fri Mar 11 16:55:38 2022 +0000

       Use prepareBinding in tryCastWorkerWrapper

refactored completeNonRecX away, but left a Note referring to it.
This MR fixes that Note.

- - - - -
4bb00839 by Matthew Pickering at 2022-04-09T07:40:28-04:00
ci: Fix nightly head.hackage pipelines

This also needs a corresponding commit to head.hackage, I also made the
job explicitly depend on the fedora33 job so that it isn't blocked by a
failing windows job, which causes docs-tarball to fail.

- - - - -
3c48e12a by Matthew Pickering at 2022-04-09T07:40:28-04:00
ci: Remove doc-tarball dependency from perf and perf-nofib jobs

These don't depend on the contents of the tarball so we can run them
straight after the fedora33 job finishes.

- - - - -
27362265 by Matthew Pickering at 2022-04-09T07:41:04-04:00
Bump deepseq to 1.4.7.0

Updates deepseq submodule

Fixes #20653

- - - - -
dcf30da8 by Joachim Breitner at 2022-04-09T13:02:19-04:00
Drop the app invariant

previously, GHC had the "let/app-invariant" which said that the RHS of a
let or the argument of an application must be of lifted type or ok for
speculation. We want this on let to freely float them around, and we
wanted that on app to freely convert between the two (e.g. in
beta-reduction or inlining).

However, the app invariant meant that simple code didn't stay simple and
this got in the way of rules matching. By removing the app invariant,
this thus fixes #20554.

The new invariant is now called "let-can-float invariant", which is
hopefully easier to guess its meaning correctly.

Dropping the app invariant means that everywhere where we effectively do
beta-reduction (in the two simplifiers, but also in `exprIsConApp_maybe`
and other innocent looking places) we now have to check if the argument
must be evaluated (unlifted and side-effecting), and analyses have to be
adjusted to the new semantics of `App`.

Also, `LetFloats` in the simplifier can now also carry such non-floating
bindings.

The fix for DmdAnal, refine by Sebastian, makes functions with unlifted
arguments strict in these arguments, which changes some signatures.

This causes some extra calls to `exprType` and `exprOkForSpeculation`,
so some perf benchmarks regress a bit (while others improve).

Metric Decrease:
    T9020
Metric Increase:
    LargeRecord
    T12545
    T15164
    T16577
    T18223
    T5642
    T9961

Co-authored-by: Sebastian Graf <sebastian.graf at kit.edu>

- - - - -
6c6c5379 by Philip Hazelden at 2022-04-09T13:02:59-04:00
Add functions traceWith, traceShowWith, traceEventWith.

As discussed at
https://github.com/haskell/core-libraries-committee/issues/36

- - - - -
8fafacf7 by Philip Hazelden at 2022-04-09T13:02:59-04:00
Add tests for several trace functions.

- - - - -
20bbf3ac by Philip Hazelden at 2022-04-09T13:02:59-04:00
Update changelog.

- - - - -
47d18b0b by Andreas Klebinger at 2022-04-09T13:03:35-04:00
Add regression test for #19569

- - - - -
5f8d6e65 by sheaf at 2022-04-09T13:04:14-04:00
Fix missing SymCo in pushCoercionIntoLambda

There was a missing SymCo in pushCoercionIntoLambda. Currently
this codepath is only used with rewrite rules, so this bug managed
to slip by, but trying to use pushCoercionIntoLambda in other contexts
revealed the bug.

- - - - -
20eca489 by Vladislav Zavialov at 2022-04-09T13:04:50-04:00
Refactor: simplify lexing of the dot

Before this patch, the lexer did a truly roundabout thing with the dot:

1. look up the varsym in reservedSymsFM and turn it into ITdot
2. under OverloadedRecordDot, turn it into ITvarsym
3. in varsym_(prefix|suffix|...) turn it into ITvarsym, ITdot, or
   ITproj, depending on extensions and whitespace

Turns out, the last step is sufficient to handle the dot correctly.
This patch removes the first two steps.

- - - - -
5440f63e by Hécate Moonlight at 2022-04-12T11:11:06-04:00
Document that DuplicateRecordFields doesn't tolerates ambiguous fields

Fix #19891

- - - - -
0090ad7b by Sebastian Graf at 2022-04-12T11:11:42-04:00
Eta reduction based on evaluation context (#21261)

I completely rewrote our Notes surrounding eta-reduction. The new entry point is
`Note [Eta reduction makes sense]`.

Then I went on to extend the Simplifier to maintain an evaluation context in the
form of a `SubDemand` inside a `SimplCont`. That `SubDemand` is useful for doing
eta reduction according to `Note [Eta reduction based on evaluation context]`,
which describes how Demand analysis, Simplifier and `tryEtaReduce` interact to
facilitate eta reduction in more scenarios.

Thus we fix #21261.

ghc/alloc perf marginally improves (-0.0%). A medium-sized win is when compiling
T3064 (-3%). It seems that haddock improves by 0.6% to 1.0%, too.

Metric Decrease:
    T3064

- - - - -
4d2ee313 by Sebastian Graf at 2022-04-12T17:54:57+02:00
Specialising through specialised method calls (#19644)

In #19644, we discovered that the ClassOp/DFun rules from
Note [ClassOp/DFun selection] inhibit transitive specialisation in a scenario
like
```
class C a where m :: Show b => a -> b -> ...; n :: ...
instance C Int where m = ... -- $cm :: Show b => Int -> b -> ...
f :: forall a b. (C a, Show b) => ...
f $dC $dShow = ... m @a $dC @b $dShow ...
main = ... f @Int @Bool ...
```
After we specialise `f` for `Int`, we'll see `m @a $dC @b $dShow` in the body of
`$sf`. But before this patch, Specialise doesn't apply the ClassOp/DFun rule to
rewrite to a call of the instance method for `C Int`, e.g., `$cm @Bool $dShow`.
As a result, Specialise couldn't further specialise `$cm` for `Bool`.

There's a better example in `Note [Specialisation modulo dictionary selectors]`.

This patch enables proper Specialisation, as follows:

1. In the App case of `specExpr`, try to apply the CalssOp/DictSel rule on the
   head of the application
2. Attach an unfolding to freshly-bound dictionary ids such as `$dC` and
   `$dShow` in `bindAuxiliaryDict`

NB: Without (2), (1) would be pointless, because `lookupRule` wouldn't be able
to look into the RHS of `$dC` to see the DFun.

(2) triggered #21332, because the Specialiser floats around dictionaries without
accounting for them in the `SpecEnv`'s `InScopeSet`, triggering a panic when
rewriting dictionary unfoldings.

Fixes #19644 and #21332.

- - - - -
b06f4f47 by Sebastian Graf at 2022-04-12T17:54:58+02:00
Specialise: Check `typeDeterminesValue` before specialising on an interesting dictionary

I extracted the checks from `Note [Type determines value]` into its own
function, so that we share the logic properly. Then I made sure that we
actually call `typeDeterminesValue` everywhere we check for `interestingDict`.

- - - - -
a42dbc55 by Matthew Pickering at 2022-04-13T06:24:52-04:00
Refine warning about defining rules in SAFE modules

This change makes it clear that it's the definition rather than any
usage which is a problem, and that rules defined in other modules will
still be  used to do rewrites.

Fixes #20923

- - - - -
df893f66 by Andreas Klebinger at 2022-04-14T08:18:37-04:00
StgLint: Lint constructor applications and strict workers for arity.

This will mean T9208 when run with lint will return a lint error instead
of resulting in a panic.

Fixes #21117

- - - - -
426ec446 by sheaf at 2022-04-14T08:19:16-04:00
Hadrian: use a set to keep track of ways

The order in which ways are provided doesn't matter,
so we use a data structure with the appropriate semantics to
represent ways.

Fixes #21378

- - - - -
7c639b9a by Dylan Yudaken at 2022-04-15T13:55:59-04:00
Only enable PROF_SPIN in DEBUG

- - - - -
96b9e5ea by Ben Gamari at 2022-04-15T13:56:34-04:00
testsuite: Add test for #21390

- - - - -
d8392f6a by Ben Gamari at 2022-04-15T13:56:34-04:00
rts: Ensure that the interpreter doesn't disregard tags

Previously the interpreter's handling of `RET_BCO` stack frames would
throw away the tag of the returned closure. This resulted in #21390.

- - - - -
83c67f76 by Alan Zimmerman at 2022-04-20T11:49:28-04:00
Add -dkeep-comments flag to keep comments in the parser

This provides a way to set the Opt_KeepRawTokenStream from the command
line, allowing exact print annotation users to see exactly what is
produced for a given parsed file, when used in conjunction with
-ddump-parsed-ast

Discussed in #19706, but this commit does not close the issue.

- - - - -
a5ea65c9 by Krzysztof Gogolewski at 2022-04-20T11:50:04-04:00
Remove LevityInfo

Every Id was storing a boolean whether it could be levity-polymorphic.
This information is no longer needed since representation-checking
has been moved to the typechecker.

- - - - -
49bd7584 by Andreas Klebinger at 2022-04-20T11:50:39-04:00
Fix a shadowing issue in StgUnarise.

For I assume performance reasons we don't record no-op replacements
during unarise. This lead to problems with code like this:

    f = \(Eta_B0 :: VoidType) x1 x2 ->
       ... let foo = \(Eta_B0 :: LiftedType) -> g x y Eta_B0
           in ...

Here we would record the outer Eta_B0 as void rep, but would not
shadow Eta_B0 inside `foo` because this arg is single-rep and so
doesn't need to replaced. But this means when looking at occurence
sites we would check the env and assume it's void rep based on the
entry we made for the (no longer in scope) outer `Eta_B0`.

Fixes #21396 and the ticket has a few more details.

- - - - -
0c02c919 by Simon Peyton Jones at 2022-04-20T11:51:15-04:00
Fix substitution in bindAuxiliaryDict

In GHC.Core.Opt.Specialise.bindAuxiliaryDict we were unnecessarily
calling `extendInScope` to bring into scope variables that were
/already/ in scope.  Worse, GHC.Core.Subst.extendInScope strangely
deleted the newly-in-scope variables from the substitution -- and that
was fatal in #21391.

I removed the redundant calls to extendInScope.

More ambitiously, I changed GHC.Core.Subst.extendInScope (and cousins)
to stop deleting variables from the substitution.  I even changed the
names of the function to extendSubstInScope (and cousins) and audited
all the calls to check that deleting from the substitution was wrong.
In fact there are very few such calls, and they are all about
introducing a fresh non-in-scope variable.  These are "OutIds"; it is
utterly wrong to mess with the "InId" substitution.

I have not added a Note, because I'm deleting wrong code, and it'd be
distracting to document a bug.

- - - - -
0481a6af by Cheng Shao at 2022-04-21T11:06:06+00:00
[ci skip] Drop outdated TODO in RtsAPI.c

- - - - -
1e062a8a by Ben Gamari at 2022-04-22T02:12:59-04:00
rts: Introduce ip_STACK_FRAME

While debugging it is very useful to be able to determine whether a
given info table is a stack frame or not. We have spare bits in the
closure flags array anyways, use one for this information.

- - - - -
08a6a2ee by Ben Gamari at 2022-04-22T02:12:59-04:00
rts: Mark closureFlags array as const

- - - - -
8f9b8282 by Krzysztof Gogolewski at 2022-04-22T02:13:35-04:00
Check for zero-bit types in sizeExpr

Fixes #20940

Metric Decrease:
    T18698a

- - - - -
fcf22883 by Andreas Klebinger at 2022-04-22T02:14:10-04:00
Include the way string in the file name for dump files.

This can be disabled by `-fno-dump-with-ways` if not desired.
Finally we will be able to look at both profiled and non-profiled dumps
when compiling with dump flags and we compile in both ways.

- - - - -
252394ce by Bodigrim at 2022-04-22T02:14:48-04:00
Improve error messages from GHC.IO.Encoding.Failure

- - - - -
250f57c1 by Bodigrim at 2022-04-22T02:14:48-04:00
Update test baselines to match new error messages from GHC.IO.Encoding.Failure

- - - - -
5ac9b321 by Ben Gamari at 2022-04-22T02:15:25-04:00
get-win32-tarballs: Drop i686 architecture

As of #18487 we no longer support 32-bit Windows.

Fixes #21372.

- - - - -
dd5fecb0 by Ben Gamari at 2022-04-22T02:16:00-04:00
hadrian: Don't rely on xxx not being present in installation path

Previously Hadrian's installation makefile would assume that the string
`xxx` did not appear in the installation path. This would of course
break for some users.

Fixes #21402.

- - - - -
09e98859 by Ben Gamari at 2022-04-22T02:16:35-04:00
testsuite: Ensure that GHC doesn't pick up environment files

Here we set GHC_ENVIRONMENT="-" to ensure that GHC invocations of tests
don't pick up a user's local package environment.

Fixes #21365.

Metric Decrease:
    T10421
    T12234
    T12425
    T13035
    T16875
    T9198

- - - - -
76bb8cb3 by Ben Gamari at 2022-04-22T02:17:11-04:00
hadrian: Enable -dlint in devel2 flavour

Previously only -dcore-lint was enabled.

- - - - -
f435d55f by Krzysztof Gogolewski at 2022-04-22T08:00:18-04:00
Fixes to rubbish literals

* In CoreToStg, the application 'RUBBISH[rep] x' was simplified
  to 'RUBBISH[rep]'. But it is possible that the result of the function
  is represented differently than the function.
* In Unarise, 'LitRubbish (primRepToType prep)'
  is incorrect: LitRubbish takes a RuntimeRep such as IntRep,
  while primRepToType returns a type such as Any @(TYPE IntRep). Use
  primRepToRuntimeRep instead.
  This code is never run in the testsuite.
* In StgToByteCode, all rubbish literals were assumed to be boxed.
  This code predates representation-polymorphic RubbishLit and I think
  it was not updated.

I don't have a testcase for any of those issues, but the code looks
wrong.

- - - - -
93c16b94 by sheaf at 2022-04-22T08:00:57-04:00
Relax "suppressing errors" assert in reportWanteds

The assertion in reportWanteds that we aren't suppressing all the
Wanted constraints was too strong: it might be the case that we are
inside an implication, and have already reported an unsolved Wanted
from outside the implication. It is possible that all Wanteds inside
the implication have been rewritten by the outer Wanted, so we shouldn't
throw an assertion failure in that case.

Fixes #21405

- - - - -
78ec692d by Andreas Klebinger at 2022-04-22T08:01:33-04:00
Mention new MutableByteArray# wrapper in base changelog.

- - - - -
56d7cb53 by Eric Lindblad at 2022-04-22T14:13:32-04:00
unlist announce

- - - - -
1e4dcf23 by sheaf at 2022-04-22T14:14:12-04:00
decideMonoTyVars: account for CoVars in candidates

The "candidates" passed to decideMonoTyVars can contain coercion holes.
This is because we might well decide to quantify over some unsolved
equality constraints, as long as they are not definitely insoluble.

In that situation, decideMonoTyVars was passing a set of type variables
that was not closed over kinds to closeWrtFunDeps, which was tripping
up an assertion failure.

Fixes #21404

- - - - -
2c541f99 by Simon Peyton Jones at 2022-04-22T14:14:47-04:00
Improve floated dicts in Specialise

Second fix to #21391.  It turned out that we missed calling
bringFloatedDictsIntoScope when specialising imports, which
led to the same bug as before.

I refactored to move that call to a single place, in specCalls,
so we can't forget it.

This meant making `FloatedDictBinds` into its own type, pairing
the dictionary bindings themselves with the set of their binders.
Nicer this way.

- - - - -
0950e2c4 by Ben Gamari at 2022-04-25T10:18:17-04:00
hadrian: Ensure that --extra-lib-dirs are used

Previously we only took `extraLibDirs` and friends from the package
description, ignoring any contribution from the `LocalBuildInfo`. Fix
this.

Fixes #20566.

- - - - -
53cc93ae by Ben Gamari at 2022-04-25T10:18:17-04:00
hadrian: Drop redundant include directories

The package-specific include directories in
Settings.Builders.Common.cIncludeDirs are now redundant since they now
come from Cabal.

Closes #20566.

- - - - -
b2721819 by Ben Gamari at 2022-04-25T10:18:17-04:00
hadrian: Clean up handling of libffi dependencies

- - - - -
18e5103f by Ben Gamari at 2022-04-25T10:18:17-04:00
testsuite: More robust library way detection

Previously `test.mk` would try to determine whether the dynamic,
profiling, and vanilla library ways are available by searching for
`PrimOpWrappers.{,dyn_,p_}hi` in directory reported by `ghc-pkg field
ghc-prim library-dirs`. However, this is extremely fragile as
there is no guarantee that there is only one library directory. To
handle the case of multiple `library-dirs` correct we would
have to carry out the delicate task of tokenising the directory list (in
shell, no less).

Since this isn't a task that I am eager to solve, I have rather moved
the detection logic into the testsuite driver and instead perform a test
compilation in each of the ways. This should be more robust than the
previous approach.

I stumbled upon this while fixing #20579.

- - - - -
6c7a4913 by Ben Gamari at 2022-04-25T10:18:17-04:00
testsuite: Cabalify ghc-config

To ensure that the build benefits from Hadrian's usual logic for building
packages, avoiding #21409.

Closes #21409.

- - - - -
9af091f7 by Ben Gamari at 2022-04-25T10:18:53-04:00
rts: Factor out built-in GC roots

- - - - -
e7c4719d by Ben Gamari at 2022-04-25T10:18:54-04:00
Ensure that wired-in exception closures aren't GC'd

As described in Note [Wired-in exceptions are not CAFfy], a small set of
built-in exception closures get special treatment in the code generator,
being declared as non-CAFfy despite potentially containing CAF
references. The original intent of this treatment for the RTS to then
add StablePtrs for each of the closures, ensuring that they are not
GC'd. However, this logic was not applied consistently and eventually
removed entirely in 951c1fb0. This lead to #21141.

Here we fix this bug by reintroducing the StablePtrs and document the
status quo.

Closes #21141.

- - - - -
9587726f by Ben Gamari at 2022-04-25T10:18:54-04:00
testsuite: Add testcase for #21141

- - - - -
cb71226f by Ben Gamari at 2022-04-25T10:19:29-04:00
Drop dead code in GHC.Linker.Static.linkBinary'

Previously we supported building statically-linked executables using
libtool. However, this was dropped in
91262e75dd1d80f8f28a3922934ec7e59290e28c in favor of using ar/ranlib
directly. Consequently we can drop this logic.

Fixes #18826.

- - - - -
9420d26b by Ben Gamari at 2022-04-25T10:19:29-04:00
Drop libtool path from settings file

GHC no longers uses libtool for linking and therefore this is no longer
necessary.

- - - - -
41cf758b by Ben Gamari at 2022-04-25T10:19:29-04:00
Drop remaining vestiges of libtool

Drop libtool logic from gen-dll, allowing us to drop the remaining logic
from the `configure` script.

Strangely, this appears to reliably reduce compiler allocations of
T16875 on Windows.

Closes #18826.

Metric Decrease:
    T16875

- - - - -
e09afbf2 by Ben Gamari at 2022-04-25T10:20:05-04:00
rts: Refactor handling of dead threads' stacks

This fixes a bug that @JunmingZhao42 and I noticed while working on her
MMTK port. Specifically, in stg_stop_thread we used stg_enter_info as a
sentinel at the tail of a stack after a thread has completed. However,
stg_enter_info expects to have a two-field payload, which we do not
push. Consequently, if the GC ends up somehow the stack it will attempt
to interpret data past the end of the stack as the frame's fields,
resulting in unsound behavior.

To fix this I eliminate this hacky use of `stg_stop_thread` and instead
introduce a new stack frame type, `stg_dead_thread_info`. Not only does
this eliminate the potential for the previously mentioned memory
unsoundness but it also more clearly captures the intended structure of
the dead threads' stacks.

- - - - -
e76705cf by Ben Gamari at 2022-04-25T10:20:05-04:00
rts: Improve documentation of closure types

Also drops the unused TREC_COMMITTED transaction state.

- - - - -
f2c08124 by Bodigrim at 2022-04-25T10:20:44-04:00
Document behaviour of RULES with KnownNat

- - - - -
360dc2bc by Li-yao Xia at 2022-04-25T19:13:06+00:00
Fix rendering of liftA haddock

- - - - -
16df6058 by Ben Gamari at 2022-04-27T10:02:25-04:00
testsuite: Report minimum and maximum stat changes

As suggested in #20733.

- - - - -
e39cab62 by Fabian Thorand at 2022-04-27T10:03:03-04:00
Defer freeing of mega block groups

Solves the quadratic worst case performance of freeing megablocks that
was described in issue #19897.

During GC runs, we now keep a secondary free list for megablocks that is
neither sorted, nor coalesced. That way, free becomes an O(1) operation
at the expense of not being able to reuse memory for larger allocations.
At the end of a GC run, the secondary free list is sorted and then
merged into the actual free list in a single pass.

That way, our worst case performance is O(n log(n)) rather than O(n^2).

We postulate that temporarily losing coalescense during a single GC run
won't have any adverse effects in practice because:

- We would need to release enough memory during the GC, and then after
  that (but within the same GC run) allocate a megablock group of more
  than one megablock. This seems unlikely, as large objects are not
  copied during GC, and so we shouldn't need such large allocations
  during a GC run.
- Allocations of megablock groups of more than one megablock are rare.
  They only happen when a single heap object is large enough to require
  that amount of space. Any allocation areas that are supposed to hold
  more than one heap object cannot use megablock groups, because only
  the first megablock of a megablock group has valid `bdescr`s. Thus,
  heap object can only start in the first megablock of a group, not in
  later ones.

- - - - -
5de6be0c by Fabian Thorand at 2022-04-27T10:03:03-04:00
Add note about inefficiency in returnMemoryToOS

- - - - -
8bef471a by sheaf at 2022-04-27T10:03:43-04:00
Ensure that Any is Boxed in FFI imports/exports

We should only accept the type `Any` in foreign import/export
declarations when it has type `Type` or `UnliftedType`.
This patch adds a kind check, and a special error message triggered by
occurrences of `Any` in foreign import/export declarations at other
kinds.

Fixes #21305

- - - - -
ba3d4e1c by Ben Gamari at 2022-04-27T10:04:19-04:00
Basic response file support

Here we introduce support into our command-line parsing infrastructure
and driver for handling gnu-style response file arguments,
typically used to work around platform command-line length limitations.

Fixes #16476.

- - - - -
3b6061be by Ben Gamari at 2022-04-27T10:04:19-04:00
testsuite: Add test for #16476

- - - - -
75bf1337 by Matthew Pickering at 2022-04-27T10:04:55-04:00
ci: Fix cabal-reinstall job

It's quite nice we can do this by mostly deleting code

Fixes #21373

- - - - -
2c00d904 by Matthew Pickering at 2022-04-27T10:04:55-04:00
ci: Add test to check that release jobs have profiled libs

- - - - -
50d78d3b by Matthew Pickering at 2022-04-27T10:04:55-04:00
ci: Explicitly handle failures in test_hadrian

We also disable the stage1 testing which is broken.

Related to #21072

- - - - -
2dcdf091 by Matthew Pickering at 2022-04-27T10:04:55-04:00
ci: Fix shell command

- - - - -
55c84123 by Matthew Pickering at 2022-04-27T10:04:55-04:00
bootstrap: Add bootstrapping files for ghc-9_2_2

Fixes #21373

- - - - -
c7ee0be6 by Matthew Pickering at 2022-04-27T10:04:55-04:00
ci: Add linting job which checks authors are not GHC CI

- - - - -
23aad124 by Adam Sandberg Ericsson at 2022-04-27T10:05:31-04:00
rts: state explicitly what evacuate and scavange mean in the copying gc

- - - - -
318e0005 by Ben Gamari at 2022-04-27T10:06:07-04:00
rts/eventlog: Don't attempt to flush if there is no writer

If the user has not configured a writer then there is nothing to flush.

- - - - -
ee11d043 by Ben Gamari at 2022-04-27T10:06:07-04:00
Enable eventlog support in all ways by default

Here we deprecate the eventlogging RTS ways and instead enable eventlog
support in the remaining ways. This simplifies packaging and reduces GHC
compilation times (as we can eliminate two whole compilations of the RTS)
while simplifying the end-user story. The trade-off is a small increase
in binary sizes in the case that the user does not want eventlogging
support, but we think that this is a fine trade-off.

This also revealed a latent RTS bug: some files which included `Cmm.h`
also assumed that it defined various macros which were in fact defined
by `Config.h`, which `Cmm.h` did not include. Fixing this in turn
revealed that `StgMiscClosures.cmm` failed to import various spinlock
statistics counters, as evidenced by the failed unregisterised build.

Closes #18948.

- - - - -
a2e5ab70 by Andreas Klebinger at 2022-04-27T10:06:43-04:00
Change `-dsuppress-ticks` to only suppress non-code ticks.

This means cost centres and coverage ticks will still be present in
output. Makes using -dsuppress-all more convenient when looking at
profiled builds.

- - - - -
ec9d7e04 by Ben Gamari at 2022-04-27T10:07:21-04:00
Bump text submodule.

This should fix #21352

- - - - -
c3105be4 by Bodigrim at 2022-04-27T10:08:01-04:00
Documentation for setLocaleEncoding

- - - - -
7f618fd3 by sheaf at 2022-04-27T10:08:40-04:00
Update docs for change to type-checking plugins

There was no mention of the changes to type-checking plugins
in the 9.4.1 notes, and the extending_ghc documentation contained
a reference to an outdated type.

- - - - -
4419dd3a by Adam Sandberg Ericsson at 2022-04-27T10:09:18-04:00
rts: add some more documentation to StgWeak closure type

- - - - -
5a7f0dee by Matthew Pickering at 2022-04-27T10:09:54-04:00
Give Cmm files fake ModuleNames which include full filepath

This fixes the initialisation functions when using -prof or
-finfo-table-map.

Fixes #21370

- - - - -
81cf52bb by sheaf at 2022-04-27T10:10:33-04:00
Mark GHC.Prim.PtrEq as Unsafe

This module exports unsafe pointer equality operations,
so we accordingly mark it as Unsafe.

Fixes #21433

- - - - -
f6a8185d by Ben Gamari at 2022-04-28T09:10:31+00:00
testsuite: Add performance test for #14766

This distills the essence of the Sigs.hs program found in the ticket.

- - - - -
c7a3dc29 by Douglas Wilson at 2022-04-28T18:54:44-04:00
hadrian: Add Monoid instance to Way

- - - - -
654bafea by Douglas Wilson at 2022-04-28T18:54:44-04:00
hadrian: Enrich flavours to build profiled/debugged/threaded ghcs per stage

- - - - -
4ad559c8 by Douglas Wilson at 2022-04-28T18:54:44-04:00
hadrian: add debug_ghc and debug_stage1_ghc flavour transformers

- - - - -
f9728fdb by Douglas Wilson at 2022-04-28T18:54:44-04:00
hadrian: Don't pass -rtsopts when building libraries

- - - - -
769279e6 by Matthew Pickering at 2022-04-28T18:54:44-04:00
testsuite: Fix calculation about whether to pass -dynamic to compiler

- - - - -
da8ae7f2 by Ben Gamari at 2022-04-28T18:55:20-04:00
hadrian: Clean up flavour transformer definitions

Previously the `ipe` and `omit_pragmas` transformers were hackily
defined using the textual key-value syntax. Fix this.

- - - - -
61305184 by Ben Gamari at 2022-04-28T18:55:56-04:00
Bump process submodule

- - - - -
a8c99391 by sheaf at 2022-04-28T18:56:37-04:00
Fix unification of ConcreteTvs, removing IsRefl#

This patch fixes the unification of concrete type variables.
The subtlety was that unifying concrete metavariables is more subtle
than other metavariables, as decomposition is possible. See the Note
[Unifying concrete metavariables], which explains how we unify a
concrete type variable with a type 'ty' by concretising 'ty', using
the function 'GHC.Tc.Utils.Concrete.concretise'.

This can be used to perform an eager syntactic check for concreteness,
allowing us to remove the IsRefl# special predicate. Instead of emitting
two constraints `rr ~# concrete_tv` and `IsRefl# rr concrete_tv`, we
instead concretise 'rr'. If this succeeds we can fill 'concrete_tv',
and otherwise we directly emit an error message to the typechecker
environment instead of deferring. We still need the error message
to be passed on (instead of directly thrown), as we might benefit from
further unification in which case we will need to zonk the stored types.
To achieve this, we change the 'wc_holes' field of 'WantedConstraints'
to 'wc_errors', which stores general delayed errors. For the moement,
a delayed error is either a hole, or a syntactic equality error.

hasFixedRuntimeRep_MustBeRefl is now hasFixedRuntimeRep_syntactic, and
hasFixedRuntimeRep has been refactored to directly return the most
useful coercion for PHASE 2 of FixedRuntimeRep.

This patch also adds a field ir_frr to the InferResult datatype,
holding a value of type Maybe FRROrigin. When this value is not
Nothing, this means that we must fill the ir_ref field with a type
which has a fixed RuntimeRep.
When it comes time to fill such an ExpType, we ensure that the type
has a fixed RuntimeRep by performing a representation-polymorphism
check with the given FRROrigin
This is similar to what we already do to ensure we fill an Infer
ExpType with a type of the correct TcLevel.
This allows us to properly perform representation-polymorphism checks
on 'Infer' 'ExpTypes'.

The fillInferResult function had to be moved to GHC.Tc.Utils.Unify
to avoid a cyclic import now that it calls hasFixedRuntimeRep.

This patch also changes the code in matchExpectedFunTys to make use
of the coercions, which is now possible thanks to the previous change.
This implements PHASE 2 of FixedRuntimeRep in some situations.
For example, the test cases T13105 and T17536b are now both accepted.

Fixes #21239 and #21325

-------------------------
Metric Decrease:
    T18223
    T5631
-------------------------

- - - - -
43bd897d by Simon Peyton Jones at 2022-04-28T18:57:13-04:00
Add INLINE pragmas for Enum helper methods

As #21343 showed, we need to be super-certain that the "helper
methods" for Enum instances are actually inlined or specialised.

I also tripped over this when I discovered that numericEnumFromTo
and friends had no pragmas at all, so their performance was very
fragile.  If they weren't inlined, all bets were off.  So I've added
INLINE pragmas for them too.

See new Note [Inline Enum method helpers] in GHC.Enum.

I also expanded Note [Checking for INLINE loop breakers] in
GHC.Core.Lint to explain why an INLINE function might temporarily
be a loop breaker -- this was the initial bug report in #21343.

Strangely we get a 16% runtime allocation decrease in
perf/should_run/T15185, but only on i386.  Since it moves in the right
direction I'm disinclined to investigate, so I'll accept it.

Metric Decrease:
    T15185

- - - - -
ca1434e3 by Ben Gamari at 2022-04-28T18:57:49-04:00
configure: Bump GHC version to 9.5

Bumps haddock submodule.

- - - - -
292e3971 by Teo Camarasu at 2022-04-28T18:58:28-04:00
add since annotation for GHC.Stack.CCS.whereFrom

- - - - -
905206d6 by Tamar Christina at 2022-04-28T22:19:34-04:00
winio: add support to iserv.

- - - - -
d182897e by Tamar Christina at 2022-04-28T22:19:34-04:00
Remove unused line
- - - - -
22cf4698 by Matthew Pickering at 2022-04-28T22:20:10-04:00
Revert "rts: Refactor handling of dead threads' stacks"

This reverts commit e09afbf2a998beea7783e3de5dce5dd3c6ff23db.

- - - - -
8ed57135 by Matthew Pickering at 2022-04-29T04:11:29-04:00
Provide efficient unionMG function for combining two module graphs.

This function is used by API clients (hls).

This supercedes !6922

- - - - -
0235ff02 by Ben Gamari at 2022-04-29T04:12:05-04:00
Bump bytestring submodule

Update to current `master`.

- - - - -
01988418 by Matthew Pickering at 2022-04-29T04:12:05-04:00
testsuite: Normalise package versions in UnusedPackages test

- - - - -
724d0dc0 by Matthew Pickering at 2022-04-29T08:59:42+00:00
testsuite: Deduplicate ways correctly

This was leading to a bug where we would run a profasm test twice which
led to invalid junit.xml which meant the test results database was not
being populated for the fedora33-perf job.

- - - - -
5630dde6 by Ben Gamari at 2022-04-29T13:06:20-04:00
rts: Refactor handling of dead threads' stacks

This fixes a bug that @JunmingZhao42 and I noticed while working on her
MMTK port. Specifically, in stg_stop_thread we used stg_enter_info as a
sentinel at the tail of a stack after a thread has completed. However,
stg_enter_info expects to have a two-field payload, which we do not
push. Consequently, if the GC ends up somehow the stack it will attempt
to interpret data past the end of the stack as the frame's fields,
resulting in unsound behavior.

To fix this I eliminate this hacky use of `stg_stop_thread` and instead
introduce a new stack frame type, `stg_dead_thread_info`. Not only does
this eliminate the potential for the previously mentioned memory
unsoundness but it also more clearly captures the intended structure of
the dead threads' stacks.

- - - - -
0cdef807 by parsonsmatt at 2022-04-30T16:51:12-04:00
Add a note about instance visibility across component boundaries

In principle, the *visible* instances are
* all instances defined in a prior top-level declaration group
  (see docs on `newDeclarationGroup`), or
* all instances defined in any module transitively imported by the
  module being compiled

However, actually searching all modules transitively below the one being
compiled is unreasonably expensive, so `reifyInstances` will report only the
instance for modules that GHC has had some cause to visit during this
compilation.  This is a shortcoming: `reifyInstances` might fail to report
instances for a type that is otherwise unusued, or instances defined in a
different component.  You can work around this shortcoming by explicitly importing the modules
whose instances you want to be visible. GHC issue #20529
has some discussion around this.

Fixes #20529

- - - - -
e2dd884a by Ryan Scott at 2022-04-30T16:51:47-04:00
Make mkFunCo take AnonArgFlags into account

Previously, whenever `mkFunCo` would produce reflexive coercions, it would
use `mkVisFunTy` to produce the kind of the coercion. However, `mkFunCo` is
also used to produce coercions between types of the form `ty1 => ty2` in
certain places. This has the unfortunate side effect of causing the type of
the coercion to appear as `ty1 -> ty2` in certain error messages, as spotted
in #21328.

This patch address this by changing replacing the use of `mkVisFunTy` with
`mkFunctionType` in `mkFunCo`. `mkFunctionType` checks the kind of `ty1` and
makes the function arrow `=>` instead of `->` if `ty1` has kind `Constraint`,
so this should always produce the correct `AnonArgFlag`. As a result, this
patch fixes part (2) of #21328.

This is not the only possible way to fix #21328, as the discussion on that
issue lists some possible alternatives. Ultimately, it was concluded that the
alternatives would be difficult to maintain, and since we already use
`mkFunctionType` in `coercionLKind` and `coercionRKind`, using `mkFunctionType`
in `mkFunCo` is consistent with this choice. Moreover, using `mkFunctionType`
does not regress the performance of any test case we have in GHC's test suite.

- - - - -
170da54f by Ben Gamari at 2022-04-30T16:52:27-04:00
Convert More Diagnostics (#20116)

Replaces uses of `TcRnUnknownMessage` with proper diagnostics
constructors.

- - - - -
39edc7b4 by Marius Ghita at 2022-04-30T16:53:06-04:00
Update user guide example rewrite rules formatting

Change the rewrite rule examples to include a space between the
composition of `f` and `g` in the map rewrite rule examples.

Without this change, if the user has locally enabled the extension
OverloadedRecordDot the copied example will result in a compile time
error that `g` is not a field of `f`.

```
    • Could not deduce (GHC.Records.HasField "g" (a -> b) (a1 -> b))
        arising from selecting the field ‘g’
```

- - - - -
2e951e48 by Adam Sandberg Ericsson at 2022-04-30T16:53:42-04:00
ghc-boot: export typesynonyms from GHC.Utils.Encoding

This makes the Haddocks easier to understand.

- - - - -
d8cbc77e by Adam Sandberg Ericsson at 2022-04-30T16:54:18-04:00
users guide: add categories to some flags

- - - - -
d0f14fad by Chris Martin at 2022-04-30T16:54:57-04:00
hacking guide: mention the core libraries committee

- - - - -
34b28200 by Matthew Pickering at 2022-04-30T16:55:32-04:00
Revert "Make the specialiser handle polymorphic specialisation"

This reverts commit ef0135934fe32da5b5bb730dbce74262e23e72e8.

See ticket #21229

-------------------------
Metric Decrease:
    T15164
Metric Increase:
    T13056
-------------------------

- - - - -
ee891c1e by Matthew Pickering at 2022-04-30T16:55:32-04:00
Add test for T21229

- - - - -
ab677cc8 by Matthew Pickering at 2022-04-30T16:56:08-04:00
Hadrian: Update README about the flavour/testsuite contract

There have been a number of tickets about non-tested flavours not
passing the testsuite.. this is expected and now noted in the
documentation. You use other flavours to run the testsuite at your own
risk.

Fixes #21418

- - - - -
b57b5b92 by Ben Gamari at 2022-04-30T16:56:44-04:00
rts/m32: Fix assertion failure

This fixes an assertion failure in the m32 allocator due to the
imprecisely specified preconditions of `m32_allocator_push_filled_list`.
Specifically, the caller must ensure that the page type is set to filled
prior to calling `m32_allocator_push_filled_list`.

While this issue did result in an assertion failure in the debug RTS,
the issue is in fact benign.

- - - - -
a7053a6c by sheaf at 2022-04-30T16:57:23-04:00
Testsuite driver: don't crash on empty metrics

The testsuite driver crashed when trying to display minimum/maximum
performance changes when there are no metrics (i.e. there is
no baseline available). This patch fixes that.

- - - - -
636f7c62 by Andreas Klebinger at 2022-05-01T22:21:17-04:00
StgLint: Check that functions are applied to compatible runtime reps

We use compatibleRep to compare reps, and avoid checking functions with
levity polymorphic types because of #21399.

- - - - -
60071076 by Hécate Moonlight at 2022-05-01T22:21:55-04:00
Add documentation to the ByteArray# primetype.

close #21417

- - - - -
2b2e3020 by Andreas Klebinger at 2022-05-01T22:22:31-04:00
exprIsDeadEnd: Use isDeadEndAppSig to check if a function appliction is bottoming.

We used to check the divergence and that the number of arguments > arity.
But arity zero represents unknown arity so this was subtly broken for a long time!

We would check if the saturated function diverges, and if we applied >=arity arguments.
But for unknown arity functions any number of arguments is >=idArity.

This fixes #21440.

- - - - -
4eaf0f33 by Eric Lindblad at 2022-05-01T22:23:11-04:00
typos
- - - - -
fc58df90 by Niklas Hambüchen at 2022-05-02T08:59:27+00:00
libraries/base: docs: Explain relationshipt between `finalizeForeignPtr` and `*Conc*` creation

Fixes https://gitlab.haskell.org/ghc/ghc/-/issues/21420

- - - - -
3e400f20 by Krzysztof Gogolewski at 2022-05-02T18:29:23-04:00
Remove obsolete code in CoreToStg

Note [Nullary unboxed tuple] was removed in e9e61f18a548b70693f4.
This codepath is tested by T15696_3.

- - - - -
4a780928 by Krzysztof Gogolewski at 2022-05-02T18:29:24-04:00
Fix several note references

- - - - -
15ffe2b0 by Sebastian Graf at 2022-05-03T20:11:51+02:00
Assume at least one evaluation for nested SubDemands (#21081, #21133)

See the new `Note [SubDemand denotes at least one evaluation]`.

A demand `n :* sd` on a let binder `x=e` now means

> "`x` was evaluated `n` times and in any program trace it is evaluated, `e` is
>  evaluated deeply in sub-demand `sd`."

The "any time it is evaluated" premise is what this patch adds. As a result,
we get better nested strictness. For example (T21081)
```hs
f :: (Bool, Bool) -> (Bool, Bool)
f pr = (case pr of (a,b) -> a /= b, True)
-- before: <MP(L,L)>
-- after:  <MP(SL,SL)>

g :: Int -> (Bool, Bool)
g x = let y = let z = odd x in (z,z) in f y
```
The change in demand signature "before" to "after" allows us to case-bind `z`
here.

Similarly good things happen for the `sd` in call sub-demands `Cn(sd)`, which
allows for more eta-reduction (which is only sound with `-fno-pedantic-bottoms`,
albeit).

We also fix #21085, a surprising inconsistency with `Poly` to `Call` sub-demand
expansion.

In an attempt to fix a regression caused by less inlining due to eta-reduction
in T15426, I eta-expanded the definition of `elemIndex` and `elemIndices`, thus
fixing #21345 on the go.

The main point of this patch is that it fixes #21081 and #21133.

Annoyingly, I discovered that more precise demand signatures for join points can
transform a program into a lazier program if that join point gets floated to the
top-level, see #21392. There is no simple fix at the moment, but !5349 might.
Thus, we accept a ~5% regression in `MultiLayerModulesTH_OneShot`, where #21392
bites us in `addListToUniqDSet`. T21392 reliably reproduces the issue.

Surprisingly, ghc/alloc perf on Windows improves much more than on other jobs, by
0.4% in the geometric mean and by 2% in T16875.

Metric Increase:
    MultiLayerModulesTH_OneShot
Metric Decrease:
    T16875

- - - - -
948c7e40 by Andreas Klebinger at 2022-05-04T09:57:34-04:00
CoreLint - When checking for levity polymorphism look through more ticks.

For expressions like `(scc<cc_name> primOp#) arg1` we should also look
at arg1 to determine if we call primOp# at a fixed runtime rep.

This is what corePrep already does but CoreLint didn't yet. This patch
will bring them in sync in this regard.

It also uses tickishFloatable in CorePrep instead of CorePrep having
it's own slightly differing definition of when a tick is floatable.

- - - - -
85bc73bd by Alexis King at 2022-05-04T09:58:14-04:00
genprimopcode: Support Unicode properly

- - - - -
063d485e by Alexis King at 2022-05-04T09:58:14-04:00
genprimopcode: Replace LaTeX documentation syntax with Haddock

The LaTeX documentation generator does not seem to have been used for
quite some time, so the LaTeX-to-Haddock preprocessing step has become a
pointless complication that makes documenting the contents of GHC.Prim
needlessly difficult. This commit replaces the LaTeX syntax with the
Haddock it would have been converted into, anyway, though with an
additional distinction: it uses single quotes in places to instruct
Haddock to generate hyperlinks to bindings. This improves the quality of
the generated output.

- - - - -
d61f7428 by Ben Gamari at 2022-05-04T09:58:50-04:00
rts/ghc.mk: Only build StgCRunAsm.S when it is needed

Previously the make build system unconditionally included StgCRunAsm.S
in the link, meaning that the RTS would require an execstack
unnecessarily.

Fixes #21478.

- - - - -
934a90dd by Simon Peyton Jones at 2022-05-04T16:15:34-04:00
Improve error reporting in generated code

Our error reporting in generated code (via desugaring before
typechecking) only worked when the generated code was just a simple
call. This commit makes it work in nested cases.

- - - - -
445d3657 by sheaf at 2022-05-04T16:16:12-04:00
Ensure Any is not levity-polymorphic in FFI

The previous patch forgot to account for a type such as

  Any @(TYPE (BoxedRep l))

for a quantified levity variable l.

- - - - -
ddd2591c by Ben Gamari at 2022-05-04T16:16:48-04:00
Update supported LLVM versions

Pull forward minimum version to match 9.2.

(cherry picked from commit c26faa54c5fbe902ccb74e79d87e3fa705e270d1)

- - - - -
f9698d79 by Ben Gamari at 2022-05-04T16:16:48-04:00
testsuite/T7275: Use sed -r

Darwin requires the `-r` flag to be compatible with GNU sed.

(cherry picked from commit 512338c8feec96c38ef0cf799f3a01b77c967c56)

- - - - -
8635323b by Ben Gamari at 2022-05-04T16:16:48-04:00
gitlab-ci: Use ld.lld on ARMv7/Linux

Due to #16177.

Also cleanup some code style issues.

(cherry picked from commit cc1c3861e2372f464bf9e3c9c4d4bd83f275a1a6)

- - - - -
4f6370c7 by Ben Gamari at 2022-05-04T16:16:48-04:00
gitlab-ci: Always preserve artifacts, even in failed jobs

(cherry picked from commit fd08b0c91ea3cab39184f1b1b1aafcd63ce6973f)

- - - - -
6f662754 by Ben Gamari at 2022-05-04T16:16:48-04:00
configure: Make sphinx version check more robust

It appears that the version of sphinx shipped on CentOS 7
reports a version string of `Sphinx v1...`. Accept the `v`.

(cherry picked from commit a9197a292fd4b13308dc6664c01351c7239357ed)

- - - - -
0032dc38 by Ben Gamari at 2022-05-04T16:16:48-04:00
gitlab-ci: Don't run make job in release pipelines

(cherry picked from commit 16d6a8ff011f2194485387dcca1c00f8ddcdbdeb)

- - - - -
27f9aab3 by Ben Gamari at 2022-05-04T16:16:48-04:00
gitlab/ci: Fix name of bootstrap compiler directory

Windows binary distributions built with Hadrian have a target platform
suffix in the name of their root directory. Teach `ci.sh` about this
fact.

(cherry picked from commit df5752f39671f6d04d8cd743003469ae5eb67235)

- - - - -
b528f0f6 by Krzysztof Gogolewski at 2022-05-05T09:05:43-04:00
Fix several note references, part 2

- - - - -
691aacf6 by Adam Sandberg Ericsson at 2022-05-05T09:06:19-04:00
adjustors: align comment about number of integer like arguments with implementation for Amd4+MinGW implementation

- - - - -
f050557e by Simon Jakobi at 2022-05-05T12:47:32-04:00
Remove two uses of IntMap.size

IntMap.size is O(n). The new code should be slightly more efficient.

The transformation of GHC.CmmToAsm.CFG.calcFreqs.nodeCount can be
described formally as the transformation:

    (\sum_{0}^{n-1} \sum_{0}^{k-1} i_nk) + n
    ==>
    (\sum_{0}^{n-1} 1 + \sum_{0}^{k-1} i_nk)

- - - - -
7da90ae3 by Tom Ellis at 2022-05-05T12:48:09-04:00
Explain that 'fail s' should run in the monad itself

- - - - -
610d0283 by Matthew Craven at 2022-05-05T12:48:47-04:00
Add a test for the bracketing in rules for (^)

- - - - -
016f9ca6 by Matthew Craven at 2022-05-05T12:48:47-04:00
Fix broken rules for (^) with known small powers

- - - - -
9372aaab by Matthew Craven at 2022-05-05T12:48:47-04:00
Give the two T19569 tests different names

- - - - -
61901b32 by Andreas Klebinger at 2022-05-05T12:49:23-04:00
SpecConstr: Properly create rules for call patterns representing partial applications

The main fix is that in addVoidWorkerArg we now add the argument to the front.

This fixes #21448.

-------------------------
Metric Decrease:
    T16875
-------------------------

- - - - -
71278dc7 by Teo Camarasu at 2022-05-05T12:50:03-04:00
add since annotations for instances of ByteArray

- - - - -
962ff90b by sheaf at 2022-05-05T12:50:42-04:00
Start 9.6.1-notes

Updates the documentation notes to start tracking changes for
the 9.6.1 release (instead of 9.4).

- - - - -
aacb15a3 by Matthew Pickering at 2022-05-05T20:24:01-04:00
ci: Add job to check that jobs.yaml is up-to-date

There have been quite a few situations where jobs.yaml has been out of
date. It's better to add a CI job which checks that it's right.

We don't want to use a staged pipeline because it obfuscates the
structure of the pipeline.

- - - - -
be7102e5 by Ben Gamari at 2022-05-05T20:24:37-04:00
rts: Ensure that XMM registers are preserved on Win64

Previously we only preserved the bottom 64-bits of the callee-saved
128-bit XMM registers, in violation of the Win64 calling convention.
Fix this.

Fixes #21465.

- - - - -
73b22ff1 by Ben Gamari at 2022-05-05T20:24:37-04:00
testsuite: Add test for #21465

- - - - -
e2ae9518 by Ziyang Liu at 2022-05-06T19:22:22-04:00
Allow `let` just before pure/return in ApplicativeDo

The following is currently rejected:

```haskell
-- F is an Applicative but not a Monad
x :: F (Int, Int)
x = do
  a <- pure 0
  let b = 1
  pure (a, b)
```

This has bitten me multiple times. This MR contains a simple fix:
only allow a "let only" segment to be merged with the next (and not
the previous) segment. As a result, when the last one or more
statements before pure/return are `LetStmt`s, there will be one
more segment containing only those `LetStmt`s.

Note that if the `let` statement mentions a name bound previously, then
the program is still rejected, for example

```haskell
x = do
  a <- pure 0
  let b = a + 1
  pure (a, b)
```

or the example in #18559. To support this would require a more
complex approach, but this is IME much less common than the
previous case.

- - - - -
0415449a by Matthew Pickering at 2022-05-06T19:22:58-04:00
template-haskell: Fix representation of OPAQUE pragmas

There is a mis-match between the TH representation of OPAQUE pragmas and
GHC's internal representation due to how OPAQUE pragmas disallow phase
annotations. It seemed most in keeping to just fix the wired in name
issue by adding a special case to the desugaring of INLINE pragmas
rather than making TH/GHC agree with how the representation should look.

Fixes #21463

- - - - -
4de887e2 by Simon Peyton Jones at 2022-05-06T19:23:34-04:00
Comments only: Note [AppCtxt]

- - - - -
6e69964d by Matthew Pickering at 2022-05-06T19:24:10-04:00
Fix name of windows release bindist in doc-tarball job

- - - - -
ced4689e by Matthew Pickering at 2022-05-06T19:24:46-04:00
ci: Generate source-tarball in release jobs

We need to distribute the source tarball so we should generate it in the
CI pipeline.

- - - - -
3c91de21 by Rob at 2022-05-08T13:40:53+02:00
Change Specialise to use OrdList.

Fixes #21362

Metric Decrease:
    T16875

- - - - -
67072c31 by Simon Jakobi at 2022-05-08T12:23:43-04:00
Tweak GHC.CmmToAsm.CFG.delEdge

mapAdjust is more efficient than mapAlter.

- - - - -
374554bb by Teo Camarasu at 2022-05-09T16:24:37-04:00
Respect -po when heap profiling (#21446)

- - - - -
1ea414b6 by Teo Camarasu at 2022-05-09T16:24:37-04:00
add test case for #21446

- - - - -
c7902078 by Jens Petersen at 2022-05-09T16:25:17-04:00
avoid hadrian/bindist/Makefile install_docs error when --docs=none

When docs are disabled the bindist does not have docs/ and hence docs-utils/ is not generated.
Here we just test that docs-utils exists before attempting to install prologue.txt and gen_contents_index
to avoid the error:

/usr/bin/install: cannot stat 'docs-utils/prologue.txt': No such file or directory
make: *** [Makefile:195: install_docs] Error 1

- - - - -
158bd659 by Hécate Moonlight at 2022-05-09T16:25:56-04:00
Correct base's changelog for 4.16.1.0

This commit reaffects the new Ix instances of the foreign integral
types from base 4.17 to 4.16.1.0

closes #21529

- - - - -
a4fbb589 by Sylvain Henry at 2022-05-09T16:26:36-04:00
STG: only print cost-center if asked to

- - - - -
50347ded by Gergo ERDI at 2022-05-10T11:43:33+00:00
Improve "Glomming" note

Add a paragraph that clarifies that `occurAnalysePgm` finding out-of-order
references, and thus needing to glom, is not a cause for concern when its
root cause is rewrite rules.

- - - - -
df2e3373 by Eric Lindblad at 2022-05-10T20:45:41-04:00
update INSTALL
- - - - -
dcac3833 by Matthew Pickering at 2022-05-10T20:46:16-04:00
driver: Make -no-keep-o-files -no-keep-hi-files work in --make mode

It seems like it was just an oversight to use the incorrect DynFlags
(global rather than local) when implementing these two options. Using
the local flags allows users to request these intermediate files get
cleaned up, which works fine in --make mode because

1. Interface files are stored in memory
2. Object files are only cleaned at the end of session (after link)

Fixes #21349

- - - - -
35da81f8 by Ben Gamari at 2022-05-10T20:46:52-04:00
configure: Check for ffi.h

As noted in #21485, we checked for ffi.h yet then failed to throw an
error if it is missing.

Fixes #21485.

- - - - -
bdc99cc2 by Simon Peyton Jones at 2022-05-10T20:47:28-04:00
Check for uninferrable variables in tcInferPatSynDecl

This fixes #21479

See Note [Unquantified tyvars in a pattern synonym]

While doing this, I found that some error messages pointed at the
pattern synonym /name/, rather than the /declaration/ so I widened the
SrcSpan to encompass the declaration.

- - - - -
142a73d9 by Matthew Pickering at 2022-05-10T20:48:04-04:00
hadrian: Fix split-sections transformer

The splitSections transformer has been broken since -dynamic-too support
was implemented in hadrian. This is because we actually build the
dynamic way when building the dynamic way, so the predicate would always
fail.

The fix is to just always pass `split-sections` even if it doesn't do
anything for a particular way.

Fixes #21138

- - - - -
699f5935 by Matthew Pickering at 2022-05-10T20:48:04-04:00
packaging: Build perf builds with -split-sections

In 8f71d958 the make build system was made to use split-sections on
linux systems but it appears this logic never made it to hadrian.
There is the split_sections flavour transformer but this doesn't appear
to be used for perf builds on linux.

Closes #21135

- - - - -
21feece2 by Simon Peyton Jones at 2022-05-10T20:48:39-04:00
Use the wrapper for an unlifted binding

We assumed the wrapper for an unlifted binding is the identity,
but as #21516 showed, that is no always true.

Solution is simple: use it.

- - - - -
68d1ea5f by Matthew Pickering at 2022-05-10T20:49:15-04:00
docs: Fix path to GHC API docs in index.html

In the make bindists we generate documentation in docs/ghc-<VER> but the
hadrian bindists generate docs/ghc/ so the path to the GHC API docs was
wrong in the index.html file.

Rather than make the hadrian and make bindists the same it was easier to
assume that if you're using the mkDocs script that you're using hadrian
bindists.

Fixes #21509

- - - - -
9d8f44a9 by Matthew Pickering at 2022-05-10T20:49:51-04:00
hadrian: Don't pass -j to haddock

This has high potential for oversubcribing as many haddock jobs can be
spawned in parralel which will each request the given number of
capabilities.

Once -jsem is implemented (#19416, !5176) we can expose that haddock via
haddock and use that to pass a semaphore.

Ticket #21136

- - - - -
fec3e7aa by Matthew Pickering at 2022-05-10T20:50:27-04:00
hadrian: Only copy and install libffi headers when using in-tree libffi

When passed `--use-system-libffi` then we shouldn't copy and install the
headers from the system package. Instead the headers are expected to be
available as a runtime dependency on the users system.

Fixes #21485 #21487

- - - - -
5b791ed3 by mikael at 2022-05-11T08:22:13-04:00
FIND_LLVM_PROG: Recognize llvm suffix used by FreeBSD, ie llc10.

- - - - -
8500206e by ARATA Mizuki at 2022-05-11T08:22:57-04:00
Make floating-point abs IEEE 754 compliant

The old code used by via-C backend didn't handle the sign bit of NaN.

See #21043.

- - - - -
4a4c77ed by Alan Zimmerman at 2022-05-11T08:23:33-04:00
EPA: do statement with leading semicolon has wrong anchor

The code

    do; a <- doAsync; b

Generated an incorrect Anchor for the statement list that starts after
the first semicolon.

This commit fixes it.

Closes #20256

- - - - -
e3ca8dac by Simon Peyton Jones at 2022-05-11T08:24:08-04:00
Specialiser: saturate DFuns correctly

Ticket #21489 showed that the saturation mechanism for
DFuns (see Note Specialising DFuns) should use both
UnspecType and UnspecArg.

We weren't doing that; but this MR fixes that problem.

No test case because it's hard to tickle, but it showed up in
Gergo's work with GHC-as-a-library.

- - - - -
fcc7dc4c by Ben Gamari at 2022-05-11T20:05:41-04:00
gitlab-ci: Check for dynamic msys2 dependencies

Both #20878 and #21196 were caused by unwanted dynamic dependencies
being introduced by boot libraries. Ensure that we catch this in CI by
attempting to run GHC in an environment with a minimal PATH.

- - - - -
3c998f0d by Matthew Pickering at 2022-05-11T20:06:16-04:00
Add back Debian9 CI jobs

We still build Deb9 bindists for now due to Ubuntu 18 and Linux Mint 19
not being at EOL until April 2023 and they still need tinfo5.

Fixes #21469

- - - - -
dea9a3d9 by Ben Gamari at 2022-05-11T20:06:51-04:00
rts: Drop setExecutable

Since f6e366c058b136f0789a42222b8189510a3693d1 setExecutable has been
dead code. Drop it.

- - - - -
32cdf62d by Simon Peyton Jones at 2022-05-11T20:07:27-04:00
Add a missing guard in GHC.HsToCore.Utils.is_flat_prod_pat

This missing guard gave rise to #21519.

- - - - -
2c00a8d0 by Matthew Pickering at 2022-05-11T20:08:02-04:00
Add mention of -hi to RTS --help

Fixes #21546

- - - - -
a2dcad4e by Andre Marianiello at 2022-05-12T02:15:48+00:00
Decouple dynflags in Cmm parser (related to #17957)

- - - - -
3a022baa by Andre Marianiello at 2022-05-12T02:15:48+00:00
Remove Module argument from initCmmParserConfig

- - - - -
2fc8d76b by Andre Marianiello at 2022-05-12T02:15:48+00:00
Move CmmParserConfig and PDConfig into GHC.Cmm.Parser.Config

- - - - -
b8c5ffab by Andre Marianiello at 2022-05-12T18:13:55-04:00
Decouple dynflags in GHC.Core.Opt.Arity (related to #17957)

Metric Decrease:
    T16875

- - - - -
3bf938b6 by sheaf at 2022-05-12T18:14:34-04:00
Update extending_ghc for TcPlugin changes

The documentation still mentioned Derived constraints and
an outdated datatype TcPluginResult.

- - - - -
668a9ef4 by jackohughes at 2022-05-13T12:10:34-04:00
Fix printing of brackets in multiplicities (#20315)

Change mulArrow to allow for printing of correct application precedence
where necessary and update callers of mulArrow to reflect this.

As part of this, move mulArrow from GHC/Utils/Outputtable to GHC/Iface/Type.

Fixes #20315

- - - - -
30b8b7f1 by Ben Gamari at 2022-05-13T12:11:09-04:00
rts: Add debug output on ocResolve failure

This makes it easier to see how resolution failures nest.

- - - - -
53b3fa1c by Ben Gamari at 2022-05-13T12:11:09-04:00
rts/PEi386: Fix handling of weak symbols

Previously we would flag the symbol as weak but failed
to set its address, which must be computed from an "auxiliary"
symbol entry the follows the weak symbol.

Fixes #21556.

- - - - -
5678f017 by Ben Gamari at 2022-05-13T12:11:09-04:00
testsuite: Add tests for #21556

- - - - -
49af0e52 by Ben Gamari at 2022-05-13T22:23:26-04:00
Re-export augment and build from GHC.List

Resolves https://gitlab.haskell.org/ghc/ghc/-/issues/19127

- - - - -
aed356e1 by Simon Peyton Jones at 2022-05-13T22:24:02-04:00
Comments only around HsWrapper

- - - - -
27b90409 by Ben Gamari at 2022-05-16T08:30:44-04:00
hadrian: Introduce linting flavour transformer (+lint)

The linting flavour enables -dlint uniformly across anything build by
the stage1 compiler.

-dcmm-lint is not currently enabled because it fails on i386 (see #21563)

- - - - -
3f316776 by Matthew Pickering at 2022-05-16T08:30:44-04:00
hadrian: Uniformly enable -dlint with enableLinting transformer

This fixes some bugs where

* -dcore-lint was being passed when building stage1 libraries with the
  boot compiler
* -dcore-lint was not being passed when building executables.

Fixes #20135

- - - - -
3d74cfca by Andreas Klebinger at 2022-05-16T08:31:20-04:00
Make closure macros EXTERN_INLINE to make debugging easier

Implements #21424.

The RTS macros get_itbl and friends are extremely helpful during debugging.
However only a select few of those were available in the compiled RTS as actual symbols
as the rest were INLINE macros.

This commit marks all of them as EXTERN_INLINE. This will still inline them at use sites
but allow us to use their compiled counterparts during debugging.

This allows us to use things like `p get_fun_itbl(ptr)` in the gdb shell
since `get_fun_itbl` will now be available as symbol!

- - - - -
93153aab by Matthew Pickering at 2022-05-16T08:31:55-04:00
packaging: Introduce CI job for generating hackage documentation

This adds a CI job (hackage-doc-tarball) which generates the necessary
tarballs for uploading libraries and documentation to hackage. The
release script knows to download this folder and the upload script will
also upload the release to hackage as part of the release.

The `ghc_upload_libs` script is moved from ghc-utils into .gitlab/ghc_upload_libs

There are two modes, preparation and upload.

* The `prepare` mode takes a link to a bindist and creates a folder containing the
  source and doc tarballs ready to upload to hackage.
* The `upload` mode takes the folder created by prepare and performs the upload to
  hackage.

Fixes #21493

Related to #21512

- - - - -
65d31d05 by Simon Peyton Jones at 2022-05-16T15:32:50-04:00
Add arity to the INLINE pragmas for pattern synonyms

The lack of INLNE arity was exposed by #21531.  The fix is
simple enough, if a bit clumsy.

- - - - -
43c018aa by Krzysztof Gogolewski at 2022-05-16T15:33:25-04:00
Misc cleanup

- Remove groupWithName (unused)
- Use the RuntimeRepType synonym where possible
- Replace getUniqueM + mkSysLocalOrCoVar with mkSysLocalOrCoVarM

No functional changes.

- - - - -
8dfea078 by Pavol Vargovcik at 2022-05-16T15:34:04-04:00
TcPlugin: access to irreducible givens + fix passed ev_binds_var

- - - - -
fb579e15 by Ben Gamari at 2022-05-17T00:25:02-04:00
driver: Introduce pgmcxx

Here we introduce proper support for compilation of C++ objects. This
includes:

 * logic in `configure` to detect the C++ toolchain and propagating this
   information into the `settings` file
 * logic in the driver to use the C++ toolchain when compiling C++
   sources

- - - - -
43628ed4 by Ben Gamari at 2022-05-17T00:25:02-04:00
testsuite: Build T20918 with HC, not CXX

- - - - -
0ef249aa by Ben Gamari at 2022-05-17T00:25:02-04:00
Introduce package to capture dependency on C++ stdlib

Here we introduce a new "virtual" package into the initial package
database, `system-cxx-std-lib`. This gives users a convenient, platform
agnostic way to link against C++ libraries, addressing #20010.

Fixes #20010.

- - - - -
03efe283 by Ben Gamari at 2022-05-17T00:25:02-04:00
testsuite: Add tests for system-cxx-std-lib package

Test that we can successfully link against C++ code both in GHCi and
batch compilation.

See #20010

- - - - -
5f6527e0 by nineonine at 2022-05-17T00:25:38-04:00
OverloadedRecordFields: mention parent name in 'ambiguous occurrence' error for better disambiguation (#17420)

- - - - -
eccdb208 by Simon Peyton Jones at 2022-05-17T07:16:39-04:00
Adjust flags for pprTrace

We were using defaultSDocContext for pprTrace, which suppresses
lots of useful infomation. This small MR adds

   GHC.Utils.Outputable.traceSDocContext

and uses it for pprTrace and pprTraceUserWarning.

traceSDocContext is a global, and hence not influenced by flags,
but that seems unavoidable.  But I made the sdocPprDebug bit
controlled by unsafeHasPprDebug, since we have the latter for
exactly this purpose.

Fixes #21569

- - - - -
d2284c4c by Simon Peyton Jones at 2022-05-17T07:17:15-04:00
Fix bad interaction between withDict and the Specialiser

This MR fixes a bad bug, where the withDict was inlined too
vigorously, which in turn made the type-class Specialiser generate
a bogus specialisation, because it saw the same overloaded function
applied to two /different/ dictionaries.

Solution: inline `withDict` later.  See (WD8) of Note [withDict]
in GHC.HsToCore.Expr

See #21575, which is fixed by this change.

- - - - -
70f52443 by Matthew Pickering at 2022-05-17T07:17:50-04:00
Bump time submodule to 1.12.2

This bumps the time submodule to the 1.12.2 release.

Fixes #21571

- - - - -
2343457d by Vladislav Zavialov at 2022-05-17T07:18:26-04:00
Remove unused test files (#21582)

Those files were moved to the perf/ subtree in 11c9a469, and then
accidentally reintroduced in 680ef2c8.

- - - - -
cb52b4ae by Ben Gamari at 2022-05-17T16:00:14-04:00
CafAnal: Improve code clarity

Here we implement a few measures to improve the clarity of the CAF
analysis implementation. Specifically:

* Use CafInfo instead of Bool since the former is more descriptive
* Rename CAFLabel to CAFfyLabel, since not all CAFfyLabels are in fact
  CAFs
* Add numerous comments

- - - - -
b048a9f4 by Ben Gamari at 2022-05-17T16:00:14-04:00
codeGen: Ensure that static datacon apps are included in SRTs

When generating an SRT for a recursive group, GHC.Cmm.Info.Build.oneSRT
filters out recursive references, as described in Note [recursive SRTs].
However, doing so for static functions would be unsound, for the reason
described in Note [Invalid optimisation: shortcutting].

However, the same argument applies to static data constructor
applications, as we discovered in #20959. Fix this by ensuring that
static data constructor applications are included in recursive SRTs.

The approach here is not entirely satisfactory, but it is a starting
point.

Fixes #20959.

- - - - -
0e2d16eb by Matthew Pickering at 2022-05-17T16:00:50-04:00
Add test for #21558

This is now fixed on master and 9.2 branch.

Closes #21558

- - - - -
ef3c8d9e by Sylvain Henry at 2022-05-17T20:22:02-04:00
Don't store LlvmConfig into DynFlags

LlvmConfig contains information read from llvm-passes and llvm-targets
files in GHC's top directory. Reading these files is done only when
needed (i.e. when the LLVM backend is used) and cached for the whole
compiler session. This patch changes the way this is done:

- Split LlvmConfig into LlvmConfig and LlvmConfigCache

- Store LlvmConfigCache in HscEnv instead of DynFlags: there is no
  good reason to store it in DynFlags. As it is fixed per session, we
  store it in the session state instead (HscEnv).

- Initializing LlvmConfigCache required some changes to driver functions
  such as newHscEnv. I've used the opportunity to untangle initHscEnv
  from initGhcMonad (in top-level GHC module) and to move it to
  GHC.Driver.Main, close to newHscEnv.

- I've also made `cmmPipeline` independent of HscEnv in order to remove
  the call to newHscEnv in regalloc_unit_tests.

- - - - -
828fbd8a by Andreas Klebinger at 2022-05-17T20:22:38-04:00
Give all EXTERN_INLINE closure macros prototypes

- - - - -
cfc8e2e2 by Ben Gamari at 2022-05-19T04:57:51-04:00
base: Introduce [sg]etFinalizerExceptionHandler

This introduces a global hook which is called when an exception is
thrown during finalization.

- - - - -
372cf730 by Ben Gamari at 2022-05-19T04:57:51-04:00
base: Throw exceptions raised while closing finalized Handles

Fixes #21336.

- - - - -
3dd2f944 by Ben Gamari at 2022-05-19T04:57:51-04:00
testsuite: Add tests for #21336

- - - - -
297156e0 by Matthew Pickering at 2022-05-19T04:58:27-04:00
Add release flavour and use it for the release jobs

The release flavour is essentially the same as the perf flavour
currently but also enables `-haddock`. I have hopefully updated all the
relevant places where the `-perf` flavour was hardcoded.

Fixes #21486

- - - - -
a05b6293 by Matthew Pickering at 2022-05-19T04:58:27-04:00
ci: Don't build sphinx documentation on centos

The centos docker image lacks the sphinx builder so we disable building
sphinx docs for these jobs.

Fixes #21580

- - - - -
209d7c69 by Matthew Pickering at 2022-05-19T04:58:27-04:00
ci: Use correct syntax when args list is empty

This seems to fail on the ancient version of bash present on CentOS

- - - - -
02d16334 by Matthew Pickering at 2022-05-19T04:59:03-04:00
hadrian: Don't attempt to build dynamic profiling libraries

We only support building static profiling libraries, the transformer was
requesting things like a dynamic, threaded, debug, profiling RTS, which
we have never produced nor distributed.

Fixes #21567

- - - - -
35bdab1c by Ben Gamari at 2022-05-19T04:59:39-04:00
configure: Check CC_STAGE0 for --target support

We previously only checked the stage 1/2 compiler
for --target support. We got away with this for quite a while but it
eventually caught up with us in #21579, where `bytestring`'s new NEON
implementation was unbuildable on Darwin due to Rosetta's seemingly
random logic for determining which executable image to execute. This
lead to a confusing failure to build `bytestring`'s cbits, when `clang`
tried to compile NEON builtins while targetting x86-64.

Fix this by checking CC_STAGE0 for --target support.

Fixes #21579.

- - - - -
0ccca94b by Norman Ramsey at 2022-05-20T05:32:32-04:00
add dominator analysis of `CmmGraph`

This commit adds module `GHC.Cmm.Dominators`, which provides a wrapper
around two existing algorithms in GHC: the Lengauer-Tarjan dominator
analysis from the X86 back end and the reverse postorder ordering from
the Cmm Dataflow framework.  Issue #20726 proposes that we evaluate
some alternatives for dominator analysis, but for the time being, the
best path forward is simply to use the existing analysis on
`CmmGraph`s.

This commit addresses a bullet in #21200.

- - - - -
54f0b578 by Norman Ramsey at 2022-05-20T05:32:32-04:00
add dominator-tree function

- - - - -
05ed917b by Norman Ramsey at 2022-05-20T05:32:32-04:00
add HasDebugCallStack; remove unneeded extensions

- - - - -
0b848136 by Andreas Klebinger at 2022-05-20T05:32:32-04:00
document fields of `DominatorSet`
- - - - -
8a26e8d6 by Ben Gamari at 2022-05-20T05:33:08-04:00
nonmoving: Fix documentation of GC statistics fields

These were previously incorrect.

Fixes #21553.

- - - - -
c1e24e61 by Matthew Pickering at 2022-05-20T05:33:44-04:00
Remove pprTrace from pushCoercionIntoLambda (#21555)

This firstly caused spurious output to be emitted (as evidenced by
 #21555) but even worse caused a massive coercion to be attempted to be
 printed (> 200k terms) which would invariably eats up all the memory of
 your computer.

The good news is that removing this trace allows the program to compile
to completion, the bad news is that the program exhibits a core lint
error (on 9.0.2) but not any other releases it seems.

Fixes #21577 and #21555

- - - - -
a36d12ee by Zubin Duggal at 2022-05-20T10:44:35-04:00
docs: Fix LlvmVersion in manpage (#21280)

- - - - -
36b8a57c by Matthew Pickering at 2022-05-20T10:45:10-04:00
validate: Use $make rather than make

In the validate script we are careful to use the $make variable as this
stores whether we are using gmake, make, quiet mode etc. There was just
this one place where we failed to use it.

Fixes #21598

- - - - -
4aa3c5bd by Norman Ramsey at 2022-05-21T03:11:04+00:00
Change `Backend` type and remove direct dependencies

With this change, `Backend` becomes an abstract type
(there are no more exposed value constructors).
Decisions that were formerly made by asking "is the
current back end equal to (or different from) this named value
constructor?" are now made by interrogating the back end about
its properties, which are functions exported by `GHC.Driver.Backend`.

There is a description of how to migrate code using `Backend` in the
user guide.

Clients using the GHC API can find a backdoor to access the Backend
datatype in GHC.Driver.Backend.Internal.

Bumps haddock submodule.

Fixes #20927

- - - - -
ecf5f363 by Julian Ospald at 2022-05-21T12:51:16-04:00
Respect DESTDIR in hadrian bindist Makefile, fixes #19646

- - - - -
7edd991e by Julian Ospald at 2022-05-21T12:51:16-04:00
Test DESTDIR in test_hadrian()

- - - - -
ea895b94 by Matthew Pickering at 2022-05-22T21:57:47-04:00
Consider the stage of typeable evidence when checking stage restriction

We were considering all Typeable evidence to be "BuiltinInstance"s which
meant the stage restriction was going unchecked. In-fact, typeable has
evidence and so we need to apply the stage restriction.

This is
complicated by the fact we don't generate typeable evidence and the
corresponding DFunIds until after typechecking is concluded so we
introcue a new `InstanceWhat` constructor, BuiltinTypeableInstance which
records whether the evidence is going to be local or not.

Fixes #21547

- - - - -
ffbe28e5 by Dominik Peteler at 2022-05-22T21:58:23-04:00
Modularize GHC.Core.Opt.LiberateCase

Progress towards #17957

- - - - -
bc723ac2 by Simon Peyton Jones at 2022-05-23T17:09:34+01:00
Improve FloatOut and SpecConstr

This patch addresses a relatively obscure situation that arose
when chasing perf regressions in !7847, which itself is fixing

It does two things:

* SpecConstr can specialise on ($df d1 d2) dictionary arguments
* FloatOut no longer checks argument strictness

See Note [Specialising on dictionaries] in GHC.Core.Opt.SpecConstr.

A test case is difficult to construct, but it makes a big difference
in nofib/real/eff/VSM, at least when we have the patch for #21286
installed. (The latter stops worker/wrapper for dictionary arguments).

There is a spectacular, but slightly illusory, improvement in
runtime perf on T15426.  I have documented the specifics in
T15426 itself.

Metric Decrease:
    T15426

- - - - -
1a4195b0 by John Ericson at 2022-05-23T17:33:59-04:00
Make debug a `Bool` not an `Int` in `StgToCmmConfig`

We don't need any more resolution than this.

Rename the field to `stgToCmmEmitDebugInfo` to indicate it is no longer
conveying any "level" information.

- - - - -
e9fff12b by Alan Zimmerman at 2022-05-23T21:04:49-04:00
EPA : Remove duplicate comments in DataFamInstD

The code

  data instance Method PGMigration = MigrationQuery Query
                                   -- ^ Run a query against the database
                                   | MigrationCode (Connection -> IO (Either String ()))
                                   -- ^ Run any arbitrary IO code

Resulted in two instances of the "-- ^ Run a query against the database"
comment appearing in the Exact Print Annotations when it was parsed.

Ensure only one is kept.

Closes #20239

- - - - -
e2520df3 by Alan Zimmerman at 2022-05-23T21:05:27-04:00
EPA: Comment Order Reversed

Make sure comments captured in the exact print annotations are in
order of increasing location

Closes #20718

- - - - -
4b45fd72 by Teo Camarasu at 2022-05-24T10:49:13-04:00
Add test for T21455

- - - - -
e2cd1d43 by Teo Camarasu at 2022-05-24T10:49:13-04:00
Allow passing -po outside profiling way

Resolves #21455

- - - - -
3b8c413a by Greg Steuck at 2022-05-24T10:49:52-04:00
Fix haddock_*_perf tests on non-GNU-grep systems

Using regexp pattern requires `egrep` and straight up `+`.  The
haddock_parser_perf and haddock_renamer_perf tests now pass on
OpenBSD. They previously incorrectly parsed the files and awk
complained about invalid syntax.

- - - - -
1db877a3 by Ben Gamari at 2022-05-24T10:50:28-04:00
hadrian/bindist: Drop redundant include of install.mk

`install.mk` is already included by `config.mk`. Moreover, `install.mk`
depends upon `config.mk` to set `RelocatableBuild`, making this first
include incorrect.

- - - - -
f485d267 by Greg Steuck at 2022-05-24T10:51:08-04:00
Remove -z wxneeded for OpenBSD

With all the recent W^X fixes in the loader this workaround is not
necessary any longer. I verified that the only tests failing for me on
OpenBSD 7.1-current are the same (libc++ related) before and after
this commit (with --fast).

- - - - -
7c51177d by Andreas Klebinger at 2022-05-24T22:13:19-04:00
Use UnionListsOrd instead of UnionLists in most places.

This should get rid of most, if not all "Overlong lists" errors and fix #20016

- - - - -
81b3741f by Andreas Klebinger at 2022-05-24T22:13:55-04:00
Fix #21563 by using Word64 for 64bit shift code.

We use the 64bit shifts only on 64bit platforms. But we
compile the code always so compiling it on 32bit caused a
lint error. So use Word64 instead.

- - - - -
2c25fff6 by Zubin Duggal at 2022-05-24T22:14:30-04:00
Fix compilation with -haddock on GHC <= 8.10

-haddock on GHC < 9.0 is quite fragile and can result in obtuse parse errors
when it encounters invalid haddock syntax.

This has started to affect users since 297156e0b8053a28a860e7a18e1816207a59547b
enabled -haddock by default on many flavours.

Furthermore, since we don't test bootstrapping with 8.10 on CI, this problem
managed to slip throught the cracks.

- - - - -
cfb9faff by sheaf at 2022-05-24T22:15:12-04:00
Hadrian: don't add "lib" for relocatable builds

The conditional in hadrian/bindist/Makefile depended on the target OS,
but it makes more sense to use whether we are using a relocatable build.
(Currently this only gets set to true on Windows, but this ensures
that the logic stays correctly coupled.)

- - - - -
9973c016 by Andre Marianiello at 2022-05-25T01:36:09-04:00
Remove HscEnv from GHC.HsToCore.Usage (related to #17957)

Metric Decrease:
    T16875

- - - - -
2ff18e39 by sheaf at 2022-05-25T01:36:48-04:00
SimpleOpt: beta-reduce through casts

The simple optimiser would sometimes fail to
beta-reduce a lambda when there were casts
in between the lambda and its arguments.
This can cause problems because we rely on
representation-polymorphic lambdas getting
beta-reduced away (for example, those
that arise from newtype constructors with
representation-polymorphic arguments, with
UnliftedNewtypes).

- - - - -
e74fc066 by CarrieMY at 2022-05-25T16:43:03+02:00
Desugar RecordUpd in `tcExpr`

This patch typechecks record updates by desugaring them inside
the typechecker using the HsExpansion mechanism, and then typechecking
this desugared result.

Example:

    data T p q = T1 { x :: Int, y :: Bool, z :: Char }
               | T2 { v :: Char }
               | T3 { x :: Int }
               | T4 { p :: Float, y :: Bool, x :: Int }
               | T5

The record update `e { x=e1, y=e2 }` desugars as follows

  e { x=e1, y=e2 }
    ===>
  let { x' = e1; y' = e2 } in
  case e of
     T1 _ _ z -> T1 x' y' z
     T4 p _ _ -> T4 p y' x'

The desugared expression is put into an HsExpansion, and we typecheck
that.

The full details are given in Note [Record Updates] in GHC.Tc.Gen.Expr.

Fixes #2595 #3632 #10808 #10856 #16501 #18311 #18802 #21158 #21289

Updates haddock submodule

- - - - -
2b8bdab8 by Eric Lindblad at 2022-05-26T03:21:58-04:00
update README
- - - - -
3d7e7e84 by BinderDavid at 2022-05-26T03:22:38-04:00
Replace dead link in Haddock documentation of Control.Monad.Fail (fixes #21602)

- - - - -
ee61c7f9 by John Ericson at 2022-05-26T03:23:13-04:00
Add Haddocks for `WwOpts`

- - - - -
da5ccf0e by Dominik Peteler at 2022-05-26T03:23:13-04:00
Avoid global compiler state for `GHC.Core.Opt.WorkWrap`

Progress towards #17957

- - - - -
3bd975b4 by sheaf at 2022-05-26T03:23:52-04:00
Optimiser: avoid introducing bad rep-poly

The functions `pushCoValArg` and `pushCoercionIntoLambda` could
introduce bad representation-polymorphism. Example:

  type RR :: RuntimeRep
  type family RR where { RR = IntRep }
  type F :: TYPE RR
  type family F where  { F  = Int# }

  co = GRefl F (TYPE RR[0])
    :: (F :: TYPE RR)
    ~# (F |> TYPE RR[0] :: TYPE IntRep)

  f :: F -> ()

`pushCoValArg` would transform the unproblematic application

  (f |> (co -> <()>)) (arg :: F |> TYPE RR[0])

into an application in which the argument does not have a fixed
`RuntimeRep`:

  f ((arg |> sym co) :: (F :: TYPE RR))

- - - - -
b22979fb by Fraser Tweedale at 2022-05-26T06:14:51-04:00
executablePath test: fix file extension treatment

The executablePath test strips the file extension (if any) when
comparing the query result with the expected value.  This is to
handle platforms where GHC adds a file extension to the output
program file (e.g. .exe on Windows).

After the initial check, the file gets deleted (if supported).
However, it tries to delete the *stripped* filename, which is
incorrect.  The test currently passes only because Windows does not
allow deleting the program while any process created from it is
alive.

Make the test program correct in general by deleting the
*non-stripped* executable filename.

- - - - -
afde4276 by Fraser Tweedale at 2022-05-26T06:14:51-04:00
fix executablePath test for NetBSD

executablePath support for NetBSD was added in
a172be07e3dce758a2325104a3a37fc8b1d20c9c, but the test was not
updated.

Update the test so that it works for NetBSD.  This requires handling
some quirks:

- The result of getExecutablePath could include "./" segments.
  Therefore use System.FilePath.equalFilePath to compare paths.

- The sysctl(2) call returns the original executable name even after
  it was deleted.  Add `canQueryAfterDelete :: [FilePath]` and
  adjust expectations for the post-delete query accordingly.

Also add a note to the `executablePath` haddock to advise that
NetBSD behaves differently from other OSes when the file has been
deleted.

Also accept a decrease in memory usage for T16875.  On Windows, the
metric is -2.2% of baseline, just outside the allowed ±2%.  I don't
see how this commit could have influenced this metric, so I suppose
it's something in the CI environment.

Metric Decrease:
    T16875

- - - - -
d0e4355a by John Ericson at 2022-05-26T06:15:30-04:00
Factor out `initArityOps` to `GHC.Driver.Config.*` module

We want `DynFlags` only mentioned in `GHC.Driver`.

- - - - -
44bb7111 by romes at 2022-05-26T16:27:57+00:00
TTG: Move MatchGroup Origin field and MatchGroupTc to GHC.Hs

- - - - -
88e58600 by sheaf at 2022-05-26T17:38:43-04:00
Add tests for eta-expansion of data constructors

This patch adds several tests relating to the eta-expansion of
data constructors, including UnliftedNewtypes and DataTypeContexts.

- - - - -
d87530bb by Richard Eisenberg at 2022-05-26T23:20:14-04:00
Generalize breakTyVarCycle to work with TyFamLHS

The function breakTyVarCycle_maybe has been installed
in a dark corner of GHC to catch some gremlins (a.k.a.
occurs-check failures) who lurk
there. But it previously only caught gremlins of the
form (a ~ ... F a ...), where some of our intrepid users
have spawned gremlins of the form (G a ~ ... F (G a) ...).
This commit improves breakTyVarCycle_maybe (and renames
it to breakTyEqCycle_maybe) to catch the new gremlins.

Happily, the change is remarkably small.

The gory details are in Note [Type equality cycles].

Test cases: typecheck/should_compile/{T21515,T21473}.

- - - - -
ed37027f by Hécate Moonlight at 2022-05-26T23:20:52-04:00
[base] Fix the links in the Data.Data module

fix #21658
fix #21657
fix #21657

- - - - -
3bd7d5d6 by Krzysztof Gogolewski at 2022-05-27T16:44:48+02:00
Use a class to check validity of withDict

This moves handling of the magic 'withDict' function from the desugarer
to the typechecker. Details in Note [withDict].

I've extracted a part of T16646Fail to a separate file T16646Fail2,
because the new error in 'reify' hides the errors from 'f' and 'g'.

WithDict now works with casts, this fixes #21328.

Part of #19915

- - - - -
b54f6c4f by sheaf at 2022-05-28T21:00:09-04:00
Fix FreeVars computation for mdo

Commit acb188e0 introduced a regression in the computation of free
variables in mdo statements, as the logic in
GHC.Rename.Expr.segmentRecStmts was slightly different depending on
whether the recursive do block corresponded to an mdo statement or
a rec statment.

This patch restores the previous computation for mdo blocks.

Fixes #21654

- - - - -
0704295c by Matthew Pickering at 2022-05-28T21:00:45-04:00
T16875: Stabilise (temporarily) by increasing acceptance threshold

The theory is that on windows there is some difference in the
environment between pipelines on master and merge requests which affects
all tests equally but because T16875 barely allocates anything it is the
test which is affected the most.

See #21557

- - - - -
6341c8ed by Matthew Pickering at 2022-05-28T21:01:20-04:00
make: Fix make maintainer-clean deleting a file tracked by source control

Fixes #21659

- - - - -
fbf2f254 by Bodigrim at 2022-05-28T21:01:58-04:00
Expand documentation of hIsTerminalDevice

- - - - -
0092c67c by Teo Camarasu at 2022-05-29T12:25:39+00:00
export IsList from GHC.IsList

it is still re-exported from GHC.Exts

- - - - -
91396327 by Sylvain Henry at 2022-05-30T09:40:55-04:00
MachO linker: fix handling of ARM64_RELOC_SUBTRACTOR

ARM64_RELOC_SUBTRACTOR relocations are paired with an
AMR64_RELOC_UNSIGNED relocation to implement: addend + sym1 - sym2
The linker was doing it in two steps, basically:
  *addend <- *addend - sym2
  *addend <- *addend + sym1
The first operation was likely to overflow. For example when the
relocation target was 32-bit and both sym1/sym2 were 64-bit addresses.
With the small memory model, (sym1-sym2) would fit in 32 bits but
(*addend-sym2) may not.

Now the linker does it in one step:
  *addend <- *addend + sym1 - sym2

- - - - -
acc26806 by Sylvain Henry at 2022-05-30T09:40:55-04:00
Some fixes to SRT documentation

- reordered the 3 SRT implementation cases from the most general to the
  most specific one:
    USE_SRT_POINTER -> USE_SRT_OFFSET -> USE_INLINE_SRT_FIELD
- added requirements for each
- found and documented a confusion about "SRT inlining" not supported
  with MachO. (It is fixed in the following commit)

- - - - -
5878f439 by Sylvain Henry at 2022-05-30T09:40:55-04:00
Enable USE_INLINE_SRT_FIELD on ARM64

It was previously disabled because of:
- a confusion about "SRT inlining" (see removed comment in this commit)
- a linker bug (overflow) in the handling of ARM64_RELOC_SUBTRACTOR
  relocation: fixed by a previous commit.

- - - - -
59bd6159 by Matthew Pickering at 2022-05-30T09:41:39-04:00
ci: Make sure to exit promptly if `make install` fails.

Due to the vageries of bash, you have to explicitly handle the failure
and exit when in a function.

This failed to exit promptly when !8247 was failing.

See #21358 for the general issue

- - - - -
5a5a28da by Sylvain Henry at 2022-05-30T09:42:23-04:00
Split GHC.HsToCore.Foreign.Decl

This is preliminary work for JavaScript support. It's better to put the
code handling the desugaring of Prim, C and JavaScript declarations into
separate modules.

- - - - -
6f5ff4fa by Sylvain Henry at 2022-05-30T09:43:05-04:00
Bump hadrian to LTS-19.8 (GHC 9.0.2)

- - - - -
f2e70707 by Sylvain Henry at 2022-05-30T09:43:05-04:00
Hadrian: remove unused code

- - - - -
2f215b9f by Simon Peyton Jones at 2022-05-30T13:44:14-04:00
Eta reduction with casted function

We want to be able to eta-reduce
   \x y. ((f x) |> co) y
by pushing 'co' inwards.  A very small change accommodates this
See Note [Eta reduction with casted function]

- - - - -
f4f6a87a by Simon Peyton Jones at 2022-05-30T13:44:14-04:00
Do arity trimming at bindings, rather than in exprArity

Sometimes there are very large casts, and coercionRKind
can be slow.

- - - - -
610a2b83 by Simon Peyton Jones at 2022-05-30T13:44:14-04:00
Make findRhsArity take RecFlag

This avoids a fixpoint iteration for the common case of
non-recursive bindings.

- - - - -
80ba50c7 by Simon Peyton Jones at 2022-05-30T13:44:14-04:00
Comments and white space

- - - - -
0079171b by Simon Peyton Jones at 2022-05-30T13:44:14-04:00
Make PrimOpId record levity

This patch concerns #20155, part (1)

The general idea is that since primops have curried bindings
(currently in PrimOpWrappers.hs) we don't need to eta-expand
them.  But we /do/ need to eta-expand the levity-polymorphic ones,
because they /don't/ have bindings.

This patch makes a start in that direction, by identifying the
levity-polymophic primops in the PrimOpId IdDetails constructor.

For the moment, I'm still eta-expanding all primops (by saying
that hasNoBinding returns True for all primops), because of the
bug reported in #20155.  But I hope that before long we can
tidy that up too, and remove the TEMPORARILY stuff in hasNoBinding.

- - - - -
6656f016 by Simon Peyton Jones at 2022-05-30T13:44:14-04:00
A bunch of changes related to eta reduction

This is a large collection of changes all relating to eta
reduction, originally triggered by #18993, but there followed
a long saga.

Specifics:

* Move state-hack stuff from GHC.Types.Id (where it never belonged)
  to GHC.Core.Opt.Arity (which seems much more appropriate).

* Add a crucial mkCast in the Cast case of
  GHC.Core.Opt.Arity.eta_expand; helps with T18223

* Add clarifying notes about eta-reducing to PAPs.
  See Note [Do not eta reduce PAPs]

* I moved tryEtaReduce from GHC.Core.Utils to GHC.Core.Opt.Arity,
  where it properly belongs.  See Note [Eta reduce PAPs]

* In GHC.Core.Opt.Simplify.Utils.tryEtaExpandRhs, pull out the code for
  when eta-expansion is wanted, to make wantEtaExpansion, and all that
  same function in GHC.Core.Opt.Simplify.simplStableUnfolding.  It was
  previously inconsistent, but it's doing the same thing.

* I did a substantial refactor of ArityType; see Note [ArityType].
  This allowed me to do away with the somewhat mysterious takeOneShots;
  more generally it allows arityType to describe the function, leaving
  its clients to decide how to use that information.

  I made ArityType abstract, so that clients have to use functions
  to access it.

* Make GHC.Core.Opt.Simplify.Utils.rebuildLam (was stupidly called
  mkLam before) aware of the floats that the simplifier builds up, so
  that it can still do eta-reduction even if there are some floats.
  (Previously that would not happen.)  That means passing the floats
  to rebuildLam, and an extra check when eta-reducting (etaFloatOk).

* In GHC.Core.Opt.Simplify.Utils.tryEtaExpandRhs, make use of call-info
  in the idDemandInfo of the binder, as well as the CallArity info. The
  occurrence analyser did this but we were failing to take advantage here.

  In the end I moved the heavy lifting to GHC.Core.Opt.Arity.findRhsArity;
  see Note [Combining arityType with demand info], and functions
  idDemandOneShots and combineWithDemandOneShots.

  (These changes partly drove my refactoring of ArityType.)

* In GHC.Core.Opt.Arity.findRhsArity
  * I'm now taking account of the demand on the binder to give
    extra one-shot info.  E.g. if the fn is always called with two
    args, we can give better one-shot info on the binders
    than if we just look at the RHS.

  * Don't do any fixpointing in the non-recursive
    case -- simple short cut.

  * Trim arity inside the loop. See Note [Trim arity inside the loop]

* Make SimpleOpt respect the eta-reduction flag
  (Some associated refactoring here.)

* I made the CallCtxt which the Simplifier uses distinguish between
  recursive and non-recursive right-hand sides.
     data CallCtxt = ... | RhsCtxt RecFlag | ...
  It affects only one thing:
     - We call an RHS context interesting only if it is non-recursive
       see Note [RHS of lets] in GHC.Core.Unfold

* Remove eta-reduction in GHC.CoreToStg.Prep, a welcome simplification.
  See Note [No eta reduction needed in rhsToBody] in GHC.CoreToStg.Prep.

Other incidental changes

* Fix a fairly long-standing outright bug in the ApplyToVal case of
  GHC.Core.Opt.Simplify.mkDupableContWithDmds. I was failing to take the
  tail of 'dmds' in the recursive call, which meant the demands were All
  Wrong.  I have no idea why this has not caused problems before now.

* Delete dead function GHC.Core.Opt.Simplify.Utils.contIsRhsOrArg

Metrics: compile_time/bytes allocated
                               Test    Metric       Baseline      New value Change
---------------------------------------------------------------------------------------
MultiLayerModulesTH_OneShot(normal) ghc/alloc  2,743,297,692  2,619,762,992  -4.5% GOOD
                     T18223(normal) ghc/alloc  1,103,161,360    972,415,992 -11.9% GOOD
                      T3064(normal) ghc/alloc    201,222,500    184,085,360  -8.5% GOOD
                      T8095(normal) ghc/alloc  3,216,292,528  3,254,416,960  +1.2%
                      T9630(normal) ghc/alloc  1,514,131,032  1,557,719,312  +2.9%  BAD
                 parsing001(normal) ghc/alloc    530,409,812    525,077,696  -1.0%

geo. mean                                 -0.1%

Nofib:
       Program           Size    Allocs   Runtime   Elapsed  TotalMem
--------------------------------------------------------------------------------
         banner          +0.0%     +0.4%     -8.9%     -8.7%      0.0%
    exact-reals          +0.0%     -7.4%    -36.3%    -37.4%      0.0%
 fannkuch-redux          +0.0%     -0.1%     -1.0%     -1.0%      0.0%
           fft2          -0.1%     -0.2%    -17.8%    -19.2%      0.0%
          fluid          +0.0%     -1.3%     -2.1%     -2.1%      0.0%
             gg          -0.0%     +2.2%     -0.2%     -0.1%      0.0%
  spectral-norm          +0.1%     -0.2%      0.0%      0.0%      0.0%
            tak          +0.0%     -0.3%     -9.8%     -9.8%      0.0%
           x2n1          +0.0%     -0.2%     -3.2%     -3.2%      0.0%
--------------------------------------------------------------------------------
            Min          -3.5%     -7.4%    -58.7%    -59.9%      0.0%
            Max          +0.1%     +2.2%    +32.9%    +32.9%      0.0%
 Geometric Mean          -0.0%     -0.1%    -14.2%    -14.8%     -0.0%

Metric Decrease:
    MultiLayerModulesTH_OneShot
    T18223
    T3064
    T15185
    T14766
Metric Increase:
    T9630

- - - - -
cac8c7bb by Matthew Pickering at 2022-05-30T13:44:50-04:00
hadrian: Fix building from source-dist without alex/happy

This fixes two bugs which were adding dependencies on alex/happy when
building from a source dist.

* When we try to pass `--with-alex` and `--with-happy` to cabal when
  configuring but the builders are not set. This is fixed by making them
  optional.
* When we configure, cabal requires alex/happy because of the
  build-tool-depends fields. These are now made optional with a cabal
  flag (build-tool-depends) for compiler/hpc-bin/genprimopcode.

Fixes #21627

- - - - -
a96dccfe by Matthew Pickering at 2022-05-30T13:44:50-04:00
ci: Test the bootstrap without ALEX/HAPPY on path

- - - - -
0e5bb3a8 by Matthew Pickering at 2022-05-30T13:44:50-04:00
ci: Test bootstrapping in release jobs

- - - - -
d8901469 by Matthew Pickering at 2022-05-30T13:44:50-04:00
ci: Allow testing bootstrapping on MRs using the "test-bootstrap" label

- - - - -
18326ad2 by Matthew Pickering at 2022-05-30T13:45:25-04:00
rts: Remove explicit timescale for deprecating -h flag

We originally planned to remove the flag in 9.4 but there's actually no
great rush to do so and it's probably less confusing (forever) to keep
the message around suggesting an explicit profiling option.

Fixes #21545

- - - - -
eaaa1389 by Matthew Pickering at 2022-05-30T13:46:01-04:00
Enable -dlint in hadrian lint transformer

Now #21563 is fixed we can properly enable `-dlint` in CI rather than a
subset of the flags.

- - - - -
0544f114 by Ben Gamari at 2022-05-30T19:16:55-04:00
upload-ghc-libs: Allow candidate-only upload

- - - - -
83467435 by Sylvain Henry at 2022-05-30T19:17:35-04:00
Avoid using DynFlags in GHC.Linker.Unit (#17957)

- - - - -
5c4421b1 by Matthew Pickering at 2022-05-31T08:35:17-04:00
hadrian: Introduce new package database for executables needed to build stage0

These executables (such as hsc2hs) are built using the boot compiler and
crucially, most libraries from the global package database.

We also move other build-time executables to be built in this stage such
as linters which also cleans up which libraries end up in the global
package database. This allows us to remove hacks where linters-common is
removed from the package database when a bindist is created.

This fixes issues caused by infinite recursion due to bytestring adding
a dependency on template-haskell.

Fixes #21634

- - - - -
0dafd3e7 by Matthew Pickering at 2022-05-31T08:35:17-04:00
Build stage1 with -V as well

This helps tracing errors which happen when building stage1

- - - - -
15d42a7a by Matthew Pickering at 2022-05-31T08:35:52-04:00
Revert "packaging: Build perf builds with -split-sections"

This reverts commit 699f593532a3cd5ca1c2fab6e6e4ce9d53be2c1f.

Split sections causes segfaults in profiling way with old toolchains
(deb9) and on windows (#21670)

Fixes #21670

- - - - -
d4c71f09 by John Ericson at 2022-05-31T16:26:28+00:00
Purge `DynFlags` and `HscEnv` from some `GHC.Core` modules where it's not too hard

Progress towards #17957

Because of `CoreM`, I did not move the `DynFlags` and `HscEnv` to other
modules as thoroughly as I usually do. This does mean that risk of
`DynFlags` "creeping back in" is higher than it usually is.

After we do the same process to the other Core passes, and then figure
out what we want to do about `CoreM`, we can finish the job started
here.

That is a good deal more work, however, so it certainly makes sense to
land this now.

- - - - -
a720322f by romes at 2022-06-01T07:44:44-04:00
Restore Note [Quasi-quote overview]

- - - - -
392ce3fc by romes at 2022-06-01T07:44:44-04:00
Move UntypedSpliceFlavour from L.H.S to GHC.Hs

UntypedSpliceFlavour was only used in the client-specific `GHC.Hs.Expr`
but was defined in the client-independent L.H.S.Expr.

- - - - -
7975202b by romes at 2022-06-01T07:44:44-04:00
TTG: Rework and improve splices

This commit redefines the structure of Splices in the AST.

We get rid of `HsSplice` which used to represent typed and untyped
splices, quasi quotes, and the result of splicing either an expression,
a type or a pattern.

Instead we have `HsUntypedSplice` which models an untyped splice or a
quasi quoter, which works in practice just like untyped splices.

The `HsExpr` constructor `HsSpliceE` which used to be constructed with
an `HsSplice` is split into `HsTypedSplice` and `HsUntypedSplice`. The
former is directly constructed with an `HsExpr` and the latter now takes
an `HsUntypedSplice`.

Both `HsType` and `Pat` constructors `HsSpliceTy` and `SplicePat` now
take an `HsUntypedSplice` instead of a `HsSplice` (remember only
/untyped splices/ can be spliced as types or patterns).

The result of splicing an expression, type, or pattern is now
comfortably stored in the extension fields `XSpliceTy`, `XSplicePat`,
`XUntypedSplice` as, respectively, `HsUntypedSpliceResult (HsType
GhcRn)`, `HsUntypedSpliceResult (Pat GhcRn)`, and `HsUntypedSpliceResult
(HsExpr GhcRn)`

Overall the TTG extension points are now better used to
make invalid states unrepresentable and model the progression between
stages better.

See Note [Lifecycle of an untyped splice, and PendingRnSplice]
and Note [Lifecycle of an typed splice, and PendingTcSplice] for more
details.

Updates haddock submodule

Fixes #21263

-------------------------
Metric Decrease:
    hard_hole_fits
-------------------------

- - - - -
320270c2 by Matthew Pickering at 2022-06-01T07:44:44-04:00
Add test for #21619

Fixes #21619

- - - - -
ef7ddd73 by Pierre Le Marre at 2022-06-01T07:44:47-04:00
Pure Haskell implementation of GHC.Unicode

Switch to a pure Haskell implementation of base:GHC.Unicode, based on the implementation of the package unicode-data (https://github.com/composewell/unicode-data/).

Approved by CLC as per https://github.com/haskell/core-libraries-committee/issues/59#issuecomment-1132106691.

- Remove current Unicode cbits.
- Add generator for Unicode property files from Unicode Character Database.
- Generate internal modules.
- Update GHC.Unicode.
- Add unicode003 test for general categories and case mappings.
- Add Python scripts to check 'base' Unicode tests outputs and characters properties.

Fixes #21375

-------------------------
Metric Decrease:
    T16875
Metric Increase:
    T4029
    T18304
    haddock.base
-------------------------

- - - - -
514a6a28 by Eric Lindblad at 2022-06-01T07:44:51-04:00
typos

- - - - -
9004be3c by Matthew Pickering at 2022-06-01T07:44:52-04:00
source-dist: Copy in files created by ./boot

Since we started producing source dists with hadrian we stopped copying
in the files created by ./boot which adds a dependency on python3 and
autoreconf. This adds back in the files which were created by running
configure.

Fixes #21673 #21672 and #21626

- - - - -
a12a3cab by Matthew Pickering at 2022-06-01T07:44:52-04:00
ci: Don't try to run ./boot when testing bootstrap of source dist

- - - - -
e07f9059 by Shlomo Shuck at 2022-06-01T07:44:55-04:00
Language.Haskell.Syntax: Fix docs for PromotedConsT etc.

Fixes ghc/ghc#21675.

- - - - -
87295e6d by Ben Gamari at 2022-06-01T07:44:56-04:00
Bump bytestring, process, and text submodules

Metric Decrease:
    T5631
Metric Increase:
    T18223

(cherry picked from commit 55fcee30cb3281a66f792e8673967d64619643af)

- - - - -
24b5bb61 by Ben Gamari at 2022-06-01T07:44:56-04:00
Bump Cabal submodule

To current `master`.

(cherry picked from commit fbb59c212415188486aafd970eafef170516356a)

- - - - -
5433a35e by Matthew Pickering at 2022-06-01T22:26:30-04:00
hadrian/tool-args: Write output to intermediate file rather than via stdout

This allows us to see the output of hadrian while it is doing the setup.

- - - - -
468f919b by Matthew Pickering at 2022-06-01T22:27:10-04:00
Make -fcompact-unwind the default

This is a follow-up to !7247 (closed) making the inclusion of compact unwinding
sections the default.

Also a slight refactoring/simplification of the flag handling to add
-fno-compact-unwind.

- - - - -
819fdc61 by Zubin Duggal at 2022-06-01T22:27:47-04:00
hadrian bootstrap: add plans for 9.0.2 and 9.2.3

- - - - -
9fa790b4 by Zubin Duggal at 2022-06-01T22:27:47-04:00
ci: Add matrix for bootstrap sources

- - - - -
ce9f986b by John Ericson at 2022-06-02T15:42:59+00:00
HsToCore.Coverage: Improve haddocks

- - - - -
f065804e by John Ericson at 2022-06-02T15:42:59+00:00
Hoist auto `mkModBreaks` and `writeMixEntries` conditions to caller

No need to inline traversing a maybe for `mkModBreaks`. And better to
make each function do one thing and let the caller deside when than
scatter the decision making and make the caller seem more imperative.

- - - - -
d550d907 by John Ericson at 2022-06-02T15:42:59+00:00
Rename `HsToCore.{Coverage -> Ticks}`

The old name made it confusing why disabling HPC didn't disable the
entire pass. The name makes it clear --- there are other reasons to add
ticks in addition.

- - - - -
6520da95 by John Ericson at 2022-06-02T15:42:59+00:00
Split out `GHC.HsToCore.{Breakpoints,Coverage}` and use `SizedSeq`

As proposed in
https://gitlab.haskell.org/ghc/ghc/-/merge_requests/7508#note_432877 and
https://gitlab.haskell.org/ghc/ghc/-/merge_requests/7508#note_434676,
`GHC.HsToCore.Ticks` is about ticks, breakpoints are separate and
backend-specific (only for the bytecode interpreter), and mix entry
writing is just for HPC.

With this split we separate out those interpreter- and HPC-specific
its, and keep the main `GHC.HsToCore.Ticks` agnostic.

Also, instead of passing the reversed list and count around, we use
`SizedSeq` which abstracts over the algorithm. This is much nicer to
avoid noise and prevents bugs.

(The bugs are not just hypothetical! I missed up the reverses on an
earlier draft of this commit.)

- - - - -
1838c3d8 by Sylvain Henry at 2022-06-02T15:43:14+00:00
GHC.HsToCore.Breakpoints: Slightly improve perf

We have the length already, so we might as well use that rather than
O(n) recomputing it.

- - - - -
5a3fdcfd by John Ericson at 2022-06-02T15:43:59+00:00
HsToCore.Coverage: Purge DynFlags

Finishes what !7467 (closed) started.

Progress towards #17957

- - - - -
9ce9ea50 by HaskellMouse at 2022-06-06T09:50:00-04:00
Deprecate TypeInType extension

This commit fixes #20312
It deprecates "TypeInType" extension
according to the following proposal:
https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0083-no-type-in-type.rst

It has been already implemented.

The migration strategy:
 1. Disable TypeInType
 2. Enable both DataKinds and PolyKinds extensions

Metric Decrease:
    T16875

- - - - -
f2e037fd by Aaron Allen at 2022-06-06T09:50:39-04:00
Diagnostics conversions, part 6 (#20116)

Replaces uses of `TcRnUnknownMessage` with proper diagnostics
constructors in `GHC.Tc.Gen.Match`, `GHC.Tc.Gen.Pat`, and
`GHC.Tc.Gen.Sig`.

- - - - -
04209f2a by Simon Peyton Jones at 2022-06-06T09:51:15-04:00
Ensure floated dictionaries are in scope (again)

In the Specialiser, we missed one more call to
bringFloatedDictsIntoScope (see #21391).

This omission led to #21689. The problem is that the call
to `rewriteClassOps` needs to have in scope any dictionaries
floated out of the arguments we have just specialised.

Easy fix.

- - - - -
a7fece19 by John Ericson at 2022-06-07T05:04:22+00:00
Don't print the number of deps in count-deps tests

It is redundant information and a source of needless version control
conflicts when multiple MRs are changing the deps list.

Just printing the list and not also its length is fine.

- - - - -
a1651a3a by John Ericson at 2022-06-07T05:06:38+00:00
Core.Lint: Reduce `DynFlags` and `HscEnv`

Co-Authored-By: Andre Marianiello <andremarianiello at users.noreply.github.com>

- - - - -
56ebf9a5 by Andreas Klebinger at 2022-06-09T09:11:43-04:00
Fix a CSE shadowing bug.

We used to process the rhs of non-recursive bindings and their body
using the same env. If we had something like
    let x = ... x ...
this caused trouble because the two xs refer to different binders
but we would substitute both for a new binder x2 causing out of scope
errors.

We now simply use two different envs for the rhs and body in cse_bind.
It's all explained in the Note [Separate envs for let rhs and body]

Fixes #21685

- - - - -
28880828 by sheaf at 2022-06-09T09:12:19-04:00
Typecheck remaining ValArgs in rebuildHsApps

This patch refactors hasFixedRuntimeRep_remainingValArgs, renaming it
to tcRemainingValArgs. The logic is moved to rebuildHsApps, which
ensures consistent behaviour across tcApp and quickLookArg1/tcEValArg.

This patch also refactors the treatment of stupid theta for data
constructors, changing the place we drop stupid theta arguments
from dsConLike to mkDataConRep (now the datacon wrapper drops these
arguments).

We decided not to implement PHASE 2 of the FixedRuntimeRep plan for
these remaining ValArgs. Future directions are outlined on the wiki:
  https://gitlab.haskell.org/ghc/ghc/-/wikis/Remaining-ValArgs

Fixes #21544 and #21650

- - - - -
1fbba97b by Matthew Pickering at 2022-06-09T09:12:54-04:00
Add test for T21682

Fixes #21682

- - - - -
8727be73 by Andreas Klebinger at 2022-06-09T09:13:29-04:00
Document dataToTag# primop

- - - - -
7eab75bb by uhbif19 at 2022-06-09T20:22:47+03:00
Remove TcRnUnknownMessage usage from GHC.Rename.Env #20115

- - - - -
46d2fc65 by uhbif19 at 2022-06-09T20:24:40+03:00
Fix TcRnPragmaWarning meaning

- - - - -
69e72ecd by Matthew Pickering at 2022-06-09T19:07:01-04:00
getProcessCPUTime: Fix the getrusage fallback to account for system CPU time

clock_gettime reports the combined total or user AND system time so in
order to replicate it with getrusage we need to add both system and user
time together.

See https://stackoverflow.com/questions/7622371/getrusage-vs-clock-gettime

Some sample measurements when building Cabal with this patch

t1: rusage
t2: clock_gettime

t1: 62347518000; t2: 62347520873
t1: 62395687000; t2: 62395690171
t1: 62432435000; t2: 62432437313
t1: 62478489000; t2: 62478492465
t1: 62514990000; t2: 62514992534
t1: 62515479000; t2: 62515480327
t1: 62515485000; t2: 62515486344

Fixes #21656

- - - - -
722814ba by Yiyun Liu at 2022-06-10T21:23:03-04:00
Use <br> instead of newline character

- - - - -
dc202080 by Matthew Craven at 2022-06-13T14:07:12-04:00
Use (fixed_lev = True) in mkDataTyConRhs

- - - - -
ad70c621 by Matthew Pickering at 2022-06-14T08:40:53-04:00
hadrian: Fix testing stage1 compiler

There were various issues with testing the stage1 compiler..

1. The wrapper was not being built
2. The wrapper was picking up the stage0 package database and trying to
   load prelude from that.
3. The wrappers never worked on windows so just don't support that for
   now.

Fixes #21072

- - - - -
ac83899d by Ben Gamari at 2022-06-14T08:41:30-04:00
validate: Ensure that $make variable is set

Currently the `$make` variable is used without being set in `validate`'s
Hadrian path, which uses make to install the binary distribution. Fix
this.

Fixes #21687.

- - - - -
59bc6008 by John Ericson at 2022-06-15T18:05:35+00:00
CoreToStg.Prep: Get rid of `DynFlags` and `HscEnv`

The call sites in `Driver.Main` are duplicative, but this is good,
because the next step is to remove `InteractiveContext` from `Core.Lint`
into `Core.Lint.Interactive`.

Also further clean up `Core.Lint` to use a better configuration record
than the one we initially added.

- - - - -
aa9d9381 by Ben Gamari at 2022-06-15T20:33:04-04:00
hadrian: Run xattr -rc . on bindist tarball

Fixes #21506.

- - - - -
cdc75a1f by Ben Gamari at 2022-06-15T20:33:04-04:00
configure: Hide spurious warning from ld

Previously the check_for_gold_t22266 configure check could result in
spurious warnings coming from the linker being blurted to stderr.
Suppress these by piping stderr to /dev/null.

- - - - -
e128b7b8 by Ben Gamari at 2022-06-15T20:33:40-04:00
cmm: Add surface syntax for MO_MulMayOflo

- - - - -
bde65ea9 by Ben Gamari at 2022-06-15T20:34:16-04:00
configure: Don't attempt to override linker on Darwin

Configure's --enable-ld-override functionality is intended to ensure
that we don't rely on ld.bfd, which tends to be slow and buggy, on
Linux and Windows. However, on Darwin the lack of sensible package
management makes it extremely easy for users to have awkward mixtures of
toolchain components from, e.g., XCode, the Apple Command-Line Tools
package, and homebrew. This leads to extremely confusing problems
like #21712.

Here we avoid this by simply giving up on linker selection on Darwin
altogether. This isn't so bad since the Apple ld64 linker has decent
performance and AFAICT fairly reliable.

Closes #21712.

- - - - -
25b510c3 by Torsten Schmits at 2022-06-16T12:37:45-04:00
replace quadratic nub to fight byte code gen perf explosion

Despite this code having been present in the core-to-bytecode
implementation, I have observed it in the wild starting with 9.2,
causing enormous slowdown in certain situations.

My test case produces the following profiles:

Before:

```
	total time  =      559.77 secs   (559766 ticks @ 1000 us, 1 processor)
	total alloc = 513,985,665,640 bytes  (excludes profiling overheads)

COST CENTRE MODULE         SRC                                         %time %alloc  ticks     bytes

elem_by     Data.OldList   libraries/base/Data/OldList.hs:429:1-7       67.6   92.9  378282 477447404296
eqInt       GHC.Classes    libraries/ghc-prim/GHC/Classes.hs:275:8-14   12.4    0.0  69333        32
$c>>=       GHC.Data.IOEnv <no location info>                            6.9    0.6  38475 3020371232
```

After:

```
	total time  =       89.83 secs   (89833 ticks @ 1000 us, 1 processor)
	total alloc = 39,365,306,360 bytes  (excludes profiling overheads)

COST CENTRE           MODULE                SRC                                                                  %time %alloc  ticks     bytes

$c>>=                 GHC.Data.IOEnv        <no location info>                                                    43.6    7.7  39156 3020403424
doCase                GHC.StgToByteCode     compiler/GHC/StgToByteCode.hs:(805,1)-(1054,53)                        2.5    7.4   2246 2920777088

```

- - - - -
aa7e1f20 by Matthew Pickering at 2022-06-16T12:38:21-04:00
hadrian: Don't install `include/` directory in bindist.

The install_includes for the RTS package used to be put in the top-level
./include folder but this would lead to confusing things happening if
you installed multiple GHC versions side-by-side.

We don't need this folder anymore because install-includes
is honoured properly by cabal and the relevant header files already
copied in by the cabal installation process.

If you want to depend on the header files for the RTS in a Haskell
project then you just have to depend on the `rts` package and the
correct include directories will be provided for you.

If you want to depend on the header files in a standard C project then
you should query ghc-pkg to get the right paths.

```
ghc-pkg field rts include-dirs  --simple-output
```

Fixes #21609

- - - - -
03172116 by Bryan Richter at 2022-06-16T12:38:57-04:00
Enable eventlogs on nightly perf job

- - - - -
ecbf8685 by Hécate Moonlight at 2022-06-16T16:30:00-04:00
Repair dead link in TH haddocks

Closes #21724

- - - - -
99ff3818 by sheaf at 2022-06-16T16:30:39-04:00
Hadrian: allow configuring Hsc2Hs

This patch adds the ability to pass options to Hsc2Hs as Hadrian
key/value settings, in the same way as cabal configure options,
using the syntax:

  *.*.hsc2hs.run.opts += ...

- - - - -
9c575f24 by sheaf at 2022-06-16T16:30:39-04:00
Hadrian bootstrap: look up hsc2hs

Hadrian bootstrapping looks up where to find ghc_pkg, but the same
logic was not in place for hsc2hs which meant we could fail to
find the appropriate hsc2hs executabe when bootstrapping Hadrian.
This patch adds that missing logic.

- - - - -
229d741f by Ben Gamari at 2022-06-18T10:42:54-04:00
ghc-heap: Add (broken) test for #21622

- - - - -
cadd7753 by Ben Gamari at 2022-06-18T10:42:54-04:00
ghc-heap: Don't Box NULL pointers

Previously we could construct a `Box` of a NULL pointer from the `link`
field of `StgWeak`. Now we take care to avoid ever introducing such
pointers in `collect_pointers` and ensure that the `link` field is
represented as a `Maybe` in the `Closure` type.

Fixes #21622

- - - - -
31c214cc by Tamar Christina at 2022-06-18T10:43:34-04:00
winio: Add support to console handles to handleToHANDLE

- - - - -
711cb417 by Ben Gamari at 2022-06-18T10:44:11-04:00
CmmToAsm/AArch64: Add SMUL[LH] instructions

These will be needed to fix #21624.

- - - - -
d05d90d2 by Ben Gamari at 2022-06-18T10:44:11-04:00
CmmToAsm/AArch64: Fix syntax of OpRegShift operands

Previously this produced invalid assembly containing a redundant comma.

- - - - -
a1e1d8ee by Ben Gamari at 2022-06-18T10:44:11-04:00
ncg/aarch64: Fix implementation of IntMulMayOflo

The code generated for IntMulMayOflo was previously wrong as it
depended upon the overflow flag, which the AArch64 MUL instruction does
not set. Fix this.

Fixes #21624.

- - - - -
26745006 by Ben Gamari at 2022-06-18T10:44:11-04:00
testsuite: Add test for #21624

Ensuring that mulIntMayOflo# behaves as expected.

- - - - -
94f2e92a by Sebastian Graf at 2022-06-20T09:40:58+02:00
CprAnal: Set signatures of DFuns to top

The recursive DFun in the reproducer for #20836 also triggered a bug in CprAnal
that is observable in a debug build. The CPR signature of a recursive DFunId
was never updated and hence the optimistic arity 0 bottom signature triggered a
mismatch with the arity 1 of the binding in WorkWrap. We never miscompiled any
code because WW doesn't exploit bottom CPR signatures.

- - - - -
b570da84 by Sebastian Graf at 2022-06-20T09:43:29+02:00
CorePrep: Don't speculatively evaluate recursive calls (#20836)

In #20836 we have optimised a terminating program into an endless loop,
because we speculated the self-recursive call of a recursive DFun.
Now we track the set of enclosing recursive binders in CorePrep to prevent
speculation of such self-recursive calls.

See the updates to Note [Speculative evaluation] for details.

Fixes #20836.

- - - - -
49fb2f9b by Sebastian Graf at 2022-06-20T09:43:32+02:00
Simplify: Take care with eta reduction in recursive RHSs (#21652)

Similar to the fix to #20836 in CorePrep, we now track the set of enclosing
recursive binders in the SimplEnv and SimpleOptEnv.
See Note [Eta reduction in recursive RHSs] for details.

I also updated Note [Arity robustness] with the insights Simon and I had in a
call discussing the issue.

Fixes #21652.

Unfortunately, we get a 5% ghc/alloc regression in T16577. That is due to
additional eta reduction in GHC.Read.choose1 and the resulting ANF-isation
of a large list literal at the top-level that didn't happen before (presumably
because it was too interesting to float to the top-level). There's not much we
can do about that.

Metric Increase:
    T16577

- - - - -
2563b95c by Sebastian Graf at 2022-06-20T09:45:09+02:00
Ignore .hie-bios

- - - - -
e4e44d8d by Simon Peyton Jones at 2022-06-20T12:31:45-04:00
Instantiate top level foralls in partial type signatures

The main fix for #21667 is the new call to tcInstTypeBnders
in tcHsPartialSigType. It was really a simple omission before.

I also moved the decision about whether we need to apply the
Monomorphism Restriction, from `decideGeneralisationPlan` to
`tcPolyInfer`.  That removes a flag from the InferGen constructor,
which is good.

But more importantly, it allows the new function,
   checkMonomorphismRestriction
called from `tcPolyInfer`, to "see" the `Types` involved rather than
the `HsTypes`.  And that in turn matters because we invoke the MR for
partial signatures if none of the partial signatures in the group have
any overloading context; and we can't answer that question for HsTypes.
See Note [Partial type signatures and the monomorphism restriction]
in GHC.Tc.Gen.Bind.

This latter is really a pre-existing bug.

- - - - -
262a9f93 by Winston Hartnett at 2022-06-20T12:32:23-04:00
Make Outputable instance for InlineSig print the InlineSpec

Fix ghc/ghc#21739

Squash fix ghc/ghc#21739

- - - - -
b5590fff by Matthew Pickering at 2022-06-20T12:32:59-04:00
Add NO_BOOT to hackage_doc_tarball job

We were attempting to boot a src-tarball which doesn't work as ./boot is
not included in the source tarball. This slipped through as the job is
only run on nightly.

- - - - -
d24afd9d by Vladislav Zavialov at 2022-06-20T17:34:44-04:00
HsToken for @-patterns and TypeApplications (#19623)

One more step towards the new design of EPA.

- - - - -
159b7628 by Tamar Christina at 2022-06-20T17:35:23-04:00
linker: only keep rtl exception tables if they have been relocated

- - - - -
da5ff105 by Andreas Klebinger at 2022-06-21T17:04:12+02:00
Ticky:Make json info a separate field.

- - - - -
1a4ce4b2 by Matthew Pickering at 2022-06-22T09:49:22+01:00
Revert "Ticky:Make json info a separate field."

This reverts commit da5ff10503e683e2148c62e36f8fe2f819328862.

This was pushed directly without review.

- - - - -
f89bf85f by Vanessa McHale at 2022-06-22T08:21:32-04:00
Flags to disable local let-floating; -flocal-float-out, -flocal-float-out-top-level CLI flags

These flags affect the behaviour of local let floating.

If `-flocal-float-out` is disabled (the default) then we disable all
local floating.

```
…(let x = let y = e in (a,b) in body)...
===>
…(let y = e; x = (a,b) in body)...

```

Further to this, top-level local floating can be disabled on it's own by
passing -fno-local-float-out-top-level.

```
x = let y = e in (a,b)
===>
y = e; x = (a,b)
```

Note that this is only about local floating, ie, floating two adjacent
lets past each other and doesn't say anything about the global floating
pass which is controlled by `-fno-float`.

Fixes #13663

- - - - -
4ccefc6e by Matthew Craven at 2022-06-22T08:22:12-04:00
Check for Int overflows in Data.Array.Byte

- - - - -
2004e3c8 by Matthew Craven at 2022-06-22T08:22:12-04:00
Add a basic test for ByteArray's Monoid instance

- - - - -
fb36770c by Matthew Craven at 2022-06-22T08:22:12-04:00
Rename `copyByteArray` to `unsafeCopyByteArray`

- - - - -
ecc9aedc by Ben Gamari at 2022-06-22T08:22:48-04:00
testsuite: Add test for #21719

Happily, this has been fixed since 9.2.

- - - - -
19606c42 by Brandon Chinn at 2022-06-22T08:23:28-04:00
Use lookupNameCache instead of lookupOrigIO

- - - - -
4c9dfd69 by Brandon Chinn at 2022-06-22T08:23:28-04:00
Break out thNameToGhcNameIO (ref. #21730)

- - - - -
eb4fb849 by Michael Peyton Jones at 2022-06-22T08:24:07-04:00
Add laws for 'toInteger' and 'toRational'

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

- - - - -
c1a950c1 by Alexander Esgen at 2022-06-22T12:36:13+00:00
Correct documentation of defaults of the `-V` RTS option

- - - - -
b7b7d90d by Matthew Pickering at 2022-06-22T21:58:12-04:00
Transcribe discussion from #21483 into a Note

In #21483 I had a discussion with Simon Marlow about the memory
retention behaviour of -Fd. I have just transcribed that conversation
here as it elucidates the potentially subtle assumptions which led to
the design of the memory retention behaviours of -Fd.

Fixes #21483

- - - - -
980d1954 by Ben Gamari at 2022-06-22T21:58:48-04:00
eventlog: Don't leave dangling pointers hanging around

Previously we failed to reset pointers to various eventlog buffers to
NULL after freeing them. In principle we shouldn't look at them after
they are freed but nevertheless it is good practice to set them to a
well-defined value.

- - - - -
575ec846 by Eric Lindblad at 2022-06-22T21:59:28-04:00
runhaskell
- - - - -
e6a69337 by Artem Pelenitsyn at 2022-06-22T22:00:07-04:00
re-export GHC.Natural.minusNaturalMaybe from Numeric.Natural

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

- - - - -
5d45aa97 by Gergo ERDI at 2022-06-22T22:00:46-04:00
When specialising, look through floatable ticks.

Fixes #21697.

- - - - -
531205ac by Andreas Klebinger at 2022-06-22T22:01:22-04:00
TagCheck.hs: Properly check if arguments are boxed types.

For one by mistake I had been checking against the kind of runtime rep
instead of the boxity.

This uncovered another bug, namely that we tried to generate the
checking code before we had associated the function arguments with
a register, so this could never have worked to begin with.

This fixes #21729 and both of the above issues.

- - - - -
c7f9f6b5 by Gleb Popov at 2022-06-22T22:02:00-04:00
Use correct arch for the FreeBSD triple in gen-data-layout.sh

Downstream bug for reference: https://bugs.freebsd.org/bugzilla/show_bug.cgi?id=261798
Relevant upstream issue: #15718

- - - - -
75f0091b by Andreas Klebinger at 2022-06-22T22:02:35-04:00
Bump nofib submodule.

Allows the shake runner to build with 9.2.3 among other things.

Fixes #21772

- - - - -
0aa0ce69 by Ben Gamari at 2022-06-27T08:01:03-04:00
Bump ghc-prim and base versions

To 0.9.0 and 4.17.0 respectively.

Bumps array, deepseq, directory, filepath, haskeline, hpc, parsec, stm,
terminfo, text, unix, haddock, and hsc2hs submodules.

(cherry picked from commit ba47b95122b7b336ce1cc00896a47b584ad24095)

- - - - -
4713abc2 by Ben Gamari at 2022-06-27T08:01:03-04:00
testsuite: Use normalise_version more consistently

Previously several tests' output were unnecessarily dependent on version
numbers, particularly of `base`. Fix this.

- - - - -
d7b0642b by Matthew Pickering at 2022-06-27T08:01:03-04:00
linters: Fix lint-submodule-refs when crashing trying to find plausible branches

- - - - -
38378be3 by Andreas Klebinger at 2022-06-27T08:01:39-04:00
hadrian: Improve haddocks for ghcDebugAssertions

- - - - -
ac7a7fc8 by Andreas Klebinger at 2022-06-27T08:01:39-04:00
Don't mark lambda binders as OtherCon

We used to put OtherCon unfoldings on lambda binders of workers
and sometimes also join points/specializations with with the
assumption that since the wrapper would force these arguments
once we execute the RHS they would indeed be in WHNF.

This was wrong for reasons detailed in #21472. So now we purge
evaluated unfoldings from *all* lambda binders.

This fixes #21472, but at the cost of sometimes not using as efficient a
calling convention. It can also change inlining behaviour as some
occurances will no longer look like value arguments when they did
before.

As consequence we also change how we compute CBV information for
arguments slightly. We now *always* determine the CBV convention
for arguments during tidy. Earlier in the pipeline we merely mark
functions as candidates for having their arguments treated as CBV.

As before the process is described in the relevant notes:
Note [CBV Function Ids]
Note [Attaching CBV Marks to ids]
Note [Never put `OtherCon` unfoldigns on lambda binders]

-------------------------
Metric Decrease:
    T12425
    T13035
    T18223
    T18223
    T18923
    MultiLayerModulesTH_OneShot
Metric Increase:
    WWRec
-------------------------

- - - - -
06cf6f4a by Tony Zorman at 2022-06-27T08:02:18-04:00
Add suggestions for unrecognised pragmas (#21589)

In case of a misspelled pragma, offer possible corrections as to what
the user could have meant.

Fixes: https://gitlab.haskell.org/ghc/ghc/-/issues/21589

- - - - -
3fbab757 by Greg Steuck at 2022-06-27T08:02:56-04:00
Remove the traces of i386-*-openbsd, long live amd64

OpenBSD will not ship any ghc packages on i386 starting with 7.2
release.  This means there will not be a bootstrap compiler easily
available.  The last available binaries are ghc-8.10.6 which is
already not supported as bootstrap for HEAD.

See here for more information:

https://marc.info/?l=openbsd-ports&m=165060700222580&w=2

- - - - -
58530271 by Bodigrim at 2022-06-27T08:03:34-04:00
Add Foldable1 and Bifoldable1 type classes

Approved by CLC in https://github.com/haskell/core-libraries-committee/issues/9

Instances roughly follow
https://hackage.haskell.org/package/semigroupoids-5.3.7/docs/Data-Semigroup-Foldable-Class.html#t:Foldable1
but the API of `Foldable1` was expanded in comparison to `semigroupoids`.

Compatibility shim is available from https://github.com/phadej/foldable1 (to be released).

Closes #13573.

- - - - -
a51f4ecc by Naomi Liu at 2022-06-27T08:04:13-04:00
add levity polymorphism to addrToAny#

- - - - -
f4edcdc4 by Naomi Liu at 2022-06-27T08:04:13-04:00
add tests for addrToAny# levity

- - - - -
07016fc9 by Matthew Pickering at 2022-06-27T08:04:49-04:00
hadrian: Update main README page

This README had some quite out-of-date content about the build system so
I did a complete pass deleting old material. I also made the section
about flavours more prominent and mentioned flavour transformers.

- - - - -
79ae2d89 by Ben Gamari at 2022-06-27T08:05:24-04:00
testsuite: Hide output from test compilations with verbosity==2

Previously the output from test compilations used to determine whether,
e.g., profiling libraries are available was shown with verbosity
levels >= 2. However, the default level is 2, meaning that most users
were often spammed with confusing errors. Fix this by bumping the
verbosity threshold for this output to >=3.

Fixes #21760.
- - - - -
995ea44d by Ben Gamari at 2022-06-27T08:06:00-04:00
configure: Only probe for LD in FIND_LD

Since 6be2c5a7e9187fc14d51e1ec32ca235143bb0d8b we would probe for LD
rather early in `configure`. However, it turns out that this breaks
`configure`'s `ld`-override logic, which assumes that `LD` was set by
the user and aborts.

Fixes #21778.

- - - - -
b43d140b by Sergei Trofimovich at 2022-06-27T08:06:39-04:00
`.hs-boot` make rules: add missing order-only dependency on target directory

Noticed missing target directory dependency as a build failure in
`make --shuffle` mode (added in https://savannah.gnu.org/bugs/index.php?62100):

    "cp" libraries/base/./GHC/Stack/CCS.hs-boot libraries/base/dist-install/build/GHC/Stack/CCS.hs-boot
    cp: cannot create regular file 'libraries/base/dist-install/build/GHC/Stack/CCS.hs-boot': No such file or directory
    libraries/haskeline/ghc.mk:4: libraries/haskeline/dist-install/build/.depend-v-p-dyn.haskell: No such file or directory
    make[1]: *** [libraries/base/ghc.mk:4: libraries/base/dist-install/build/GHC/Stack/CCS.hs-boot] Error 1 shuffle=1656129254
    make: *** [Makefile:128: all] Error 2 shuffle=1656129254

Note that `cp` complains about inability to create target file.

The change adds order-only dependency on a target directory (similar to
the rest of rules in that file).

The bug is lurking there since 2009 commit 34cc75e1a (`GHC new build
system megapatch`.) where upfront directory creation was never added to
`.hs-boot` files.

- - - - -
57a5f88c by Ben Gamari at 2022-06-28T03:24:24-04:00
Mark AArch64/Darwin as requiring sign-extension

Apple's AArch64 ABI requires that the caller sign-extend small integer
arguments. Set platformCConvNeedsExtension to reflect this fact.

Fixes #21773.

- - - - -
df762ae9 by Ben Gamari at 2022-06-28T03:24:24-04:00
-ddump-llvm shouldn't imply -fllvm

Previously -ddump-llvm would change the backend used, which contrasts
with all other dump flags. This is quite surprising and cost me quite
a bit of time. Dump flags should not change compiler behavior.

Fixes #21776.

- - - - -
70f0c1f8 by Ben Gamari at 2022-06-28T03:24:24-04:00
CmmToAsm/AArch64: Re-format argument handling logic

Previously there were very long, hard to parse lines. Fix this.

- - - - -
696d64c3 by Ben Gamari at 2022-06-28T03:24:24-04:00
CmmToAsm/AArch64: Sign-extend narrow C arguments

The AArch64/Darwin ABI requires that function arguments narrower
than 32-bits must be sign-extended by the caller. We neglected to
do this, resulting in #20735.

Fixes #20735.

- - - - -
c006ac0d by Ben Gamari at 2022-06-28T03:24:24-04:00
testsuite: Add test for #20735

- - - - -
16b9100c by Ben Gamari at 2022-06-28T03:24:59-04:00
integer-gmp: Fix cabal file

Evidently fields may not come after sections in a cabal file.

- - - - -
03cc5d02 by Sergei Trofimovich at 2022-06-28T15:20:45-04:00
ghc.mk: fix 'make install' (`mk/system-cxx-std-lib-1.0.conf.install` does not exist)

before the change `make install` was failing as:

```
"mv" "/<<NIX>>/ghc-9.3.20220406/lib/ghc-9.5.20220625/bin/ghc-stage2" "/<<NIX>>/ghc-9.3.20220406/lib/ghc-9.5.20220625/bin/ghc"
make[1]: *** No rule to make target 'mk/system-cxx-std-lib-1.0.conf.install', needed by 'install_packages'.  Stop.
```

I think it's a recent regression caused by 0ef249aa where `system-cxx-std-lib-1.0.conf`
is created (somewhat manually), but not the .install varianlt of it.

The fix is to consistently use `mk/system-cxx-std-lib-1.0.conf` everywhere.

Closes: https://gitlab.haskell.org/ghc/ghc/-/issues/21784

- - - - -
eecab8f9 by Simon Peyton Jones at 2022-06-28T15:21:21-04:00
Comments only, about join points

This MR just adds some documentation about why casts
destroy join points, following #21716.

- - - - -
251471e7 by Matthew Pickering at 2022-06-28T19:02:41-04:00
Cleanup BuiltInSyntax vs UserSyntax

There was some confusion about whether FUN/TYPE/One/Many should be
BuiltInSyntax or UserSyntax. The answer is certainly UserSyntax as
BuiltInSyntax is for things which are directly constructed by the parser
rather than going through normal renaming channels.

I fixed all the obviously wrong places I could find and added a test for
the original bug which was caused by this (#21752)

Fixes #21752 #20695 #18302

- - - - -
0e22f16c by Ben Gamari at 2022-06-28T19:03:16-04:00
template-haskell: Bump version to 2.19.0.0

Bumps text and exceptions submodules due to bounds.

- - - - -
bbe6f10e by Emily Bourke at 2022-06-29T08:23:13+00:00
Tiny tweak to `IOPort#` documentation

The exclamation mark and bracket don’t seem to make sense here. I’ve
looked through the history, and I don’t think they’re deliberate – possibly
a copy-and-paste error.
- - - - -
70e47489 by Dominik Peteler at 2022-06-29T19:26:31-04:00
Remove `CoreOccurAnal` constructor of the `CoreToDo` type

It was dead code since the last occurence in an expression context got
removed in 71916e1c018dded2e68d6769a2dbb8777da12664.

- - - - -
d0722170 by nineonine at 2022-07-01T08:15:56-04:00
Fix panic with UnliftedFFITypes+CApiFFI (#14624)

When declaring foreign import using CAPI calling convention, using
unlifted unboxed types would result in compiler panic. There was
an attempt to fix the situation in #9274, however it only addressed
some of the ByteArray cases.

This patch fixes other missed cases for all prims that may be used
as basic foreign types.

- - - - -
eb043148 by Douglas Wilson at 2022-07-01T08:16:32-04:00
rts: gc stats: account properly for copied bytes in sequential collections

We were not updating the [copied,any_work,scav_find_work, max_n_todo_overflow]
counters during sequential collections. As well, we were double counting for
parallel collections.

To fix this we add an `else` clause to the `if (is_par_gc())`.

The par_* counters do not need to be updated in the sequential case
because they must be 0.

- - - - -
f95edea9 by Matthew Pickering at 2022-07-01T19:21:55-04:00
desugar: Look through ticks when warning about possible literal overflow

Enabling `-fhpc` or `-finfo-table-map` would case a tick to end up
between the appliation of `neg` to its argument. This defeated the
special logic which looks for `NegApp ... (HsOverLit` to warn about
possible overflow if a user writes a negative literal (without out
NegativeLiterals) in their code.

Fixes #21701

- - - - -
f25c8d03 by Matthew Pickering at 2022-07-01T19:22:31-04:00
ci: Fix definition of slow-validate flavour (so that -dlint) is passed

In this embarassing sequence of events we were running slow-validate
without -dlint.

- - - - -
bf7991b0 by Mike Pilgrem at 2022-07-02T10:12:04-04:00
Identify the extistence of the `runhaskell` command and that it is equivalent to the `runghc` command. Add an entry to the index for `runhaskell`. See https://gitlab.haskell.org/ghc/ghc/-/issues/21411
- - - - -
9e79f6d0 by Simon Jakobi at 2022-07-02T10:12:39-04:00
Data.Foldable1: Remove references to Foldable-specific note

...as discussed in
https://gitlab.haskell.org/ghc/ghc/-/merge_requests/8495#note_439455.

- - - - -
3a8970ac by romes at 2022-07-03T14:11:31-04:00
TTG: Move HsModule to L.H.S

Move the definition of HsModule defined in GHC.Hs to
Language.Haskell.Syntax with an added TTG parameter and corresponding
extension fields.

This is progress towards having the haskell-syntax package, as described
in #21592

- - - - -
f9f80995 by romes at 2022-07-03T14:11:31-04:00
TTG: Move ImpExp client-independent bits to L.H.S.ImpExp

Move the GHC-independent definitions from GHC.Hs.ImpExp to
Language.Haskell.Syntax.ImpExp with the required TTG extension fields
such as to keep the AST independent from GHC.

This is progress towards having the haskell-syntax package, as described
in #21592

Bumps haddock submodule

- - - - -
c43dbac0 by romes at 2022-07-03T14:11:31-04:00
Refactor ModuleName to L.H.S.Module.Name

ModuleName used to live in GHC.Unit.Module.Name. In this commit, the
definition of ModuleName and its associated functions are moved to
Language.Haskell.Syntax.Module.Name according to the current plan
towards making the AST GHC-independent.

The instances for ModuleName for Outputable, Uniquable and Binary were
moved to the module in which the class is defined because these instances
depend on GHC.

The instance of Eq for ModuleName is slightly changed to no longer
depend on unique explicitly and instead uses FastString's instance of
Eq.

- - - - -
2635c6f2 by konsumlamm at 2022-07-03T14:12:11-04:00
Expand `Ord` instance for `Down`

Approved by CLC in https://github.com/haskell/core-libraries-committee/issues/23#issuecomment-1172932610

- - - - -
36fba0df by Anselm Schüler at 2022-07-04T05:06:42+00:00
Add applyWhen to Data.Function per CLC prop

Approved by CLC in https://github.com/haskell/core-libraries-committee/issues/71#issuecomment-1165830233

- - - - -
3b13aab1 by Matthew Pickering at 2022-07-04T15:15:00-04:00
hadrian: Don't read package environments in ghc-stage1 wrapper

The stage1 compiler may be on the brink of existence and not have even a
working base library. You may have installed packages globally with a
similar stage2 compiler which will then lead to arguments such as
--show-iface not even working because you are passing too many package
flags. The solution is simple, don't read these implicit files.

Fixes #21803

- - - - -
aba482ea by Andreas Klebinger at 2022-07-04T17:55:55-04:00
Ticky:Make json info a separate field.

Fixes #21233

- - - - -
74f3867d by Matthew Pickering at 2022-07-04T17:56:30-04:00
Add docs:<pkg> command to hadrian to build docs for just one package

- - - - -
418afaf1 by Matthew Pickering at 2022-07-04T17:56:30-04:00
upload-docs: propagate publish correctly in upload_sdist

- - - - -
ed793d7a by Matthew Pickering at 2022-07-04T17:56:30-04:00
docs-upload: Fix upload script when no packages are listed

- - - - -
d002c6e0 by Matthew Pickering at 2022-07-04T17:56:30-04:00
hadrian: Add --haddock-base-url option for specifying base-url when generating docs

The motiviation for this flag is to be able to produce documentation
which is suitable for uploading for hackage, ie, the cross-package links
work correctly.

There are basically three values you want to set this to:

* off - default, base_url = ../%pkg% which works for local browsing
* on - no argument , base_url = https:://hackage.haskell.org/package/%pkg%/docs - for hackage docs upload
* on - argument, for example, base_url = http://localhost:8080/package/%pkg%/docs for testing the documentation.

The `%pkg%` string is a template variable which is replaced with the
package identifier for the relevant package.

This is one step towards fixing #21749

- - - - -
41eb749a by Matthew Pickering at 2022-07-04T17:56:31-04:00
Add nightly job for generating docs suitable for hackage upload

- - - - -
620ee7ed by Matthew Pickering at 2022-07-04T17:57:05-04:00
ghci: Support :set prompt in multi repl

This adds supports for various :set commands apart from `:set <FLAG>` in
multi repl, this includes `:set prompt` and so-on.

Fixes #21796

- - - - -
b151b65e by Matthew Pickering at 2022-07-05T16:32:31-04:00
Vendor filepath inside template-haskell

Adding filepath as a dependency of template-haskell means that it can't
be reinstalled if any build-plan depends on template-haskell.

This is a temporary solution for the 9.4 release.

A longer term solution is to split-up the template-haskell package into
the wired-in part and a non-wired-in part which can be reinstalled. This
was deemed quite risky on the 9.4 release timescale.

Fixes #21738

- - - - -
c9347ecf by John Ericson at 2022-07-05T16:33:07-04:00
Factor fields of `CoreDoSimplify` into separate data type

This avoids some partiality. The work @mmhat is doing cleaning up and
modularizing `Core.Opt` will build on this nicely.

- - - - -
d0e74992 by Eric Lindblad at 2022-07-06T01:35:48-04:00
https urls
- - - - -
803e965c by Eric Lindblad at 2022-07-06T01:35:48-04:00
options and typos
- - - - -
5519baa5 by Eric Lindblad at 2022-07-06T01:35:48-04:00
grammar
- - - - -
4ddc1d3e by Eric Lindblad at 2022-07-06T01:35:48-04:00
sources
- - - - -
c95c2026 by Matthew Pickering at 2022-07-06T01:35:48-04:00
Fix lint warnings in bootstrap.py

- - - - -
86ced2ad by romes at 2022-07-06T01:36:23-04:00
Restore Eq instance of ImportDeclQualifiedStyle

Fixes #21819

- - - - -
3547e264 by romes at 2022-07-06T13:50:27-04:00
Prune L.H.S modules of GHC dependencies

Move around datatypes, functions and instances that are GHC-specific out
of the `Language.Haskell.Syntax.*` modules to reduce the GHC
dependencies in them -- progressing towards #21592

Creates a module `Language.Haskell.Syntax.Basic` to hold basic
definitions required by the other L.H.S modules (and don't belong in any
of them)

- - - - -
e4eea07b by romes at 2022-07-06T13:50:27-04:00
TTG: Move CoreTickish out of LHS.Binds

Remove the `[CoreTickish]` fields from datatype `HsBindLR idL idR` and
move them to the extension point instance, according to the plan
outlined in #21592 to separate the base AST from the GHC specific bits.

- - - - -
acc1816b by romes at 2022-07-06T13:50:27-04:00
TTG for ForeignImport/Export

Add a TTG parameter to both `ForeignImport` and `ForeignExport` and,
according to #21592, move the GHC-specific bits in them and in the other
AST data types related to foreign imports and exports to the TTG
extension point.

- - - - -
371c5ecf by romes at 2022-07-06T13:50:27-04:00
TTG for HsTyLit

Add TTG parameter to `HsTyLit` to move the GHC-specific `SourceText`
fields to the extension point and out of the base AST.

Progress towards #21592

- - - - -
fd379d1b by romes at 2022-07-06T13:50:27-04:00
Remove many GHC dependencies from L.H.S

Continue to prune the `Language.Haskell.Syntax.*` modules out of GHC
imports according to the plan in the linked issue.

Moves more GHC-specific declarations to `GHC.*` and brings more required
GHC-independent declarations to `Language.Haskell.Syntax.*` (extending
e.g. `Language.Haskell.Syntax.Basic`).

Progress towards #21592

Bump haddock submodule for !8308

-------------------------
Metric Decrease:
    hard_hole_fits
-------------------------

- - - - -
c5415bc5 by Alan Zimmerman at 2022-07-06T13:50:27-04:00
Fix exact printing of the HsRule name

Prior to this branch, the HsRule name was

    XRec pass (SourceText,RuleName)

and there is an ExactPrint instance for (SourceText, RuleName).

The SourceText has moved to a different location, so synthesise the
original to trigger the correct instance when printing.

We need both the SourceText and RuleName when exact printing, as it is
possible to have a NoSourceText variant, in which case we fall back to
the FastString.

- - - - -
665fa5a7 by Matthew Pickering at 2022-07-06T13:51:03-04:00
driver: Fix issue with module loops and multiple home units

We were attempting to rehydrate all dependencies of a particular module,
but we actually only needed to rehydrate those of the current package
(as those are the ones participating in the loop).

This fixes loading GHC into a multi-unit session.

Fixes #21814

- - - - -
bbcaba6a by Andreas Klebinger at 2022-07-06T13:51:39-04:00
Remove a bogus #define from ClosureMacros.h

- - - - -
fa59223b by Tamar Christina at 2022-07-07T23:23:57-04:00
winio: make consoleReadNonBlocking not wait for any events at all.

- - - - -
42c917df by Adam Sandberg Ericsson at 2022-07-07T23:24:34-04:00
rts: allow NULL to be used as an invalid StgStablePtr

- - - - -
3739e565 by Andreas Schwab at 2022-07-07T23:25:10-04:00
RTS: Add stack marker to StgCRunAsm.S

Every object file must be properly marked for non-executable stack, even if it
contains no code.

- - - - -
a889bc05 by Ben Gamari at 2022-07-07T23:25:45-04:00
Bump unix submodule

Adds `config.sub` to unix's `.gitignore`, fixing #19574.

- - - - -
3609a478 by Matthew Pickering at 2022-07-09T11:11:58-04:00
ghci: Fix most calls to isLoaded to work in multi-mode

The most egrarious thing this fixes is the report about the total number
of loaded modules after starting a session.

Ticket #20889

- - - - -
fc183c90 by Matthew Pickering at 2022-07-09T11:11:58-04:00
Enable :edit command in ghci multi-mode.

This works after the last change to isLoaded.

Ticket #20888

- - - - -
46050534 by Simon Peyton Jones at 2022-07-09T11:12:34-04:00
Fix a scoping bug in the Specialiser

In the call to `specLookupRule` in `already_covered`, in `specCalls`,
we need an in-scope set that includes the free vars of the arguments.
But we simply were not guaranteeing that: did not include the
`rule_bndrs`.

Easily fixed.  I'm not sure how how this bug has lain for quite
so long without biting us.

Fixes #21828.

- - - - -
6e8d9056 by Simon Peyton Jones at 2022-07-12T13:26:52+00:00
Edit Note [idArity varies independently of dmdTypeDepth]

...and refer to it in GHC.Core.Lint.lintLetBind.

Fixes #21452

- - - - -
89ba4655 by Simon Peyton Jones at 2022-07-12T13:26:52+00:00
Tiny documentation wibbles (comments only)

- - - - -
61a46c6d by Eric Lindblad at 2022-07-13T08:28:29-04:00
fix readme
- - - - -
61babb5e by Eric Lindblad at 2022-07-13T08:28:29-04:00
fix bootstrap
- - - - -
8b417ad5 by Eric Lindblad at 2022-07-13T08:28:29-04:00
tarball
- - - - -
e9d9f078 by Zubin Duggal at 2022-07-13T14:00:18-04:00
hie-files: Fix scopes for deriving clauses and instance signatures (#18425)

- - - - -
c4989131 by Zubin Duggal at 2022-07-13T14:00:18-04:00
hie-files: Record location of filled in default method bindings

This is useful for hie files to reconstruct the evidence that default methods
depend on.

- - - - -
9c52e7fc by Zubin Duggal at 2022-07-13T14:00:18-04:00
testsuite: Factor out common parts from hiefile tests

- - - - -
6a9e4493 by sheaf at 2022-07-13T14:00:56-04:00
Hadrian: update documentation of settings

The documentation for key-value settings was a bit out of date.
This patch updates it to account for `cabal.configure.opts` and
`hsc2hs.run.opts`.

The user-settings document was also re-arranged, to make the key-value
settings more prominent (as it doesn't involve changing the Hadrian
source code, and thus doesn't require any recompilation of Hadrian).

- - - - -
a2f142f8 by Zubin Duggal at 2022-07-13T20:43:32-04:00
Fix potential space leak that arise from ModuleGraphs retaining references
to previous ModuleGraphs, in particular the lazy `mg_non_boot` field.
This manifests in `extendMG`.

Solution: Delete `mg_non_boot` as it is only used for `mgLookupModule`, which
is only called in two places in the compiler, and should only be called at most
once for every home unit:

GHC.Driver.Make:
      mainModuleSrcPath :: Maybe String
      mainModuleSrcPath = do
        ms <- mgLookupModule mod_graph (mainModIs hue)
        ml_hs_file (ms_location ms)

GHCI.UI:
listModuleLine modl line = do
   graph <- GHC.getModuleGraph
   let this = GHC.mgLookupModule graph modl

Instead `mgLookupModule` can be a linear function that looks through the entire
list of `ModuleGraphNodes`

Fixes #21816

- - - - -
dcf8b30a by Ben Gamari at 2022-07-13T20:44:08-04:00
rts: Fix AdjustorPool bitmap manipulation

Previously the implementation of bitmap_first_unset assumed that
`__builtin_clz` would accept `uint8_t` however it apparently rather
extends its argument to `unsigned int`.

To fix this we simply revert to a naive implementation since handling
the various corner cases with `clz` is quite tricky. This should be
fine given that AdjustorPool isn't particularly hot. Ideally we would
have a single, optimised bitmap implementation in the RTS but I'll leave
this for future work.

Fixes #21838.

- - - - -
ad8f3e15 by Luite Stegeman at 2022-07-16T07:20:36-04:00
Change GHCi bytecode return convention for unlifted datatypes.

This changes the bytecode return convention for unlifted
algebraic datatypes to be the same as for lifted
types, i.e. ENTER/PUSH_ALTS instead of
RETURN_UNLIFTED/PUSH_ALTS_UNLIFTED

Fixes #20849

- - - - -
5434d1a3 by Colten Webb at 2022-07-16T07:21:15-04:00
Compute record-dot-syntax types
Ensures type information for record-dot-syntax
is included in HieASTs. See #21797

- - - - -
89d169ec by Colten Webb at 2022-07-16T07:21:15-04:00
Add record-dot-syntax test

- - - - -
4beb9f3c by Ben Gamari at 2022-07-16T07:21:51-04:00
Document RuntimeRep polymorphism limitations of catch#, et al

As noted in #21868, several primops accepting continuations producing
RuntimeRep-polymorphic results aren't nearly as polymorphic as their
types suggest. Document this limitation and adapt the `UnliftedWeakPtr`
test to avoid breaking this limitation in `keepAlive#`.

- - - - -
4ef1c65d by Ben Gamari at 2022-07-16T07:21:51-04:00
Make keepAlive# out-of-line

This is a naive approach to fixing the unsoundness noticed in #21708.
Specifically, we remove the lowering of `keepAlive#` via CorePrep and
instead turn it into an out-of-line primop.
This is simple, inefficient (since the continuation must now be heap
allocated), but good enough for 9.4.1. We will revisit this
(particiularly via #16098) in a future release.

Metric Increase:
    T4978
    T7257
    T9203

- - - - -
1bbff35d by Greg Steuck at 2022-07-16T07:22:29-04:00
Suppress extra output from configure check for c++ libraries

- - - - -
3acbd7ad by Ben Gamari at 2022-07-16T07:23:04-04:00
rel-notes: Drop mention of #21745 fix

Since we have backported the fix to 9.4.1.

- - - - -
b27c2774 by Dominik Peteler at 2022-07-16T07:23:43-04:00
Align the behaviour of `dopt` and `log_dopt`

Before the behaviour of `dopt` and `logHasDumpFlag` (and the underlying
function `log_dopt`) were different as the latter did not take the
verbosity level into account. This led to problems during the
refactoring as we cannot simply replace calls to `dopt` with calls to
`logHasDumpFlag`.

In addition to that a subtle bug in the GHC module was fixed:
`setSessionDynFlags` did not update the logger and as a consequence the
verbosity value of the logger was not set appropriately.

Fixes #21861

- - - - -
28347d71 by Douglas Wilson at 2022-07-16T13:25:06-04:00
rts: forkOn context switches the target capability

Fixes #21824

- - - - -
f1c44991 by Ben Gamari at 2022-07-16T13:25:41-04:00
cmm: Eliminate orphan Outputable instances

Here we reorganize `GHC.Cmm` to eliminate the orphan `Outputable` and
`OutputableP` instances for the Cmm AST. This makes it significantly
easier to use the Cmm pretty-printers in tracing output without
incurring module import cycles.

- - - - -
f2e5e763 by Ben Gamari at 2022-07-16T13:25:41-04:00
cmm: Move toBlockList to GHC.Cmm

- - - - -
fa092745 by Ben Gamari at 2022-07-16T13:25:41-04:00
compiler: Add haddock sections to GHC.Utils.Panic

- - - - -
097759f9 by Ben Gamari at 2022-07-16T13:26:17-04:00
configure: Don't override Windows CXXFLAGS

At some point we used the clang distribution from msys2's `MINGW64`
environment for our Windows toolchain. This defaulted to using libgcc
and libstdc++ for its runtime library. However, we found for a variety
of reasons that compiler-rt, libunwind, and libc++ were more reliable,
consequently we explicitly overrode the CXXFLAGS to use these.

However, since then we have switched to use the `CLANG64` packaging,
which default to these already. Consequently we can drop these
arguments, silencing some redundant argument warnings from clang.

Fixes #21669.

- - - - -
e38a2684 by Ben Gamari at 2022-07-16T23:50:36-04:00
rts/linker/Elf: Check that there are no NULL ctors

- - - - -
616365b0 by Ben Gamari at 2022-07-16T23:50:36-04:00
rts/linker/Elf: Introduce support for invoking finalizers on unload

Addresses #20494.

- - - - -
cdd3be20 by Ben Gamari at 2022-07-16T23:50:36-04:00
testsuite: Add T20494

- - - - -
03c69d8d by Ben Gamari at 2022-07-16T23:50:36-04:00
rts/linker/PEi386: Rename finit field to fini

fini is short for "finalizer", which does not contain a "t".

- - - - -
033580bc by Ben Gamari at 2022-07-16T23:50:36-04:00
rts/linker/PEi386: Refactor handling of oc->info

Previously we would free oc->info after running initializers. However,
we can't do this is we want to also run finalizers.

Moreover, freeing oc->info so early was wrong for another reason:
we will need it in order to unregister the exception tables (see the
call to `RtlDeleteFunctionTable`).

In service of #20494.

- - - - -
f17912e4 by Ben Gamari at 2022-07-16T23:50:36-04:00
rts/linker/PEi386: Add finalization support

This implements #20494 for the PEi386 linker.

Happily, this also appears to fix `T9405`, resolving #21361.

- - - - -
2cd75550 by Ben Gamari at 2022-07-16T23:50:36-04:00
Loader: Implement gnu-style -l:$path syntax

Gnu ld allows `-l` to be passed an absolute file path,
signalled by a `:` prefix. Implement this in the GHC's
loader search logic.

- - - - -
5781a360 by Ben Gamari at 2022-07-16T23:50:36-04:00
Statically-link against libc++ on Windows

Unfortunately on Windows we have no RPATH-like facility, making dynamic
linking extremely fragile. Since we cannot assume that the user will
add their GHC installation to `$PATH` (and therefore their DLL
search path) we cannot assume that the loader will be able to locate our
`libc++.dll`. To avoid this, we instead statically link against `libc++.a` on
Windows.

Fixes #21435.

- - - - -
8e2e883b by Ben Gamari at 2022-07-16T23:50:36-04:00
rts/linker/PEi386: Ensure that all .ctors/.dtors sections are run

It turns out that PE objects may have multiple `.ctors`/`.dtors`
sections but the RTS linker had assumed that there was only one. Fix
this.

Fixes #21618.

- - - - -
fba04387 by Ben Gamari at 2022-07-16T23:50:36-04:00
rts/linker/PEi386: Respect dtor/ctor priority

Previously we would run constructors and destructors in arbitrary order
despite explicit priorities.

Fixes #21847.

- - - - -
1001952f by Ben Gamari at 2022-07-16T23:50:36-04:00
testsuite: Add test for #21618 and #21847

- - - - -
6f3816af by Ben Gamari at 2022-07-16T23:50:36-04:00
rts/linker/PEi386: Fix exception unwind unregistration

RtlDeleteFunctionTable expects a pointer to the .pdata section
yet we passed it the .xdata section.

Happily, this fixes #21354.

- - - - -
d9bff44c by Ben Gamari at 2022-07-16T23:50:36-04:00
rts/linker/MachO: Drop dead code

- - - - -
d161e6bc by Ben Gamari at 2022-07-16T23:50:36-04:00
rts/linker/MachO: Use section flags to identify initializers

- - - - -
fbb17110 by Ben Gamari at 2022-07-16T23:50:36-04:00
rts/linker/MachO: Introduce finalizer support

- - - - -
5b0ed8a8 by Ben Gamari at 2022-07-16T23:50:37-04:00
testsuite: Use system-cxx-std-lib instead of config.stdcxx_impl

- - - - -
6c476e1a by Ben Gamari at 2022-07-16T23:50:37-04:00
rts/linker/Elf: Work around GCC 6 init/fini behavior

It appears that GCC 6t (at least on i386) fails to give
init_array/fini_array sections the correct SHT_INIT_ARRAY/SHT_FINI_ARRAY
section types, instead marking them as SHT_PROGBITS. This caused T20494
to fail on Debian.

- - - - -
5f8203b8 by Ben Gamari at 2022-07-16T23:50:37-04:00
testsuite: Mark T13366Cxx as unbroken on Darwin

- - - - -
1fd2f851 by Ben Gamari at 2022-07-16T23:50:37-04:00
rts/linker: Fix resolution of __dso_handle on Darwin

Darwin expects a leading underscore.

- - - - -
a2dc00f3 by Ben Gamari at 2022-07-16T23:50:37-04:00
rts/linker: Clean up section kinds

- - - - -
aeb1a7c3 by Ben Gamari at 2022-07-16T23:50:37-04:00
rts/linker: Ensure that __cxa_finalize is called on code unload

- - - - -
028f081e by Ben Gamari at 2022-07-16T23:51:12-04:00
testsuite: Fix T11829 on Centos 7

It appears that Centos 7 has a more strict C++ compiler than most
distributions since std::runtime_error is defined in <stdexcept> rather
than <exception>. In T11829 we mistakenly imported the latter.

- - - - -
a10584e8 by Ben Gamari at 2022-07-17T22:30:32-04:00
hadrian: Rename documentation directories for consistency with make

* Rename `docs` to `doc`
* Place pdf documentation in `doc/` instead of `doc/pdfs/`

Fixes #21164.

- - - - -
b27c5947 by Anselm Schüler at 2022-07-17T22:31:11-04:00
Fix incorrect proof of applyWhen’s properties

- - - - -
eb031a5b by Matthew Pickering at 2022-07-18T08:04:47-04:00
hadrian: Add multi:<pkg> and multi targets for starting a multi-repl

This patch adds support to hadrian for starting a multi-repl containing
all the packages which stage0 can build. In particular, there is the new
user-facing command:

```
./hadrian/ghci-multi
```

which when executed will start a multi-repl containing the `ghc` package
and all it's dependencies.

This is implemented by two new hadrian targets:

```
./hadrian/build multi:<pkg>
```

Construct the arguments for a multi-repl session where the top-level
package is <pkg>. For example, `./hadrian/ghci-multi` is implemented
using `multi:ghc` target.

There is also the `multi` command which constructs a repl for everything
in stage0 which we can build.

- - - - -
19e7cac9 by Eric Lindblad at 2022-07-18T08:05:27-04:00
changelog typo
- - - - -
af6731a4 by Eric Lindblad at 2022-07-18T08:05:27-04:00
typos

- - - - -
415468fe by Simon Peyton Jones at 2022-07-18T16:36:54-04:00
Refactor SpecConstr to use treat bindings uniformly

This patch, provoked by #21457, simplifies SpecConstr by treating
top-level and nested bindings uniformly (see the new scBind).

* Eliminates the mysterious scTopBindEnv

* Refactors scBind to handle top-level and nested definitions
  uniformly.

* But, for now at least, continues the status quo of not doing
  SpecConstr for top-level non-recursive bindings.  (In contrast
  we do specialise nested non-recursive bindings, although the
  original paper did not; see Note [Local let bindings].)

  I tried the effect of specialising top-level non-recursive
  bindings (which is now dead easy to switch on, unlike before)
  but found some regressions, so I backed off.  See !8135.

It's a pure refactoring.  I think it'll do a better job in a few
cases, but there is no regression test.

- - - - -
d4d3fe6e by Andreas Klebinger at 2022-07-18T16:37:29-04:00
Rule matching: Don't compute the FVs if we don't look at them.

- - - - -
5f907371 by Simon Peyton Jones at 2022-07-18T16:38:04-04:00
White space only in FamInstEnv

- - - - -
ae3b3b62 by Simon Peyton Jones at 2022-07-18T16:38:04-04:00
Make transferPolyIdInfo work for CPR

I don't know why this hasn't bitten us before, but it was plain wrong.

- - - - -
9bdfdd98 by Simon Peyton Jones at 2022-07-18T16:38:04-04:00
Inline mapAccumLM

This function is called in inner loops in the compiler, and it's
overloaded and higher order.  Best just to inline it.

This popped up when I was looking at something else.  I think
perhaps GHC is delicately balanced on the cusp of inlining this
automatically.

- - - - -
d0b806ff by Simon Peyton Jones at 2022-07-18T16:38:04-04:00
Make SetLevels honour floatConsts

This fix,  in the definition of profitableFloat,
is just for consistency. `floatConsts` should
do what it says!

I don't think it'll affect anything much, though.

- - - - -
d1c25a48 by Simon Peyton Jones at 2022-07-18T16:38:04-04:00
Refactor wantToUnboxArg a bit

* Rename GHC.Core.Opt.WorkWrap.Utils.wantToUnboxArg to canUnboxArg
  and similarly wantToUnboxResult to canUnboxResult.

* Add GHC.Core.Opt.DmdAnal.wantToUnboxArg as a wrapper for
  the (new) GHC.Core.Opt.WorkWrap.Utils.canUnboxArg,
  avoiding some yukky duplication.

  I decided it was clearer to give it a new data type for its
  return type, because I nedeed the FD_RecBox case which was not
  otherwise readiliy expressible.

* Add dcpc_args to WorkWrap.Utils.DataConPatContext for the payload

* Get rid of the Unlift constructor of UnboxingDecision, eliminate
  two panics, and two arguments to canUnboxArg (new name).  Much
  nicer now.

- - - - -
6d8a715e by Teo Camarasu at 2022-07-18T16:38:44-04:00
Allow running memInventory when the concurrent nonmoving gc is enabled

If the nonmoving gc is enabled and we are using a threaded RTS,
we now try to grab the collector mutex to avoid memInventory and
the collection racing.

Before memInventory was disabled.

- - - - -
aa75bbde by Ben Gamari at 2022-07-18T16:39:20-04:00
gitignore: don't ignore all aclocal.m4 files

While GHC's own aclocal.m4 is generated by the aclocal tool, other
packages' aclocal.m4 are committed in the repository. Previously
`.gitignore` included an entry which covered *any* file named
`aclocal.m4`, which lead to quite some confusion (e.g. see #21740).
Fix this by modifying GHC's `.gitignore` to only cover GHC's own
`aclocal.m4`.

- - - - -
4b98c5ce by Boris Lykah at 2022-07-19T02:34:12-04:00
Add mapAccumM, forAccumM to Data.Traversable

Approved by Core Libraries Committee in
https://github.com/haskell/core-libraries-committee/issues/65#issuecomment-1186275433

- - - - -
bd92182c by Ben Gamari at 2022-07-19T02:34:47-04:00
configure: Use AC_PATH_TOOL to detect tools

Previously we used AC_PATH_PROG which, as noted by #21601, does not
look for tools with a target prefix,
breaking cross-compilation.

Fixes #21601.

- - - - -
e8c07aa9 by Matthew Pickering at 2022-07-19T10:07:53-04:00
driver: Fix implementation of -S

We were failing to stop before running the assembler so the object file
was also created.

Fixes #21869

- - - - -
e2f0094c by Ben Gamari at 2022-07-19T10:08:28-04:00
rts/ProfHeap: Ensure new Censuses are zeroed

When growing the Census array ProfHeap previously neglected to
zero the new part of the array. Consequently `freeEra` would attempt to
free random words that often looked suspiciously like pointers.

Fixes #21880.

- - - - -
81d65f7f by sheaf at 2022-07-21T15:37:22+02:00
Make withDict opaque to the specialiser

As pointed out in #21575, it is not sufficient to set withDict to inline
after the typeclass specialiser, because we might inline withDict in one
module and then import it in another, and we run into the same problem.
This means we could still end up with incorrect runtime results because
the typeclass specialiser would assume that distinct typeclass evidence
terms at the same type are equal, when this is not necessarily the case
when using withDict.

Instead, this patch introduces a new magicId, 'nospec', which is only
inlined in CorePrep. We make use of it in the definition of withDict
to ensure that the typeclass specialiser does not common up distinct
typeclass evidence terms.

Fixes #21575

- - - - -
9a3e1f31 by Dominik Peteler at 2022-07-22T08:18:40-04:00
Refactored Simplify pass

 * Removed references to driver from GHC.Core.LateCC, GHC.Core.Simplify
   namespace and GHC.Core.Opt.Stats.
   Also removed services from configuration records.

 * Renamed GHC.Core.Opt.Simplify to GHC.Core.Opt.Simplify.Iteration.

 * Inlined `simplifyPgm` and renamed `simplifyPgmIO` to `simplifyPgm`
   and moved the Simplify driver to GHC.Core.Opt.Simplify.

 * Moved `SimplMode` and `FloatEnable` to GHC.Core.Opt.Simplify.Env.

 * Added a configuration record `TopEnvConfig` for the `SimplTopEnv` environment
   in GHC.Core.Opt.Simplify.Monad.

 * Added `SimplifyOpts` and `SimplifyExprOpts`. Provide initialization functions
   for those in a new module GHC.Driver.Config.Core.Opt.Simplify.
   Also added initialization functions for `SimplMode` to that module.

 * Moved `CoreToDo` and friends to a new module GHC.Core.Pipeline.Types
   and the counting types and functions (`SimplCount` and `Tick`) to new
   module GHC.Core.Opt.Stats.

 * Added getter functions for the fields of `SimplMode`. The pedantic bottoms
   option and the platform are retrieved from the ArityOpts and RuleOpts and the
   getter functions allow us to retrieve values from `SpecEnv` without the
   knowledge where the data is stored exactly.

 * Moved the coercion optimization options from the top environment to
   `SimplMode`. This way the values left in the top environment are those
   dealing with monadic functionality, namely logging, IO related stuff and
   counting. Added a note "The environments of the Simplify pass".

 * Removed `CoreToDo` from GHC.Core.Lint and GHC.CoreToStg.Prep and got rid of
   `CoreDoSimplify`. Pass `SimplifyOpts` in the `CoreToDo` type instead.

 * Prep work before removing `InteractiveContext` from `HscEnv`.

- - - - -
2c5991cc by Simon Peyton Jones at 2022-07-22T08:18:41-04:00
Make the specialiser deal better with specialised methods

This patch fixes #21848, by being more careful to update unfoldings
in the type-class specialiser.

See the new Note [Update unfolding after specialisation]

Now that we are being so much more careful about unfoldings,
it turned out that I could dispense with se_interesting, and
all its tricky corners. Hooray.  This fixes #21368.

- - - - -
ae166635 by Ben Gamari at 2022-07-22T08:18:41-04:00
ghc-boot: Clean up UTF-8 codecs

In preparation for moving the UTF-8 codecs into `base`:

* Move them to GHC.Utils.Encoding.UTF8
* Make names more consistent
* Add some Haddocks

- - - - -
e8ac91db by Ben Gamari at 2022-07-22T08:18:41-04:00
base: Introduce GHC.Encoding.UTF8

Here we copy a subset of the UTF-8 implementation living in `ghc-boot`
into `base`, with the intent of dropping the former in the future. For
this reason, the `ghc-boot` copy is now CPP-guarded on
`MIN_VERSION_base(4,18,0)`.

Naturally, we can't copy *all* of the functions defined by `ghc-boot` as
some depend upon `bytestring`; we rather just copy those which only
depend upon `base` and `ghc-prim`.

Further consolidation?
----------------------

Currently GHC ships with at least five UTF-8 implementations:

* the implementation used by GHC in `ghc-boot:GHC.Utils.Encoding`; this
  can be used at a number of types including `Addr#`, `ByteArray#`,
  `ForeignPtr`, `Ptr`, `ShortByteString`, and `ByteString`. Most of this
  can be removed in GHC 9.6+2, when the copies in `base` will become
  available to `ghc-boot`.
* the copy of the `ghc-boot` definition now exported by
  `base:GHC.Encoding.UTF8`. This can be used at `Addr#`, `Ptr`,
  `ByteArray#`, and `ForeignPtr`
* the decoder used by `unpackCStringUtf8#` in `ghc-prim:GHC.CString`;
  this is specialised at `Addr#`.
* the codec used by the IO subsystem in `base:GHC.IO.Encoding.UTF8`;
  this is specialised at `Addr#` but, unlike the above, supports
  recovery in the presence of partial codepoints (since in IO contexts
  codepoints may be broken across buffers)
* the implementation provided by the `text` library

This does seem a tad silly. On the other hand, these implementations
*do* materially differ from one another (e.g. in the types they support,
the detail in errors they can report, and the ability to recover from
partial codepoints). Consequently, it's quite unclear that further
consolidate would be worthwhile.

- - - - -
f9ad8025 by Ben Gamari at 2022-07-22T08:18:41-04:00
Add a Note summarising GHC's UTF-8 implementations

GHC has a somewhat dizzying array of UTF-8 implementations. This note
describes why this is the case.

- - - - -
72dfad3d by Ben Gamari at 2022-07-22T08:18:42-04:00
upload_ghc_libs: Fix path to documentation

The documentation was moved in a10584e8df9b346cecf700b23187044742ce0b35
but this one occurrence was note updated.

Finally closes #21164.

- - - - -
a8b150e7 by sheaf at 2022-07-22T08:18:44-04:00
Add test for #21871

This adds a test for #21871, which was fixed by the No Skolem Info
rework (MR !7105).

Fixes #21871

- - - - -
6379f942 by sheaf at 2022-07-22T08:18:46-04:00
Add test for #21360

The way record updates are typechecked/desugared changed in MR !7981.
Because we desugar in the typechecker to a simple case expression, the
pattern match checker becomes able to spot the long-distance information
and avoid emitting an incorrect pattern match warning.

Fixes #21360

- - - - -
ce0cd12c by sheaf at 2022-07-22T08:18:47-04:00
Hadrian: don't try to build "unix" on Windows
- - - - -
dc27e15a by Simon Peyton Jones at 2022-07-25T09:42:01-04:00
Implement DeepSubsumption

This MR adds the language extension -XDeepSubsumption, implementing
GHC proposal #511.  This change mitigates the impact of GHC proposal

The changes are highly localised, by design.  See Note [Deep subsumption]
in GHC.Tc.Utils.Unify.

The main changes are:

* Add -XDeepSubsumption, which is on by default in Haskell98 and Haskell2010,
  but off in Haskell2021.

  -XDeepSubsumption largely restores the behaviour before the "simple subsumption" change.
  -XDeepSubsumpition has a similar flavour as -XNoMonoLocalBinds:
  it makes type inference more complicated and less predictable, but it
  may be convenient in practice.

* The main changes are in:
  * GHC.Tc.Utils.Unify.tcSubType, which does deep susumption and eta-expanansion
  * GHC.Tc.Utils.Unify.tcSkolemiseET, which does deep skolemisation
  * In GHC.Tc.Gen.App.tcApp we call tcSubTypeNC to match the result
    type. Without deep subsumption, unifyExpectedType would be sufficent.

  See Note [Deep subsumption] in GHC.Tc.Utils.Unify.

* There are no changes to Quick Look at all.

* The type of `withDict` becomes ambiguous; so add -XAllowAmbiguousTypes to
  GHC.Magic.Dict

* I fixed a small but egregious bug in GHC.Core.FVs.varTypeTyCoFVs, where
  we'd forgotten to take the free vars of the multiplicity of an Id.

* I also had to fix tcSplitNestedSigmaTys

  When I did the shallow-subsumption patch
    commit 2b792facab46f7cdd09d12e79499f4e0dcd4293f
    Date:   Sun Feb 2 18:23:11 2020 +0000
    Simple subsumption

  I changed tcSplitNestedSigmaTys to not look through function arrows
  any more.  But that was actually an un-forced change.  This function
  is used only in

  * Improving error messages in GHC.Tc.Gen.Head.addFunResCtxt
  * Validity checking for default methods: GHC.Tc.TyCl.checkValidClass
  * A couple of calls in the GHCi debugger: GHC.Runtime.Heap.Inspect

  All to do with validity checking and error messages. Acutally its
  fine to look under function arrows here, and quite useful a test
  DeepSubsumption05 (a test motivated by a build failure in the
  `lens` package) shows.

  The fix is easy.  I added Note [tcSplitNestedSigmaTys].

- - - - -
e31ead39 by Matthew Pickering at 2022-07-25T09:42:01-04:00
Add tests that -XHaskell98 and -XHaskell2010 enable DeepSubsumption

- - - - -
67189985 by Matthew Pickering at 2022-07-25T09:42:01-04:00
Add DeepSubsumption08

- - - - -
5e93a952 by Simon Peyton Jones at 2022-07-25T09:42:01-04:00
Fix the interaction of operator sections and deep subsumption

Fixes DeepSubsumption08

- - - - -
918620d9 by Zubin Duggal at 2022-07-25T09:42:01-04:00
Add DeepSubsumption09

- - - - -
2a773259 by Gabriella Gonzalez at 2022-07-25T09:42:40-04:00
Default implementation for mempty/(<>)

Approved by: https://github.com/haskell/core-libraries-committee/issues/61

This adds a default implementation for `mempty` and `(<>)` along
with a matching `MINIMAL` pragma so that `Semigroup` and `Monoid`
instances can be defined in terms of `sconcat` / `mconcat`.

The description for each class has also been updated to include the
equivalent set of laws for the `sconcat`-only / `mconcat`-only
instances.

- - - - -
73836fc8 by Bryan Richter at 2022-07-25T09:43:16-04:00
ci: Disable (broken) perf-nofib

See #21859

- - - - -
c24ca5c3 by sheaf at 2022-07-25T09:43:58-04:00
Docs: clarify ConstraintKinds infelicity

GHC doesn't consistently require the ConstraintKinds extension to
be enabled, as it allows programs such as type families returning
a constraint without this extension.

MR !7784 fixes this infelicity, but breaking user programs was deemed
to not be worth it, so we document it instead.

Fixes #21061.

- - - - -
5f2fbd5e by Simon Peyton Jones at 2022-07-25T09:44:34-04:00
More improvements to worker/wrapper

This patch fixes #21888, and simplifies finaliseArgBoxities
by eliminating the (recently introduced) data type FinalDecision.

A delicate interaction meant that this patch
   commit d1c25a48154236861a413e058ea38d1b8320273f
   Date:   Tue Jul 12 16:33:46 2022 +0100
   Refactor wantToUnboxArg a bit

make worker/wrapper go into an infinite loop.  This patch
fixes it by narrowing the handling of case (B) of
Note [Boxity for bottoming functions], to deal only the
arguemnts that are type variables.  Only then do we drop
the trimBoxity call, which is what caused the bug.

I also
* Added documentation of case (B), which was previously
  completely un-mentioned.  And a regression test,
  T21888a, to test it.

* Made unboxDeeplyDmd stop at lazy demands.  It's rare anyway
  for a bottoming function to have a lazy argument (mainly when
  the data type is recursive and then we don't want to unbox
  deeply).  Plus there is Note [No lazy, Unboxed demands in
  demand signature]

* Refactored the Case equation for dmdAnal a bit, to do less
  redundant pattern matching.

- - - - -
b77d95f8 by Simon Peyton Jones at 2022-07-25T09:45:09-04:00
Fix a small buglet in tryEtaReduce

Gergo points out (#21801) that GHC.Core.Opt.Arity.tryEtaReduce was
making an ill-formed cast.  It didn't matter, because the subsequent
guard discarded it; but still worth fixing.  Spurious warnings are
distracting.

- - - - -
3bbde957 by Zubin Duggal at 2022-07-25T09:45:45-04:00
Fix #21889, GHCi misbehaves with Ctrl-C on Windows

On Windows, we create multiple levels of wrappers for GHCi which ultimately
execute ghc --interactive. In order to handle console events properly, each of
these wrappers must call FreeConsole() in order to hand off event processing to
the child process. See #14150.

In addition to this, FreeConsole must only be called from interactive processes (#13411).

This commit makes two changes to fix this situation:

1. The hadrian wrappers generated using `hadrian/bindist/cwrappers/version-wrapper.c` call `FreeConsole`
   if the CPP flag INTERACTIVE_PROCESS is set, which is set when we are generating a wrapper for GHCi.
2. The GHCi wrapper in `driver/ghci/` calls the `ghc-$VER.exe` executable which is not wrapped rather
   than calling `ghc.exe` is is wrapped on windows (and usually non-interactive, so can't call `FreeConsole`:

   Before:
   ghci-$VER.exe calls ghci.exe which calls ghc.exe which calls ghc-$VER.exe

   After:
   ghci-$VER.exe calls ghci.exe which calls ghc-$VER.exe

- - - - -
79f1b021 by Simon Jakobi at 2022-07-25T09:46:21-04:00
docs: Fix documentation of \cases

Fixes #21902.

- - - - -
e4bf9592 by sternenseemann at 2022-07-25T09:47:01-04:00
ghc-cabal: allow Cabal 3.8 to unbreak make build

When bootstrapping GHC 9.4.*, the build will fail when configuring
ghc-cabal as part of the make based build system due to this upper
bound, as Cabal has been updated to a 3.8 release.

Reference #21914, see especially
https://gitlab.haskell.org/ghc/ghc/-/issues/21914#note_444699

- - - - -
726d938e by Simon Peyton Jones at 2022-07-25T14:38:14-04:00
Fix isEvaldUnfolding and isValueUnfolding

This fixes (1) in #21831.  Easy, obviously correct.

- - - - -
5d26c321 by Simon Peyton Jones at 2022-07-25T14:38:14-04:00
Switch off eta-expansion in rules and unfoldings

I think this change will make little difference except to reduce
clutter.  But that's it -- if it causes problems we can switch it
on again.

- - - - -
d4fe2f4e by Simon Peyton Jones at 2022-07-25T14:38:14-04:00
Teach SpecConstr about typeDeterminesValue

This patch addresses #21831, point 2.  See
Note [generaliseDictPats] in SpecConstr

I took the opportunity to refactor the construction of specialisation
rules a bit, so that the rule name says what type we are specialising
at.

Surprisingly, there's a 20% decrease in compile time for test
perf/compiler/T18223. I took a look at it, and the code size seems the
same throughout. I did a quick ticky profile which seemed to show a
bit less substitution going on.  Hmm.  Maybe it's the "don't do
eta-expansion in stable unfoldings" patch, which is part of the
same MR as this patch.

Anyway, since it's a move in the right direction, I didn't think it
was worth looking into further.

Metric Decrease:
    T18223

- - - - -
65f7838a by Simon Peyton Jones at 2022-07-25T14:38:14-04:00
Add a 'notes' file in testsuite/tests/perf/compiler

This file is just a place to accumlate notes about particular
benchmarks, so that I don't keep re-inventing the wheel.

- - - - -
61faff40 by Simon Peyton Jones at 2022-07-25T14:38:50-04:00
Get the in-scope set right in FamInstEnv.injectiveBranches

There was an assert error, as Gergo pointed out in #21896.

I fixed this by adding an InScopeSet argument to tcUnifyTyWithTFs.
And also to GHC.Core.Unify.niFixTCvSubst.

I also took the opportunity to get a couple more InScopeSets right,
and to change some substTyUnchecked into substTy.

This MR touches a lot of other files, but only because I also took the
opportunity to introduce mkInScopeSetList, and use it.

- - - - -
4a7256a7 by Cheng Shao at 2022-07-25T20:41:55+00:00
Add location to cc phase

- - - - -
96811ba4 by Cheng Shao at 2022-07-25T20:41:55+00:00
Avoid as pipeline when compiling c

- - - - -
2869b66d by Cheng Shao at 2022-07-25T20:42:20+00:00
testsuite: Skip test cases involving -S when testing unregisterised GHC

We no longer generate .s files anyway.

Metric Decrease:
    MultiLayerModules
    T10421
    T13035
    T13701
    T14697
    T16875
    T18140
    T18304
    T18923
    T9198

- - - - -
82a0991a by Ben Gamari at 2022-07-25T23:32:05-04:00
testsuite: introduce nonmoving_thread_sanity way

(cherry picked from commit 19f8fce3659de3d72046bea9c61d1a82904bc4ae)

- - - - -
4b087973 by Ben Gamari at 2022-07-25T23:32:06-04:00
rts/nonmoving: Track segment state

It can often be useful during debugging to be able to determine the
state of a nonmoving segment. Introduce some state, enabled by DEBUG, to
track this.

(cherry picked from commit 40e797ef591ae3122ccc98ab0cc3cfcf9d17bd7f)

- - - - -
54a5c32d by Ben Gamari at 2022-07-25T23:32:06-04:00
rts/nonmoving: Don't scavenge objects which weren't evacuated

This fixes a rather subtle bug in the logic responsible for scavenging
objects evacuated to the non-moving generation. In particular, objects
can be allocated into the non-moving generation by two ways:

 a. evacuation out of from-space by the garbage collector
 b. direct allocation by the mutator

Like all evacuation, objects moved by (a) must be scavenged, since they
may contain references to other objects located in from-space. To
accomplish this we have the following scheme:

 * each nonmoving segment's block descriptor has a scan pointer which
   points to the first object which has yet to be scavenged

 * the GC tracks a set of "todo" segments which have pending scavenging
   work

 * to scavenge a segment, we scavenge each of the unmarked blocks
   between the scan pointer and segment's `next_free` pointer.

   We skip marked blocks since we know the allocator wouldn't have
   allocated into marked blocks (since they contain presumably live
   data).

   We can stop at `next_free` since, by
   definition, the GC could not have evacuated any objects to blocks
   above `next_free` (otherwise `next_free wouldn't be the first free
   block).

However, this neglected to consider objects allocated by path (b).
In short, the problem is that objects directly allocated by the mutator
may become unreachable (but not swept, since the containing segment is
not yet full), at which point they may contain references to swept objects.
Specifically, we observed this in #21885 in the following way:

1. the mutator (specifically in #21885, a `lockCAF`) allocates an object
   (specifically a blackhole, which here we will call `blkh`; see Note
   [Static objects under the nonmoving collector] for the reason why) on
   the non-moving heap. The bitmap of the allocated block remains 0
   (since allocation doesn't affect the bitmap) and the containing
   segment's (which we will call `blkh_seg`) `next_free` is advanced.
2. We enter the blackhole, evaluating the blackhole to produce a result
   (specificaly a cons cell) in the nursery
3. The blackhole gets updated into an indirection pointing to the cons
   cell; it is pushed to the generational remembered set
4. we perform a GC, the cons cell is evacuated into the nonmoving heap
   (into segment `cons_seg`)
5. the cons cell is marked
6. the GC concludes
7. the CAF and blackhole become unreachable
8. `cons_seg` is filled
9. we start another GC; the cons cell is swept
10. we start a new GC
11. something is evacuated into `blkh_seg`, adding it to the "todo" list
12. we attempt to scavenge `blkh_seg` (namely, all unmarked blocks
    between `scan` and `next_free`, which includes `blkh`). We attempt to
    evacuate `blkh`'s indirectee, which is the previously-swept cons cell.
    This is unsafe, since the indirectee is no longer a valid heap
    object.

The problem here was that the scavenging logic *assumed* that (a) was
the only source of allocations into the non-moving heap and therefore
*all* unmarked blocks between `scan` and `next_free` were evacuated.
However, due to (b) this is not true.

The solution is to ensure that that the scanned region only encompasses
the region of objects allocated during evacuation. We do this by
updating `scan` as we push the segment to the todo-segment list to
point to the block which was evacuated into.

Doing this required changing the nonmoving scavenging implementation's
update of the `scan` pointer to bump it *once*, instead of after
scavenging each block as was done previously. This is because we may end
up evacuating into the segment being scavenged as we scavenge it. This
was quite tricky to discover but the result is quite simple,
demonstrating yet again that global mutable state should be used
exceedingly sparingly.

Fixes #21885

(cherry picked from commit 0b27ea23efcb08639309293faf13fdfef03f1060)

- - - - -
25c24535 by Ben Gamari at 2022-07-25T23:32:06-04:00
testsuite: Skip a few tests as in the nonmoving collector

Residency monitoring under the non-moving collector is quite
conservative (e.g. the reported value is larger than reality) since
otherwise we would need to block on concurrent collection. Skip a few
tests that are sensitive to residency.

(cherry picked from commit 6880e4fbf728c04e8ce83e725bfc028fcb18cd70)

- - - - -
42147534 by sternenseemann at 2022-07-26T16:26:53-04:00
hadrian: add flag disabling selftest rules which require QuickCheck

The hadrian executable depends on QuickCheck for building, meaning this
library (and its dependencies) will need to be built for bootstrapping
GHC in the future. Building QuickCheck, however, can require
TemplateHaskell. When building a statically linking GHC toolchain,
TemplateHaskell can be tricky to get to work, and cross-compiling
TemplateHaskell doesn't work at all without -fexternal-interpreter,
so QuickCheck introduces an element of fragility to GHC's bootstrap.

Since the selftest rules are the only part of hadrian that need
QuickCheck, we can easily eliminate this bootstrap dependency when
required by introducing a `selftest` flag guarding the rules' inclusion.

Closes #8699.

- - - - -
9ea29d47 by Simon Peyton Jones at 2022-07-26T16:27:28-04:00
Regression test for #21848

- - - - -
ef30e215 by Matthew Pickering at 2022-07-28T13:56:59-04:00
driver: Don't create LinkNodes when -no-link is enabled

Fixes #21866

- - - - -
fc23b5ed by sheaf at 2022-07-28T13:57:38-04:00
Docs: fix mistaken claim about kind signatures

This patch fixes #21806 by rectifying an incorrect claim about
the usage of kind variables in the header of a data declaration with
a standalone kind signature.

It also adds some clarifications about the number of parameters expected
in GADT declarations and in type family declarations.

- - - - -
2df92ee1 by Matthew Pickering at 2022-08-02T05:20:01-04:00
testsuite: Correctly set withNativeCodeGen

Fixes #21918

- - - - -
f2912143 by Matthew Pickering at 2022-08-02T05:20:45-04:00
Fix since annotations in GHC.Stack.CloneStack

Fixes #21894

- - - - -
aeb8497d by Andreas Klebinger at 2022-08-02T19:26:51-04:00
Add -dsuppress-coercion-types to make coercions even smaller.

Instead of `` `cast` <Co:11> :: (Some -> Really -> Large Type)``
simply print `` `cast` <Co:11> :: ... ``

- - - - -
97655ad8 by sheaf at 2022-08-02T19:27:29-04:00
User's guide: fix typo in hasfield.rst

Fixes #21950

- - - - -
35aef18d by Yiyun Liu at 2022-08-04T02:55:07-04:00
Remove TCvSubst and use Subst for both term and type-level subst

This patch removes the TCvSubst data type and instead uses Subst as
the environment for both term and type level substitution. This
change is partially motivated by the existential type proposal,
which will introduce types that contain expressions and therefore
forces us to carry around an "IdSubstEnv" even when substituting for
types. It also reduces the amount of code because "Subst" and
"TCvSubst" share a lot of common operations. There isn't any
noticeable impact on performance (geo. mean for ghc/alloc is around
0.0% but we have -94 loc and one less data type to worry abount).

Currently, the "TCvSubst" data type for substitution on types is
identical to the "Subst" data type except the former doesn't store
"IdSubstEnv". Using "Subst" for type-level substitution means there
will be a redundant field stored in the data type. However, in cases
where the substitution starts from the expression, using "Subst" for
type-level substitution saves us from having to project "Subst" into a
"TCvSubst". This probably explains why the allocation is mostly even
despite the redundant field.

The patch deletes "TCvSubst" and moves "Subst" and its relevant
functions from "GHC.Core.Subst" into "GHC.Core.TyCo.Subst".
Substitution on expressions is still defined in "GHC.Core.Subst" so we
don't have to expose the definition of "Expr" in the hs-boot file that
"GHC.Core.TyCo.Subst" must import to refer to "IdSubstEnv" (whose
codomain is "CoreExpr"). Most functions named fooTCvSubst are renamed
into fooSubst with a few exceptions (e.g. "isEmptyTCvSubst" is a
distinct function from "isEmptySubst"; the former ignores the
emptiness of "IdSubstEnv"). These exceptions mainly exist for
performance reasons and will go away when "Expr" and "Type" are
mutually recursively defined (we won't be able to take those
shortcuts if we can't make the assumption that expressions don't
appear in types).

- - - - -
b99819bd by Krzysztof Gogolewski at 2022-08-04T02:55:43-04:00
Fix TH + defer-type-errors interaction (#21920)

Previously, we had to disable defer-type-errors in splices because of #7276.
But this fix is no longer necessary, the test T7276 no longer segfaults
and is now correctly deferred.

- - - - -
fb529cae by Andreas Klebinger at 2022-08-04T13:57:25-04:00
Add a note about about W/W for unlifting strict arguments

This fixes #21236.

- - - - -
fffc75a9 by Matthew Pickering at 2022-08-04T13:58:01-04:00
Force safeInferred to avoid retaining extra copy of DynFlags

This will only have a (very) modest impact on memory but we don't want
to retain old copies of DynFlags hanging around so best to force this
value.

- - - - -
0f43837f by Matthew Pickering at 2022-08-04T13:58:01-04:00
Force name selectors to ensure no reference to Ids enter the NameCache

I observed some unforced thunks in the NameCache which were retaining a
whole Id, which ends up retaining a Type.. which ends up retaining old
copies of HscEnv containing stale HomeModInfo.

- - - - -
0b1f5fd1 by Matthew Pickering at 2022-08-04T13:58:01-04:00
Fix leaks in --make mode when there are module loops

This patch fixes quite a tricky leak where we would end up retaining
stale ModDetails due to rehydrating modules against non-finalised
interfaces.

== Loops with multiple boot files

It is possible for a module graph to have a loop (SCC, when ignoring boot files)
which requires multiple boot files to break. In this case we must perform the
necessary hydration steps before and after compiling modules which have boot files
which are described above for corectness but also perform an additional hydration step
at the end of the SCC to remove space leaks.

Consider the following example:

┌───────┐   ┌───────┐
│       │   │       │
│   A   │   │   B   │
│       │   │       │
└─────┬─┘   └───┬───┘
      │         │
 ┌────▼─────────▼──┐
 │                 │
 │        C        │
 └────┬─────────┬──┘
      │         │
 ┌────▼──┐  ┌───▼───┐
 │       │  │       │
 │ A-boot│  │ B-boot│
 │       │  │       │
 └───────┘  └───────┘

 A, B and C live together in a SCC. Say we compile the modules in order
 A-boot, B-boot, C, A, B then when we compile A we will perform the hydration steps
 (because A has a boot file). Therefore C will be hydrated relative to A, and the
 ModDetails for A will reference C/A. Then when B is compiled C will be rehydrated again,
 and so B will reference C/A,B, its interface will be hydrated relative to both A and B.
 Now there is a space leak because say C is a very big module, there are now two different copies of
 ModDetails kept alive by modules A and B.

The way to avoid this space leak is to rehydrate an entire SCC together at the
end of compilation so that all the ModDetails point to interfaces for .hs files.
In this example, when we hydrate A, B and C together then both A and B will refer to
C/A,B.

See #21900 for some more discussion.

-------------------------------------------------------

In addition to this simple case, there is also the potential for a leak
during parallel upsweep which is also fixed by this patch. Transcibed is
Note [ModuleNameSet, efficiency and space leaks]

Note [ModuleNameSet, efficiency and space leaks]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~

During unsweep the results of compiling modules are placed into a MVar, to find
the environment the module needs to compile itself in the MVar is consulted and
the HomeUnitGraph is set accordingly. The reason we do this is that precisely tracking
module dependencies and recreating the HUG from scratch each time is very expensive.

In serial mode (-j1), this all works out fine because a module can only be compiled after
its dependencies have finished compiling and not interleaved with compiling module loops.
Therefore when we create the finalised or no loop interfaces, the HUG only contains
finalised interfaces.

In parallel mode, we have to be more careful because the HUG variable can contain
non-finalised interfaces which have been started by another thread. In order to avoid
a space leak where a finalised interface is compiled against a HPT which contains a
non-finalised interface we have to restrict the HUG to only the visible modules.

The visible modules is recording in the ModuleNameSet, this is propagated upwards
whilst compiling and explains which transitive modules are visible from a certain point.
This set is then used to restrict the HUG before the module is compiled to only
the visible modules and thus avoiding this tricky space leak.

Efficiency of the ModuleNameSet is of utmost importance because a union occurs for
each edge in the module graph. Therefore the set is represented directly as an IntSet
which provides suitable performance, even using a UniqSet (which is backed by an IntMap) is
too slow. The crucial test of performance here is the time taken to a do a no-op build in --make mode.

See test "jspace" for an example which used to trigger this problem.

Fixes #21900

- - - - -
1d94a59f by Matthew Pickering at 2022-08-04T13:58:01-04:00
Store interfaces in ModIfaceCache more directly

I realised hydration was completely irrelavant for this cache because
the ModDetails are pruned from the result. So now it simplifies things a
lot to just store the ModIface and Linkable, which we can put into the
cache straight away rather than wait for the final version of a
HomeModInfo to appear.

- - - - -
6c7cd50f by Cheng Shao at 2022-08-04T23:01:45-04:00
cmm: Remove unused ReadOnlyData16

We don't actually emit rodata16 sections anywhere.

- - - - -
16333ad7 by Andreas Klebinger at 2022-08-04T23:02:20-04:00
findExternalRules: Don't needlessly traverse the list of rules.

- - - - -
52c15674 by Krzysztof Gogolewski at 2022-08-05T12:47:05-04:00
Remove backported items from 9.6 release notes

They have been backported to 9.4 in commits 5423d84bd9a28f,
13c81cb6be95c5, 67ccbd6b2d4b9b.

- - - - -
78d232f5 by Matthew Pickering at 2022-08-05T12:47:40-04:00
ci: Fix pages job

The job has been failing because we don't bundle haddock docs anymore in
the docs dist created by hadrian.

Fixes #21789

- - - - -
037bc9c9 by Ben Gamari at 2022-08-05T22:00:29-04:00
codeGen/X86: Don't clobber switch variable in switch generation

Previously ce8745952f99174ad9d3bdc7697fd086b47cdfb5 assumed that it was
safe to clobber the switch variable when generating code for a jump
table since we were at the end of a block. However, this assumption is
wrong; the register could be live in the jump target.

Fixes #21968.

- - - - -
50c8e1c5 by Matthew Pickering at 2022-08-05T22:01:04-04:00
Fix equality operator in jspace test

- - - - -
e9c77a22 by Andreas Klebinger at 2022-08-06T06:13:17-04:00
Improve BUILD_PAP comments

- - - - -
41234147 by Andreas Klebinger at 2022-08-06T06:13:17-04:00
Make dropTail comment a haddock comment

- - - - -
ff11d579 by Andreas Klebinger at 2022-08-06T06:13:17-04:00
Add one more sanity check in stg_restore_cccs

- - - - -
1f6c56ae by Andreas Klebinger at 2022-08-06T06:13:17-04:00
StgToCmm: Fix isSimpleScrut when profiling is enabled.

When profiling is enabled we must enter functions that might represent
thunks in order for their sccs to show up in the profile.

We might allocate even if the function is already evaluated in this
case. So we can't consider any potential function thunk to be a simple
scrut when profiling.

Not doing so caused profiled binaries to segfault.

- - - - -
fab0ee93 by Andreas Klebinger at 2022-08-06T06:13:17-04:00
Change `-fprof-late` to insert cost centres after unfolding creation.

The former behaviour of adding cost centres after optimization but
before unfoldings are created is not available via the flag
`prof-late-inline` instead.

I also reduced the overhead of -fprof-late* by pushing the cost centres
into lambdas. This means the cost centres will only account for
execution of functions and not their partial application.

Further I made LATE_CC cost centres it's own CC flavour so they now
won't clash with user defined ones if a user uses the same string for
a custom scc.

LateCC: Don't put cost centres inside constructor workers.

With -fprof-late they are rarely useful as the worker is usually
inlined. Even if the worker is not inlined or we use -fprof-late-linline
they are generally not helpful but bloat compile and run time
significantly. So we just don't add sccs inside constructor workers.

-------------------------
Metric Decrease:
    T13701
-------------------------

- - - - -
f8bec4e3 by Ben Gamari at 2022-08-06T06:13:53-04:00
gitlab-ci: Fix hadrian bootstrapping of release pipelines

Previously we would attempt to test hadrian bootstrapping in the
`validate` build flavour. However, `ci.sh` refuses to run validation
builds during release pipelines, resulting in job failures. Fix this by
testing bootstrapping in the `release` flavour during release pipelines.

We also attempted to record perf notes for these builds, which is
redundant work and undesirable now since we no longer build in a
consistent flavour.

- - - - -
c0348865 by Ben Gamari at 2022-08-06T11:45:17-04:00
compiler: Eliminate two uses of foldr in favor of foldl'

These two uses constructed maps, which is a case where foldl' is
generally more efficient since we avoid constructing an intermediate
O(n)-depth stack.

- - - - -
d2e4e123 by Ben Gamari at 2022-08-06T11:45:17-04:00
rts: Fix code style

- - - - -
57f530d3 by Ben Gamari at 2022-08-06T11:45:17-04:00
genprimopcode: Drop ArrayArray# references

As ArrayArray# no longer exists

- - - - -
7267cd52 by Ben Gamari at 2022-08-06T11:45:17-04:00
base: Organize Haddocks in GHC.Conc.Sync

- - - - -
aa818a9f by Ben Gamari at 2022-08-06T11:48:50-04:00
Add primop to list threads

A user came to #ghc yesterday wondering how best to check whether they
were leaking threads. We ended up using the eventlog but it seems to me
like it would be generally useful if Haskell programs could query their
own threads.

- - - - -
6d1700b6 by Ben Gamari at 2022-08-06T11:51:35-04:00
rts: Move thread labels into TSO

This eliminates the thread label HashTable and instead tracks this
information in the TSO, allowing us to use proper StgArrBytes arrays for
backing the label and greatly simplifying management of object lifetimes
when we expose them to the user with the coming `threadLabel#` primop.

- - - - -
1472044b by Ben Gamari at 2022-08-06T11:54:52-04:00
Add a primop to query the label of a thread

- - - - -
43f2b271 by Ben Gamari at 2022-08-06T11:55:14-04:00
base: Share finalization thread label

For efficiency's sake we float the thread label assigned to the
finalization thread to the top-level, ensuring that we only need to
encode the label once.

- - - - -
1d63b4fb by Ben Gamari at 2022-08-06T11:57:11-04:00
users-guide: Add release notes entry for thread introspection support

- - - - -
09bca1de by Ben Gamari at 2022-08-07T01:19:35-04:00
hadrian: Fix binary distribution install attributes

Previously we would use plain `cp` to install various parts of the
binary distribution. However, `cp`'s behavior w.r.t. file attributes is
quite unclear; for this reason it is much better to rather use
`install`.

Fixes #21965.

- - - - -
2b8ea16d by Ben Gamari at 2022-08-07T01:19:35-04:00
hadrian: Fix installation of system-cxx-std-lib package conf

- - - - -
7b514848 by Ben Gamari at 2022-08-07T01:20:10-04:00
gitlab-ci: Bump Docker images

To give the ARMv7 job access to lld, fixing #21875.

- - - - -
afa584a3 by Ben Gamari at 2022-08-07T05:08:52-04:00
hadrian: Don't use mk/config.mk.in

Ultimately we want to drop mk/config.mk so here I extract the bits
needed by the Hadrian bindist installation logic into a Hadrian-specific
file. While doing this I fixed binary distribution installation, #21901.

- - - - -
b9bb45d7 by Ben Gamari at 2022-08-07T05:08:52-04:00
hadrian: Fix naming of cross-compiler wrappers

- - - - -
78d04cfa by Ben Gamari at 2022-08-07T11:44:58-04:00
hadrian: Extend xattr Darwin hack to cover /lib

As noted in #21506, it is now necessary to remove extended attributes
from `/lib` as well as `/bin` to avoid SIP issues on Darwin.

Fixes #21506.

- - - - -
20457d77 by Andreas Klebinger at 2022-08-08T14:42:26+02:00
NCG(x86): Compile add+shift as lea if possible.

- - - - -
742292e4 by Andreas Klebinger at 2022-08-08T16:46:37-04:00
dataToTag#: Skip runtime tag check if argument is infered tagged

This addresses one part of #21710.

- - - - -
1504a93e by Cheng Shao at 2022-08-08T16:47:14-04:00
rts: remove redundant stg_traceCcszh

This out-of-line primop has no Haskell wrapper and hasn't been used
anywhere in the tree. Furthermore, the code gets in the way of !7632, so
it should be garbage collected.

- - - - -
a52de3cb by Andreas Klebinger at 2022-08-08T16:47:50-04:00
Document a divergence from the report in parsing function lhss.

GHC is happy to parse `(f) x y = x + y` when it should be a parse error
based on the Haskell report. Seems harmless enough so we won't fix it
but it's documented now.

Fixes #19788

- - - - -
5765e133 by Ben Gamari at 2022-08-08T16:48:25-04:00
gitlab-ci: Add release job for aarch64/debian 11

- - - - -
5b26f324 by Ben Gamari at 2022-08-08T19:39:20-04:00
gitlab-ci: Introduce validation job for aarch64 cross-compilation

Begins to address #11958.

- - - - -
e866625c by Ben Gamari at 2022-08-08T19:39:20-04:00
Bump process submodule

- - - - -
ae707762 by Ben Gamari at 2022-08-08T19:39:20-04:00
gitlab-ci: Add basic support for cross-compiler testiing

Here we add a simple qemu-based test for cross-compilers.

- - - - -
50912d68 by Ben Gamari at 2022-08-08T19:39:57-04:00
rts: Ensure that Array# card arrays are initialized

In #19143 I noticed that newArray# failed to initialize the card table
of newly-allocated arrays. However, embarrassingly, I then only fixed
the issue in newArrayArray# and, in so doing, introduced the potential
for an integer underflow on zero-length arrays (#21962).

Here I fix the issue in newArray#, this time ensuring that we do not
underflow in pathological cases.

Fixes #19143.

- - - - -
e5ceff56 by Ben Gamari at 2022-08-08T19:39:57-04:00
testsuite: Add test for #21962

- - - - -
c1c08bd8 by Ben Gamari at 2022-08-09T02:31:14-04:00
gitlab-ci: Don't use coreutils on Darwin

In general we want to ensure that the tested environment is as similar
as possible to the environment the user will use. In the case of Darwin,
this means we want to use the system's BSD command-line utilities, not
coreutils.

This would have caught #21974.

- - - - -
1c582f44 by Ben Gamari at 2022-08-09T02:31:14-04:00
hadrian: Fix bindist installation on Darwin

It turns out that `cp -P` on Darwin does not always copy a symlink as
a symlink. In order to get these semantics one must pass `-RP`. It's not
entirely clear whether this is valid under POSIX, but it is nevertheless
what Apple does.

- - - - -
681aa076 by Ben Gamari at 2022-08-09T02:31:49-04:00
hadrian: Fix access mode of installed package registration files

Previously hadrian's bindist Makefile would modify package
registrations placed by `install` via a shell pipeline and `mv`.
However, the use of `mv` means that if umask is set then the user may
otherwise end up with package registrations which are inaccessible.
Fix this by ensuring that the mode is 0644.

- - - - -
e9dfd26a by Krzysztof Gogolewski at 2022-08-09T02:32:24-04:00
Cleanups around pretty-printing

* Remove hack when printing OccNames. No longer needed since e3dcc0d5
* Remove unused `pprCmms` and `instance Outputable Instr`
* Simplify `pprCLabel` (no need to pass platform)
* Remove evil `Show`/`Eq` instances for `SDoc`. They were needed by
  ImmLit, but that can take just a String instead.
* Remove instance `Outputable CLabel` - proper output of labels
  needs a platform, and is done by the `OutputableP` instance

- - - - -
66d2e927 by Ben Gamari at 2022-08-09T13:46:48-04:00
rts/linker: Resolve iconv_* on FreeBSD

FreeBSD's libiconv includes an implementation of the
iconv_* functions in libc. Unfortunately these can
only be resolved using dlvsym, which is how the RTS linker
usually resolves such functions. To fix this we include an ad-hoc
special case for iconv_*.

Fixes #20354.

- - - - -
5d66a0ce by Ben Gamari at 2022-08-09T13:46:48-04:00
system-cxx-std-lib: Add support for FreeBSD libcxxrt

- - - - -
ea90e61d by Ben Gamari at 2022-08-09T13:46:48-04:00
gitlab-ci: Bump to use freebsd13 runners

- - - - -
d71a2051 by sheaf at 2022-08-09T13:47:28-04:00
Fix size_up_alloc to account for UnliftedDatatypes

The size_up_alloc function mistakenly considered any type that isn't
lifted to not allocate anything, which is wrong. What we want instead
is to check the type isn't boxed. This accounts for (BoxedRep Unlifted).

Fixes #21939

- - - - -
76b52cf0 by Douglas Wilson at 2022-08-10T06:01:53-04:00
testsuite: 21651 add test for closeFdWith + setNumCapabilities

This bug does not affect windows, which does not use the
base module GHC.Event.Thread.

- - - - -
7589ee72 by Douglas Wilson at 2022-08-10T06:01:53-04:00
base: Fix races in IOManager (setNumCapabilities,closeFdWith)

Fix for #21651

Fixes three bugs:

- writes to eventManager should be atomic. It is accessed concurrently by ioManagerCapabilitiesChanged and closeFdWith.
- The race in closeFdWith described in the ticket.
- A race in getSystemEventManager where it accesses the 'IOArray' in
  'eventManager' before 'ioManagerCapabilitiesChanged' has written to
  'eventManager', causing an Array Index exception. The fix here is to
  'yield' and retry.

- - - - -
dc76439d by Trevis Elser at 2022-08-10T06:02:28-04:00
Updates language extension documentation

Adding a 'Status' field with a few values:
- Deprecated
- Experimental
- InternalUseOnly
- Noting if included in 'GHC2021', 'Haskell2010' or 'Haskell98'

Those values are pulled from the existing descriptions or elsewhere in
the documentation.

While at it, include the :implied by: where appropriate, to provide
more detail.

Fixes #21475

- - - - -
823fe5b5 by Jens Petersen at 2022-08-10T06:03:07-04:00
hadrian RunRest: add type signature for stageNumber

avoids warning seen on 9.4.1:

src/Settings/Builders/RunTest.hs:264:53: warning: [-Wtype-defaults]
    • Defaulting the following constraints to type ‘Integer’
        (Show a0)
          arising from a use of ‘show’
          at src/Settings/Builders/RunTest.hs:264:53-84
        (Num a0)
          arising from a use of ‘stageNumber’
          at src/Settings/Builders/RunTest.hs:264:59-83
    • In the second argument of ‘(++)’, namely
        ‘show (stageNumber (C.stage ctx))’
      In the second argument of ‘($)’, namely
        ‘"config.stage=" ++ show (stageNumber (C.stage ctx))’
      In the expression:
        arg $ "config.stage=" ++ show (stageNumber (C.stage ctx))
    |
264 |             , arg "-e", arg $ "config.stage="    ++ show (stageNumber (C.stage ctx))
    |                                                     ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^

compilation tested locally

- - - - -
f95bbdca by Sylvain Henry at 2022-08-10T09:44:46-04:00
Add support for external static plugins (#20964)

This patch adds a new command-line flag:

  -fplugin-library=<file-path>;<unit-id>;<module>;<args>

used like this:

  -fplugin-library=path/to/plugin.so;package-123;Plugin.Module;["Argument","List"]

It allows a plugin to be loaded directly from a shared library. With
this approach, GHC doesn't compile anything for the plugin and doesn't
load any .hi file for the plugin and its dependencies. As such GHC
doesn't need to support two environments (one for plugins, one for
target code), which was the more ambitious approach tracked in #14335.

Fix #20964

Co-authored-by: Josh Meredith <joshmeredith2008 at gmail.com>

- - - - -
5bc489ca by Ben Gamari at 2022-08-10T09:45:22-04:00
gitlab-ci: Fix ARMv7 build

It appears that the CI refactoring carried out in
5ff690b8474c74e9c968ef31e568c1ad0fe719a1 failed to carry over some
critical configuration: setting the build/host/target platforms and
forcing use of a non-broken linker.

- - - - -
596db9a5 by Ben Gamari at 2022-08-10T09:45:22-04:00
gitlab-ci: Run ARMv7 jobs when ~ARM label is used

- - - - -
7cabea7c by Ben Gamari at 2022-08-10T15:37:58-04:00
hadrian: Don't attempt to install documentation if doc/ doesn't exist

Previously we would attempt to install documentation even if the `doc`
directory doesn't exist (e.g. due to `--docs=none`). This would result
in the surprising side-effect of the entire contents of the bindist
being installed in the destination documentation directory. Fix this.

Fixes #21976.

- - - - -
67575f20 by normalcoder at 2022-08-10T15:38:34-04:00
ncg/aarch64: Don't use x18 register on AArch64/Darwin

Apple's ABI documentation [1] says: "The platforms reserve register x18.
Don’t use this register." While this wasn't problematic in previous
Darwin releases, macOS 13 appears to start zeroing this register
periodically. See #21964.

[1] https://developer.apple.com/documentation/xcode/writing-arm64-code-for-apple-platforms

- - - - -
45eb4cbe by Andreas Klebinger at 2022-08-10T22:41:12-04:00
Note [Trimming auto-rules]: State that this improves compiler perf.

- - - - -
5c24b1b3 by Bodigrim at 2022-08-10T22:41:50-04:00
Document that threadDelay / timeout are susceptible to overflows on 32-bit machines

- - - - -
ff67c79e by Alan Zimmerman at 2022-08-11T16:19:57-04:00
EPA: DotFieldOcc does not have exact print annotations

For the code

    {-# LANGUAGE OverloadedRecordUpdate #-}

    operatorUpdate f = f{(+) = 1}

There are no exact print annotations for the parens around the +
symbol, nor does normal ppr print them.

This MR fixes that.

Closes #21805

Updates haddock submodule

- - - - -
dca43a04 by Matthew Pickering at 2022-08-11T16:20:33-04:00
Revert "gitlab-ci: Add release job for aarch64/debian 11"

This reverts commit 5765e13370634979eb6a0d9f67aa9afa797bee46.

The job was not tested before being merged and fails CI
(https://gitlab.haskell.org/ghc/ghc/-/jobs/1139392)

Ticket #22005

- - - - -
ffc9116e by Eric Lindblad at 2022-08-16T09:01:26-04:00
typo
- - - - -
cd6f5bfd by Ben Gamari at 2022-08-16T09:02:02-04:00
CmmToLlvm: Don't aliasify builtin LLVM variables

Our aliasification logic would previously turn builtin LLVM variables
into aliases, which apparently confuses LLVM. This manifested in
initializers failing to be emitted, resulting in many profiling failures
with the LLVM backend.

Fixes #22019.

- - - - -
dc7da356 by Bryan Richter at 2022-08-16T09:02:38-04:00
run_ci: remove monoidal-containers

Fixes #21492

MonoidalMap is inlined and used to implement Variables, as before.

The top-level value "jobs" is reimplemented as a regular Map, since it
doesn't use the monoidal union anyway.

- - - - -
64110544 by Cheng Shao at 2022-08-16T09:03:15-04:00
CmmToAsm/AArch64: correct a typo

- - - - -
f6a5524a by Andreas Klebinger at 2022-08-16T14:34:11-04:00
Fix #21979 - compact-share failing with -O

I don't have good reason to believe the optimization level should affect
if sharing works or not here. So limit the test to the normal way.

- - - - -
68154a9d by Ben Gamari at 2022-08-16T14:34:47-04:00
users-guide: Fix reference to dead llvm-version substitution

Fixes #22052.

- - - - -
28c60d26 by Ben Gamari at 2022-08-16T14:34:47-04:00
users-guide: Fix incorrect reference to `:extension: role

- - - - -
71102c8f by Ben Gamari at 2022-08-16T14:34:47-04:00
users-guide: Add :ghc-flag: reference

- - - - -
385f420b by Ben Gamari at 2022-08-16T14:34:47-04:00
hadrian: Place manpage in docroot

This relocates it from docs/ to doc/

- - - - -
84598f2e by Ben Gamari at 2022-08-16T14:34:47-04:00
Bump haddock submodule

Includes merge of `main` into `ghc-head` as well as some Haddock users
guide fixes.

- - - - -
59ce787c by Ben Gamari at 2022-08-16T14:34:47-04:00
base: Add changelog entries from ghc-9.2

Closes #21922.

- - - - -
a14e6ae3 by Ben Gamari at 2022-08-16T14:34:47-04:00
relnotes: Add "included libraries" section

As noted in #21988, some users rely on this.

- - - - -
a4212edc by Ben Gamari at 2022-08-16T14:34:47-04:00
users-guide: Rephrase the rewrite rule documentation

Previously the wording was a tad unclear. Fix this.

Closes #21114.

- - - - -
3e493dfd by Peter Becich at 2022-08-17T08:43:21+01:00
Implement Response File support for HPC

This is an improvement to HPC authored by Richard Wallace
(https://github.com/purefn) and myself. I have received permission from
him to attempt to upstream it. This improvement was originally
implemented as a patch to HPC via input-output-hk/haskell.nix:
https://github.com/input-output-hk/haskell.nix/pull/1464

Paraphrasing Richard, HPC currently requires all inputs as command line arguments.
With large projects this can result in an argument list too long error.
I have only seen this error in Nix, but I assume it can occur is a plain Unix environment.

This MR adds the standard response file syntax support to HPC. For
example you can now pass a file to the command line which contains the
arguments.

```
hpc @response_file_1 @response_file_2 ...

The contents of a Response File must have this format:
COMMAND ...

example:
report my_library.tix --include=ModuleA --include=ModuleB
```

Updates hpc submodule

Co-authored-by:  Richard Wallace <rwallace at thewallacepack.net>

Fixes #22050

- - - - -
436867d6 by Matthew Pickering at 2022-08-18T09:24:08-04:00
ghc-heap: Fix decoding of TSO closures

An extra field was added to the TSO structure in 6d1700b6 but the
decoding logic in ghc-heap was not updated for this new field.

Fixes #22046

- - - - -
a740a4c5 by Matthew Pickering at 2022-08-18T09:24:44-04:00
driver: Honour -x option

The -x option is used to manually specify which phase a file should be
started to be compiled from (even if it lacks the correct extension). I
just failed to implement this when refactoring the driver.

In particular Cabal calls GHC with `-E -cpp -x hs Foo.cpphs` to
preprocess source files using GHC.

I added a test to exercise this case.

Fixes #22044

- - - - -
e293029d by Simon Peyton Jones at 2022-08-18T09:25:19-04:00
Be more careful in chooseInferredQuantifiers

This fixes #22065. We were failing to retain a quantifier that
was mentioned in the kind of another retained quantifier.

Easy to fix.

- - - - -
714c936f by Bryan Richter at 2022-08-18T18:37:21-04:00
testsuite: Add test for #21583

- - - - -
989b844d by Ben Gamari at 2022-08-18T18:37:57-04:00
compiler: Drop --build-id=none hack

Since 2011 the object-joining implementation has had a hack to pass
`--build-id=none` to `ld` when supported, seemingly to work around a
linker bug. This hack is now unnecessary and may break downstream users
who expect objects to have valid build-ids. Remove it.

Closes #22060.

- - - - -
519c712e by Matthew Pickering at 2022-08-19T00:09:11-04:00
Make ru_fn field strict to avoid retaining Ids

It's better to perform this projection from Id to Name strictly so we
don't retain an old Id (hence IdInfo, hence Unfolding, hence everything
etc)

- - - - -
7dda04b0 by Matthew Pickering at 2022-08-19T00:09:11-04:00
Force `getOccFS bndr` to avoid retaining reference to Bndr.

This is another symptom of #19619

- - - - -
4303acba by Matthew Pickering at 2022-08-19T00:09:11-04:00
Force unfoldings when they are cleaned-up in Tidy and CorePrep

If these thunks are not forced then the entire unfolding for the binding
is live throughout the whole of CodeGen despite the fact it should have
been discarded.

Fixes #22071

- - - - -
2361b3bc by Matthew Pickering at 2022-08-19T00:09:47-04:00
haddock docs: Fix links from identifiers to dependent packages

When implementing the base_url changes I made the pretty bad mistake of
zipping together two lists which were in different orders. The simpler
thing to do is just modify `haddockDependencies` to also return the
package identifier so that everything stays in sync.

Fixes #22001

- - - - -
9a7e2ea1 by Matthew Pickering at 2022-08-19T00:10:23-04:00
Revert "Refactor SpecConstr to use treat bindings uniformly"

This reverts commit 415468fef8a3e9181b7eca86de0e05c0cce31729.

This refactoring introduced quite a severe residency regression (900MB
live from 650MB live when compiling mmark), see #21993 for a reproducer
and more discussion.

Ticket #21993

- - - - -
9789e845 by Zachary Wood at 2022-08-19T14:17:28-04:00
tc: warn about lazy annotations on unlifted arguments (fixes #21951)

- - - - -
e5567289 by Andreas Klebinger at 2022-08-19T14:18:03-04:00
Fix #22048 where we failed to drop rules for -fomit-interface-pragmas.

Now we also filter the local rules (again) which fixes the issue.

- - - - -
51ffd009 by Swann Moreau at 2022-08-19T18:29:21-04:00
Print constraints in quotes (#21167)

This patch improves the uniformity of error message formatting by
printing constraints in quotes, as we do for types.

Fix #21167

- - - - -
ab3e0f5a by Sasha Bogicevic at 2022-08-19T18:29:57-04:00
19217 Implicitly quantify type variables in :kind command

- - - - -
9939e95f by MorrowM at 2022-08-21T16:51:38-04:00
Recognize file-header pragmas in GHCi (#21507)

- - - - -
fb7c2d99 by Matthew Pickering at 2022-08-21T16:52:13-04:00
hadrian: Fix bootstrapping with ghc-9.4

The error was that we were trying to link together

    containers from boot package library (which depends template-haskell in boot package library)
    template-haskell from in-tree package database

So the fix is to build containers in stage0 (and link against template-haskell built in stage0).

Fixes #21981

- - - - -
b946232c by Mario Blažević at 2022-08-22T22:06:21-04:00
Added pprType with precedence argument, as a prerequisite to fix issues #21723 and #21942.

* refines the precedence levels, adding `qualPrec` and `funPrec` to better control parenthesization
* `pprParendType`, `pprFunArgType`, and `instance Ppr Type` all just call `pprType` with proper precedence
* `ParensT` constructor is now always printed parenthesized
* adds the precedence argument to `pprTyApp` as well, as it needs to keep track and pass it down
* using `>=` instead of former `>` to match the Core type printing logic
* some test outputs have changed, losing extraneous parentheses

- - - - -
fe4ff0f7 by Mario Blažević at 2022-08-22T22:06:21-04:00
Fix and test for issue #21723

- - - - -
33968354 by Mario Blažević at 2022-08-22T22:06:21-04:00
Test for issue #21942

- - - - -
c9655251 by Mario Blažević at 2022-08-22T22:06:21-04:00
Updated the changelog

- - - - -
80102356 by Ben Gamari at 2022-08-22T22:06:57-04:00
hadrian: Don't duplicate binaries on installation

Previously we used `install` on symbolic links, which ended up
copying the target file rather than installing a symbolic link.

Fixes #22062.

- - - - -
b929063e by M Farkas-Dyck at 2022-08-24T02:37:01-04:00
Unbreak Haddock comments in `GHC.Core.Opt.WorkWrap.Utils`.

Closes #22092.

- - - - -
112e4f9c by Cheng Shao at 2022-08-24T02:37:38-04:00
driver: don't actually merge objects when ar -L works

- - - - -
a9f0e68e by Ben Gamari at 2022-08-24T02:38:13-04:00
rts: Consistently use MiB in stats output

Previously we would say `MB` even where we
meant `MiB`.
- - - - -
a90298cc by Simon Peyton Jones at 2022-08-25T08:38:16+01:00
Fix arityType: -fpedantic-bottoms, join points, etc

This MR fixes #21694, #21755.  It also makes sure that #21948 and
fix to #21694.

* For #21694 the underlying problem was that we were calling arityType
  on an expression that had free join points.  This is a Bad Bad Idea.
  See Note [No free join points in arityType].

* To make "no free join points in arityType" work out I had to avoid
  trying to use eta-expansion for runRW#. This entailed a few changes
  in the Simplifier's treatment of runRW#.  See
  GHC.Core.Opt.Simplify.Iteration Note [No eta-expansion in runRW#]

* I also made andArityType work correctly with -fpedantic-bottoms;
  see Note [Combining case branches: andWithTail].

* Rewrote Note [Combining case branches: optimistic one-shot-ness]

* arityType previously treated join points differently to other
  let-bindings. This patch makes them unform; arityType analyses
  the RHS of all bindings to get its ArityType, and extends am_sigs.

  I realised that, now we have am_sigs giving the ArityType for
  let-bound Ids, we don't need the (pre-dating) special code in
  arityType for join points. But instead we need to extend the env for
  Rec bindings, which weren't doing before.  More uniform now.  See
  Note [arityType for let-bindings].

  This meant we could get rid of ae_joins, and in fact get rid of
  EtaExpandArity altogether.  Simpler.

* And finally, it was the strange treatment of join-point Ids in
  arityType (involving a fake ABot type) that led to a serious bug:
  #21755.  Fixed by this refactoring, which treats them uniformly;
  but without breaking #18328.

  In fact, the arity for recursive join bindings is pretty tricky;
  see the long Note [Arity for recursive join bindings]
  in GHC.Core.Opt.Simplify.Utils.  That led to more refactoring,
  including deciding that an Id could have an Arity that is bigger
  than its JoinArity; see Note [Invariants on join points], item
  2(b) in GHC.Core

* Make sure that the "demand threshold" for join points in DmdAnal
  is no bigger than the join-arity.  In GHC.Core.Opt.DmdAnal see
  Note [Demand signatures are computed for a threshold arity based on idArity]

* I moved GHC.Core.Utils.exprIsDeadEnd into GHC.Core.Opt.Arity,
  where it more properly belongs.

* Remove an old, redundant hack in FloatOut.  The old Note was
  Note [Bottoming floats: eta expansion] in GHC.Core.Opt.SetLevels.

Compile time improves very slightly on average:

Metrics: compile_time/bytes allocated
---------------------------------------------------------------------------------------
  T18223(normal) ghc/alloc    725,808,720    747,839,216  +3.0%  BAD
  T6048(optasm)  ghc/alloc    105,006,104    101,599,472  -3.2% GOOD
  geo. mean                                          -0.2%
  minimum                                            -3.2%
  maximum                                            +3.0%

For some reason Windows was better

   T10421(normal) ghc/alloc    125,888,360    124,129,168  -1.4% GOOD
   T18140(normal) ghc/alloc     85,974,520     83,884,224  -2.4% GOOD
  T18698b(normal) ghc/alloc    236,764,568    234,077,288  -1.1% GOOD
   T18923(normal) ghc/alloc     75,660,528     73,994,512  -2.2% GOOD
    T6048(optasm) ghc/alloc    112,232,512    108,182,520  -3.6% GOOD
  geo. mean                                          -0.6%

I had a quick look at T18223 but it is knee deep in coercions and
the size of everything looks similar before and after.  I decided
to accept that 3% increase in exchange for goodness elsewhere.

Metric Decrease:
    T10421
    T18140
    T18698b
    T18923
    T6048

Metric Increase:
    T18223

- - - - -
909edcfc by Ben Gamari at 2022-08-25T10:03:34-04:00
upload_ghc_libs: Add means of passing Hackage credentials

- - - - -
28402eed by M Farkas-Dyck at 2022-08-25T10:04:17-04:00
Scrub some partiality in `CommonBlockElim`.

- - - - -
54affbfa by Ben Gamari at 2022-08-25T20:05:31-04:00
hadrian: Fix whitespace

Previously this region of Settings.Packages was incorrectly indented.

- - - - -
c4bba0f0 by Ben Gamari at 2022-08-25T20:05:31-04:00
validate: Drop --legacy flag

In preparation for removal of the legacy `make`-based build system.

- - - - -
822b0302 by Ben Gamari at 2022-08-25T20:05:31-04:00
gitlab-ci: Drop make build validation jobs

In preparation for removal of the `make`-based build system

- - - - -
6fd9b0a1 by Ben Gamari at 2022-08-25T20:05:31-04:00
Drop make build system

Here we at long last remove the `make`-based build system, it having
been replaced with the Shake-based Hadrian build system. Users are
encouraged to refer to the documentation in `hadrian/doc` and this [1]
blog post for details on using Hadrian.

Closes #17527.

[1] https://www.haskell.org/ghc/blog/20220805-make-to-hadrian.html

- - - - -
dbb004b0 by Ben Gamari at 2022-08-25T20:05:31-04:00
Remove testsuite/tests/perf/haddock/.gitignore

As noted in #16802, this is no longer needed.

Closes #16802.

- - - - -
fe9d824d by Ben Gamari at 2022-08-25T20:05:31-04:00
Drop hc-build script

This has not worked for many, many years and relied on the now-removed
`make`-based build system.

- - - - -
659502bc by Ben Gamari at 2022-08-25T20:05:31-04:00
Drop mkdirhier

This is only used by nofib's dead `dist` target

- - - - -
4a426924 by Ben Gamari at 2022-08-25T20:05:31-04:00
Drop mk/{build,install,config}.mk.in

- - - - -
46924b75 by Ben Gamari at 2022-08-25T20:05:31-04:00
compiler: Drop comment references to make

- - - - -
d387f687 by Harry Garrood at 2022-08-25T20:06:10-04:00
Add inits1 and tails1 to Data.List.NonEmpty

See https://github.com/haskell/core-libraries-committee/issues/67

- - - - -
8603c921 by Harry Garrood at 2022-08-25T20:06:10-04:00
Add since annotations and changelog entries

- - - - -
6b47aa1c by Krzysztof Gogolewski at 2022-08-25T20:06:46-04:00
Fix redundant import

This fixes a build error on x86_64-linux-alpine3_12-validate.
See the function 'loadExternalPlugins' defined in this file.

- - - - -
4786acf7 by sheaf at 2022-08-26T15:05:23-04:00
Pmc: consider any 2 dicts of the same type equal

This patch massages the keys used in the `TmOracle` `CoreMap` to ensure
that dictionaries of coherent classes give the same key.
That is, whenever we have an expression we want to insert or lookup in
the `TmOracle` `CoreMap`, we first replace any dictionary
`$dict_abcd :: ct` with a value of the form `error @ct`.

This allows us to common-up view pattern functions with required
constraints whose arguments differed only in the uniques of the
dictionaries they were provided, thus fixing #21662.

This is a rather ad-hoc change to the keys used in the
`TmOracle` `CoreMap`. In the long run, we would probably want to use
a different representation for the keys instead of simply using
`CoreExpr` as-is. This more ambitious plan is outlined in #19272.

Fixes #21662
Updates unix submodule

- - - - -
f5e0f086 by Krzysztof Gogolewski at 2022-08-26T15:06:01-04:00
Remove label style from printing context

Previously, the SDocContext used for code generation contained
information whether the labels should use Asm or C style.
However, at every individual call site, this is known statically.
This removes the parameter to 'PprCode' and replaces every 'pdoc'
used to print a label in code style with 'pprCLabel' or 'pprAsmLabel'.
The OutputableP instance is now used only for dumps.

The output of T15155 changes, it now uses the Asm style
(which is faithful to what actually happens).

- - - - -
1007829b by Cheng Shao at 2022-08-26T15:06:40-04:00
boot: cleanup legacy args

Cleanup legacy boot script args, following removal of the legacy make
build system.

- - - - -
95fe09da by Simon Peyton Jones at 2022-08-27T00:29:02-04:00
Improve SpecConstr for evals

As #21763 showed, we were over-specialising in some cases, when
the function involved was doing a simple 'eval', but not taking
the value apart, or branching on it.

This MR fixes the problem.  See Note [Do not specialise evals].

Nofib barely budges, except that spectral/cichelli allocates about
3% less.

Compiler bytes-allocated improves a bit
   geo. mean                                          -0.1%
   minimum                                            -0.5%
   maximum                                            +0.0%

The -0.5% is on T11303b, for what it's worth.

- - - - -
565a8ec8 by Matthew Pickering at 2022-08-27T00:29:39-04:00
Revert "Revert "Refactor SpecConstr to use treat bindings uniformly""

This reverts commit 851d8dd89a7955864b66a3da8b25f1dd88a503f8.

This commit was originally reverted due to an increase in space usage.
This was diagnosed as because the SCE increased in size and that was
being retained by another leak. See #22102

- - - - -
82ce1654 by Matthew Pickering at 2022-08-27T00:29:39-04:00
Avoid retaining bindings via ModGuts held on the stack

It's better to overwrite the bindings fields of the ModGuts before
starting an iteration as then all the old bindings can be collected as
soon as the simplifier has processed them. Otherwise we end up with the
old bindings being alive until right at the end of the simplifier pass
as the mg_binds field is only modified right at the end.

- - - - -
64779dcd by Matthew Pickering at 2022-08-27T00:29:39-04:00
Force imposs_deflt_cons in filterAlts

This fixes a pretty serious space leak as the forced thunk would retain
`Alt b` values which would then contain reference to a lot of old
bindings and other simplifier gunk.

The OtherCon unfolding was not forced on subsequent simplifier runs so
more and more old stuff would be retained until the end of
simplification.

Fixing this has a drastic effect on maximum residency for the mmark
package which goes from

```
  45,005,401,056 bytes allocated in the heap
  17,227,721,856 bytes copied during GC
     818,281,720 bytes maximum residency (33 sample(s))
       9,659,144 bytes maximum slop
            2245 MiB total memory in use (0 MB lost due to fragmentation)
```

to

```
  45,039,453,304 bytes allocated in the heap
  13,128,181,400 bytes copied during GC
     331,546,608 bytes maximum residency (40 sample(s))
       7,471,120 bytes maximum slop
             916 MiB total memory in use (0 MB lost due to fragmentation)
```

See #21993 for some more discussion.

- - - - -
a3b23a33 by Matthew Pickering at 2022-08-27T00:29:39-04:00
Use Solo to avoid retaining the SCE but to avoid performing the substitution

The use of Solo here allows us to force the selection into the SCE to obtain
the Subst but without forcing the substitution to be applied. The resulting thunk
is placed into a lazy field which is rarely forced, so forcing it regresses
peformance.

- - - - -
161a6f1f by Simon Peyton Jones at 2022-08-27T00:30:14-04:00
Fix a nasty loop in Tidy

As the remarkably-simple #22112 showed, we were making a black hole
in the unfolding of a self-recursive binding.  Boo!

It's a bit tricky.  Documented in GHC.Iface.Tidy,
   Note [tidyTopUnfolding: avoiding black holes]

- - - - -
68e6786f by Giles Anderson at 2022-08-29T00:01:35+02:00
Use TcRnDiagnostic in GHC.Tc.TyCl.Class (#20117)

The following `TcRnDiagnostic` messages have been introduced:

TcRnIllegalHsigDefaultMethods
TcRnBadGenericMethod
TcRnWarningMinimalDefIncomplete
TcRnDefaultMethodForPragmaLacksBinding
TcRnIgnoreSpecialisePragmaOnDefMethod
TcRnBadMethodErr
TcRnNoExplicitAssocTypeOrDefaultDeclaration

- - - - -
cbe51ac5 by Simon Peyton Jones at 2022-08-29T04:18:57-04:00
Fix a bug in anyInRnEnvR

This bug was a subtle error in anyInRnEnvR, introduced by

    commit d4d3fe6e02c0eb2117dbbc9df72ae394edf50f06
    Author: Andreas Klebinger <klebinger.andreas at gmx.at>
    Date:   Sat Jul 9 01:19:52 2022 +0200

    Rule matching: Don't compute the FVs if we don't look at them.

The net result was #22028, where a rewrite rule would wrongly
match on a lambda.

The fix to that function is easy.

- - - - -
0154bc80 by sheaf at 2022-08-30T06:05:41-04:00
Various Hadrian bootstrapping fixes

  - Don't always produce a distribution archive (#21629)
  - Use correct executable names for ghc-pkg and hsc2hs on windows
    (we were missing the .exe file extension)
  - Fix a bug where we weren't using the right archive format on Windows
    when unpacking the bootstrap sources.

Fixes #21629

- - - - -
451b1d90 by Matthew Pickering at 2022-08-30T06:06:16-04:00
ci: Attempt using normal submodule cloning strategy

We do not use any recursively cloned submodules, and this protects us
from flaky upstream remotes.

Fixes #22121

- - - - -
9d5ad7c4 by Pi Delport at 2022-08-30T22:40:46+00:00
Fix typo in Any docs: stray "--"

- - - - -
3a002632 by Pi Delport at 2022-08-30T22:40:46+00:00
Fix typo in Any docs: syntatic -> syntactic

- - - - -
7f490b13 by Simon Peyton Jones at 2022-08-31T03:53:54-04:00
Add a missing trimArityType

This buglet was exposed by #22114, a consequence of my earlier
refactoring of arity for join points.

- - - - -
e6fc820f by Ben Gamari at 2022-08-31T13:16:01+01:00
Bump binary submodule to 0.8.9.1

- - - - -
4c1e7b22 by Ben Gamari at 2022-08-31T13:16:01+01:00
Bump stm submodule to 2.5.1.0

- - - - -
837472b4 by Ben Gamari at 2022-08-31T13:16:01+01:00
users-guide: Document system-cxx-std-lib

- - - - -
f7a9947a by Douglas Wilson at 2022-08-31T13:16:01+01:00
Update submodule containers to 0.6.6

- - - - -
4ab1c2ca by Douglas Wilson at 2022-08-31T13:16:02+01:00
Update submodule process to 1.6.15.0

- - - - -
1309ea1e by Ben Gamari at 2022-08-31T13:16:02+01:00
Bump directory submodule to 1.3.7.1

- - - - -
7962a33a by Douglas Wilson at 2022-08-31T13:16:02+01:00
Bump text submodule to 2.0.1

- - - - -
fd8d80c3 by Ben Gamari at 2022-08-31T13:26:52+01:00
Bump deepseq submodule to 1.4.8.0

- - - - -
a9baafac by Ben Gamari at 2022-08-31T13:26:52+01:00
Add dates to base, ghc-prim changelogs

- - - - -
2cee323c by Ben Gamari at 2022-08-31T13:26:52+01:00
Update autoconf scripts

Scripts taken from autoconf 02ba26b218d3d3db6c56e014655faf463cefa983

- - - - -
e62705ff by Ben Gamari at 2022-08-31T13:26:53+01:00
Bump bytestring submodule to 0.11.3.1

- - - - -
f7b4dcbd by Douglas Wilson at 2022-08-31T13:26:53+01:00
Update submodule Cabal to tag Cabal-v3.8.1.0

closes #21931

- - - - -
e8eaf807 by Matthew Pickering at 2022-08-31T18:27:57-04:00
Refine in-tree compiler args for --test-compiler=stage1

Some of the logic to calculate in-tree arguments was not correct for the
stage1 compiler. Namely we were not correctly reporting whether we were
building static or dynamic executables and whether debug assertions were
enabled.

Fixes #22096

- - - - -
6b2f7ffe by Matthew Pickering at 2022-08-31T18:27:57-04:00
Make ghcDebugAssertions into a Stage predicate (Stage -> Bool)

We also care whether we have debug assertions enabled for a stage one
compiler, but the way which we turned on the assertions was quite
different from the stage2 compiler. This makes the logic for turning on
consistent across both and has the advantage of being able to correct
determine in in-tree args whether a flavour enables assertions or not.

Ticket #22096

- - - - -
15111af6 by Zubin Duggal at 2022-09-01T01:18:50-04:00
Add regression test for #21550

This was fixed by ca90ffa321a31842a32be1b5b6e26743cd677ec5
"Use local instances with least superclass depth"

- - - - -
7d3a055d by Krzysztof Gogolewski at 2022-09-01T01:19:26-04:00
Minor cleanup

- Remove mkHeteroCoercionType, sdocImpredicativeTypes, isStateType (unused),
  isCoVar_maybe (duplicated by getCoVar_maybe)
- Replace a few occurrences of voidPrimId with (# #).
  void# is a deprecated synonym for the unboxed tuple.
- Use showSDoc in :show linker.
  This makes it consistent with the other :show commands

- - - - -
31a8989a by Tommy Bidne at 2022-09-01T12:01:20-04:00
Change Ord defaults per CLC proposal

Approved by CLC in https://github.com/haskell/core-libraries-committee/issues/24#issuecomment-1233331267

- - - - -
7f527f01 by Matthew Pickering at 2022-09-01T12:01:56-04:00
Fix bootstrap with ghc-9.0

It turns out Solo is a very recent addition to base, so for older GHC
versions we just defined it inline here the one place we use it in the
compiler.

- - - - -
d2be80fd by Sebastian Graf at 2022-09-05T23:12:14-04:00
DmdAnal: Don't panic in addCaseBndrDmd (#22039)

Rather conservatively return Top.
See Note [Untyped demand on case-alternative binders].

I also factored `addCaseBndrDmd` into two separate functions `scrutSubDmd` and
`fieldBndrDmds`.

Fixes #22039.

- - - - -
25f68ace by Ben Gamari at 2022-09-05T23:12:50-04:00
gitlab-ci: Ensure that ghc derivation is in scope

Previously the lint-ci job attempted to use cabal-install (specifically
`cabal update`) without a GHC in PATH. However, cabal-install-3.8
appears to want GHC, even for `cabal update`.

- - - - -
f37b621f by sheaf at 2022-09-06T11:51:53+00:00
Update instances.rst, clarifying InstanceSigs

Fixes #22103

- - - - -
d4f908f7 by Jan Hrček at 2022-09-06T15:36:58-04:00
Fix :add docs in user guide

- - - - -
808bb793 by Cheng Shao at 2022-09-06T15:37:35-04:00
ci: remove unused build_make/test_make in ci script

- - - - -
d0a2efb2 by Eric Lindblad at 2022-09-07T16:42:45-04:00
typo
- - - - -
fac0098b by Eric Lindblad at 2022-09-07T16:42:45-04:00
typos

- - - - -
a581186f by Eric Lindblad at 2022-09-07T16:42:45-04:00
whitespace

- - - - -
04a738cb by Cheng Shao at 2022-09-07T16:43:22-04:00
CmmToAsm: remove unused ModLocation from NatM_State

- - - - -
ee1cfaa9 by Krzysztof Gogolewski at 2022-09-07T16:43:58-04:00
Minor SDoc cleanup

Change calls to renderWithContext with showSDocOneLine; it's more
efficient and explanatory.

Remove polyPatSig (unused)

- - - - -
7918265d by Krzysztof Gogolewski at 2022-09-07T16:43:58-04:00
Remove Outputable Char instance

Use 'text' instead of 'ppr'.
Using 'ppr' on the list "hello" rendered as "h,e,l,l,o".

- - - - -
77209ab3 by Georgi Lyubenov at 2022-09-08T17:14:36+03:00
Export liftA2 from Prelude

Changes:
In order to be warning free and compatible, we hide Applicative(..)
from Prelude in a few places and instead import it directly from
Control.Applicative.
Please see the migration guide at
https://github.com/haskell/core-libraries-committee/blob/main/guides/export-lifta2-prelude.md
for more details.

This means that Applicative is now exported in its entirety from
Prelude.

Motivation:

This change is motivated by a few things:
* liftA2 is an often used function, even more so than (<*>) for some
  people.
* When implementing Applicative, the compiler will prompt you for either
  an implementation of (<*>) or of liftA2, but trying to use the latter
  ends with an error, without further imports. This could be confusing
  for newbies.
* For teaching, it is often times easier to introduce liftA2 first,
  as it is a natural generalisation of fmap.
* This change seems to have been unanimously and enthusiastically
  accepted by the CLC members, possibly indicating a lot of love for it.
* This change causes very limited breakage, see the linked issue below
  for an investigation on this.

See https://github.com/haskell/core-libraries-committee/issues/50
for the surrounding discussion and more details.

- - - - -
442a94e8 by Georgi Lyubenov at 2022-09-08T17:14:36+03:00
Add changelog entry for liftA2 export from Prelude

- - - - -
fb968680 by Georgi Lyubenov at 2022-09-08T17:14:36+03:00
Bump submodule containers to one with liftA2 warnings fixed

- - - - -
f54ff818 by Georgi Lyubenov at 2022-09-08T17:14:36+03:00
Bump submodule Cabal to one with liftA2 warnings fixed

- - - - -
a4b34808 by Georgi Lyubenov at 2022-09-08T17:14:36+03:00
Isolate some Applicative hidings to GHC.Prelude

By reexporting the entirety of Applicative from GHC.Prelude, we can save
ourselves some `hiding` and importing of `Applicative` in consumers of GHC.Prelude.
This also has the benefit of isolating this type of change to
GHC.Prelude, so that people in the future don't have to think about it.

- - - - -
9c4ea90c by Cheng Shao at 2022-09-08T17:49:47-04:00
CmmToC: enable 64-bit CallishMachOp on 32-bit targets

Normally, the unregisterised builds avoid generating 64-bit
CallishMachOp in StgToCmm, so CmmToC doesn't support these. However,
there do exist cases where we'd like to invoke cmmToC for other cmm
inputs which may contain such CallishMachOps, and it's a rather low
effort to add support for these since they only require calling into
existing ghc-prim cbits.

- - - - -
04062510 by Alexis King at 2022-09-11T11:30:32+02:00
Add native delimited continuations to the RTS

This patch implements GHC proposal 313, "Delimited continuation
primops", by adding native support for delimited continuations to the
GHC RTS.

All things considered, the patch is relatively small. It almost
exclusively consists of changes to the RTS; the compiler itself is
essentially unaffected. The primops come with fairly extensive Haddock
documentation, and an overview of the implementation strategy is given
in the Notes in rts/Continuation.c.

This first stab at the implementation prioritizes simplicity over
performance. Most notably, every continuation is always stored as a
single, contiguous chunk of stack. If one of these chunks is
particularly large, it can result in poor performance, as the current
implementation does not attempt to cleverly squeeze a subset of the
stack frames into the existing stack: it must fit all at once. If this
proves to be a performance issue in practice, a cleverer strategy would
be a worthwhile target for future improvements.

- - - - -
ee471dfb by Cheng Shao at 2022-09-12T07:07:33-04:00
rts: fix missing dirty_MVAR argument in stg_writeIOPortzh

- - - - -
a5f9c35f by Cheng Shao at 2022-09-12T13:29:05-04:00
ci: enable parallel compression for xz

- - - - -
3a815f30 by Ryan Scott at 2022-09-12T13:29:41-04:00
Windows: Always define _UCRT when compiling C code

As seen in #22159, this is required to ensure correct behavior when MinGW-w64
headers are in the `C_INCLUDE_PATH`.

Fixes #22159.

- - - - -
65a0bd69 by sheaf at 2022-09-13T10:27:52-04:00
Add diagnostic codes

This MR adds diagnostic codes, assigning unique numeric codes to
error and warnings, e.g.

  error: [GHC-53633]
  Pattern match is redundant

This is achieved as follows:

  - a type family GhcDiagnosticCode that gives the diagnostic code
    for each diagnostic constructor,
  - a type family ConRecursInto that specifies whether to recur into
    an argument of the constructor to obtain a more fine-grained code
    (e.g. different error codes for different 'deriving' errors),
  - generics machinery to generate the value-level function assigning
    each diagnostic its error code; see Note [Diagnostic codes using generics]
    in GHC.Types.Error.Codes.

The upshot is that, to add a new diagnostic code, contributors only need
to modify the two type families mentioned above. All logic relating to
diagnostic codes is thus contained to the GHC.Types.Error.Codes module,
with no code duplication.

This MR also refactors error message datatypes a bit, ensuring we can
derive Generic for them, and cleans up the logic around constraint
solver reports by splitting up 'TcSolverReportInfo' into separate
datatypes (see #20772).

Fixes #21684

- - - - -
362cca13 by sheaf at 2022-09-13T10:27:53-04:00
Diagnostic codes: acccept test changes

The testsuite output now contains diagnostic codes, so many tests need
to be updated at once.
We decided it was best to keep the diagnostic codes in the testsuite
output, so that contributors don't inadvertently make changes to the
diagnostic codes.

- - - - -
08f6730c by Adam Gundry at 2022-09-13T10:28:29-04:00
Allow imports to reference multiple fields with the same name (#21625)

If a module `M` exports two fields `f` (using DuplicateRecordFields), we can
still accept

    import M (f)
    import M hiding (f)

and treat `f` as referencing both of them.  This was accepted in GHC 9.0, but gave
rise to an ambiguity error in GHC 9.2.  See #21625.

This patch also documents this behaviour in the user's guide, and updates the
test for #16745 which is now treated differently.

- - - - -
c14370d7 by Cheng Shao at 2022-09-13T10:29:07-04:00
ci: remove unused appveyor config

- - - - -
dc6af9ed by Cheng Shao at 2022-09-13T10:29:45-04:00
compiler: remove unused lazy state monad

- - - - -
646d15ad by Eric Lindblad at 2022-09-14T03:13:56-04:00
Fix typos

This fixes various typos and spelling mistakes
in the compiler.

Fixes #21891

- - - - -
7d7e71b0 by Matthew Pickering at 2022-09-14T03:14:32-04:00
hadrian: Bump index state

This bumps the index state so a build plan can also be found when
booting with 9.4.

Fixes #22165

- - - - -
98b62871 by Matthew Pickering at 2022-09-14T17:17:04-04:00
hadrian: Use a stamp file to record when a package is built in a certain way

Before this patch which library ways we had built wasn't recorded
directly. So you would run into issues if you build the .conf file with
some library ways before switching the library ways which you wanted to
build.

Now there is one stamp file for each way, so in order to build a
specific way you can need that specific stamp file rather than going
indirectly via the .conf file.

- - - - -
b42cedbe by Matthew Pickering at 2022-09-14T17:17:04-04:00
hadrian: Inplace/Final package databases

There are now two different package databases per stage. An inplace
package database contains .conf files which point directly into the
build directories. The final package database contains .conf files which
point into the installed locations. The inplace .conf files are created
before any building happens and have fake ABI hash values. The final
.conf files are created after a package finished building and contains
the proper ABI has.

The motivation for this is to make the dependency structure more
fine-grained when building modules. Now a module depends just depends
directly on M.o from package p rather than the .conf file depend on the
.conf file for package p. So when all of a modules direct dependencies
have finished building we can start building it rather than waiting for
the whole package to finish.

The secondary motivation is that the multi-repl doesn't need to build
everything before starting the multi-repl session. We can just configure
the inplace package-db and use that in order to start the repl.

- - - - -
6515c32b by Matthew Pickering at 2022-09-14T17:17:04-04:00
hadrian: Add some more packages to multi-cradle

The main improvement here is to pass `-this-unit-id` for executables so
that they can be added to the multi-cradle if desired as well as normal
library packages.

- - - - -
e470e91f by Matthew Pickering at 2022-09-14T17:17:04-04:00
hadrian: Need builders needed by Cabal Configure in parallel

Because of the use of withStaged (which needs the necessary builder)
when configuring a package, the builds of stage1:exe:ghc-bin and
stage1:exe:ghc-pkg where being linearised when building a specific
target like `binary-dist-dir`.

Thankfully the fix is quite local, to supply all the `withStaged`
arguments together so the needs can be batched together and hence
performed in parallel.

Fixes #22093

- - - - -
c4438347 by Matthew Pickering at 2022-09-14T17:17:04-04:00
Remove stage1:exe:ghc-bin pre-build from CI script

CI builds stage1:exe:ghc-bin before the binary-dist target which
introduces some quite bad linearisation (see #22093) because we don't
build stage1 compiler in parallel with anything. Then when the
binary-dist target is started we have to build stage1:exe:ghc-pkg before
doing anything.

Fixes #22094

- - - - -
71d8db86 by Matthew Pickering at 2022-09-14T17:17:04-04:00
hadrian: Add extra implicit dependencies from DeriveLift

ghc -M should know that modules which use DeriveLift (or
TemplateHaskellQuotes) need TH.Lib.Internal but until it does, we have
to add these extra edges manually or the modules will be compiled before
TH.Lib.Internal is compiled which leads to a desugarer error.

- - - - -
43e574f0 by Greg Steuck at 2022-09-14T17:17:43-04:00
Repair c++ probing on OpenBSD

Failure without this change:
```
checking C++ standard library flavour... libc++
checking for linkage against 'c++ c++abi'... failed
checking for linkage against 'c++ cxxrt'... failed
configure: error: Failed to find C++ standard library
```

- - - - -
534b39ee by Douglas Wilson at 2022-09-14T17:18:21-04:00
libraries: template-haskell: vendor filepath differently

Vendoring with ../ in hs-source-dirs prevents upload to hackage.

(cherry picked from commit 1446be7586ba70f9136496f9b67f792955447842)

- - - - -
bdd61cd6 by M Farkas-Dyck at 2022-09-14T22:39:34-04:00
Unbreak Hadrian with Cabal 3.8.

- - - - -
df04d6ec by Krzysztof Gogolewski at 2022-09-14T22:40:09-04:00
Fix typos

- - - - -
d6ea8356 by Andreas Klebinger at 2022-09-15T10:12:41+02:00
Tag inference: Fix #21954 by retaining tagsigs of vars in function position.

For an expression like:

    case x of y
      Con z -> z

If we also retain the tag sig for z we can generate code to immediately return
it rather than calling out to stg_ap_0_fast.

- - - - -
7cce7007 by Andreas Klebinger at 2022-09-15T10:12:42+02:00
Stg.InferTags.Rewrite - Avoid some thunks.

- - - - -
88c4cbdb by Cheng Shao at 2022-09-16T13:57:56-04:00
hadrian: enable -fprof-late only for profiling ways

- - - - -
d7235831 by Cheng Shao at 2022-09-16T13:57:56-04:00
hadrian: add late_ccs flavour transformer

- - - - -
ce203753 by Cheng Shao at 2022-09-16T13:58:34-04:00
configure: remove unused program checks

- - - - -
9b4c1056 by Pierre Le Marre at 2022-09-16T13:59:16-04:00
Update to Unicode 15.0

- - - - -
c6e9b89a by Bodigrim at 2022-09-16T13:59:55-04:00
Avoid partial head and tail in ghc-heap; replace with total pattern-matching

- - - - -
616afde3 by Cheng Shao at 2022-09-16T14:00:33-04:00
hadrian: relax Cabal upper bound to allow building with Cabal-3.8

A follow up of !8910.

- - - - -
df35d994 by Alexis King at 2022-09-16T14:01:11-04:00
Add links to the continuations haddocks in the docs for each primop

fixes #22176

- - - - -
383f7549 by Matthew Pickering at 2022-09-16T21:42:10-04:00
-Wunused-pattern-binds: Recurse into patterns to check whether there's a splice

See the examples in #22057 which show we have to traverse deeply into a
pattern to determine whether it contains a splice or not. The original
implementation pointed this out but deemed this very shallow traversal
"too expensive".

Fixes #22057

I also fixed an oversight in !7821 which meant we lost a warning which
was present in 9.2.2.

Fixes #22067

- - - - -
5031bf49 by sheaf at 2022-09-16T21:42:49-04:00
Hadrian: Don't try to build terminfo on Windows

Commit b42cedbe introduced a dependency on terminfo on Windows,
but that package isn't available on Windows.

- - - - -
c9afe221 by M Farkas-Dyck at 2022-09-17T06:44:47-04:00
Clean up some. In particular:
• Delete some dead code, largely under `GHC.Utils`.
• Clean up a few definitions in `GHC.Utils.(Misc, Monad)`.
• Clean up `GHC.Types.SrcLoc`.
• Derive stock `Functor, Foldable, Traversable` for more types.
• Derive more instances for newtypes.

Bump haddock submodule.

- - - - -
85431ac3 by Cheng Shao at 2022-09-17T06:45:25-04:00
driver: pass original Cmm filename in ModLocation

When compiling Cmm, the ml_hs_file field is used to indicate Cmm
filename when later generating DWARF information. We should pass the
original filename here, otherwise for preprocessed Cmm files, the
filename will be a temporary filename which is confusing.

- - - - -
63aa0069 by Cheng Shao at 2022-09-17T06:46:04-04:00
rts: remove legacy logging cabal flag

- - - - -
bd0f4184 by Cheng Shao at 2022-09-17T06:46:04-04:00
rts: make threaded ways optional

For certain targets (e.g. wasm32-wasi), the threaded rts is known not to
work. This patch adds a "threaded" cabal flag to rts to make threaded
rts ways optional. Hadrian enables this flag iff the flavour rtsWays
contains threaded ways.

- - - - -
8a666ad2 by Ryan Scott at 2022-09-18T08:00:44-04:00
DeriveFunctor: Check for last type variables using dataConUnivTyVars

Previously, derived instances of `Functor` (as well as the related classes
`Foldable`, `Traversable`, and `Generic1`) would determine which constraints to
infer by checking for fields that contain the last type variable. The problem
was that this last type variable was taken from `tyConTyVars`. For GADTs, the
type variables in each data constructor are _not_ the same type variables as
in `tyConTyVars`, leading to #22167.

This fixes the issue by instead checking for the last type variable using
`dataConUnivTyVars`. (This is very similar in spirit to the fix for #21185,
which also replaced an errant use of `tyConTyVars` with type variables from
each data constructor.)

Fixes #22167.

- - - - -
78037167 by Vladislav Zavialov at 2022-09-18T08:01:20-04:00
Lexer: pass updated buffer to actions (#22201)

In the lexer, predicates have the following type:
	{ ... } :: user       -- predicate state
		-> AlexInput  -- input stream before the token
		-> Int        -- length of the token
		-> AlexInput  -- input stream after the token
		-> Bool       -- True <=> accept the token
This is documented in the Alex manual.

There is access to the input stream both before and after the token.
But when the time comes to construct the token, GHC passes only the
initial string buffer to the lexer action. This patch fixes it:

	- type Action = PsSpan -> StringBuffer -> Int ->                 P (PsLocated Token)
	+ type Action = PsSpan -> StringBuffer -> Int -> StringBuffer -> P (PsLocated Token)

Now lexer actions have access to the string buffer both before and after
the token, just like the predicates. It's just a matter of passing an
additional function parameter throughout the lexer.

- - - - -
75746594 by Vladislav Zavialov at 2022-09-18T08:01:20-04:00
Lexer: define varsym without predicates (#22201)

Before this patch, the varsym lexing rules were defined as follows:

	<0> {
	  @varsym / { precededByClosingToken `alexAndPred` followedByOpeningToken } { varsym_tight_infix }
	  @varsym / { followedByOpeningToken }  { varsym_prefix }
	  @varsym / { precededByClosingToken }  { varsym_suffix }
	  @varsym                               { varsym_loose_infix }
	}

Unfortunately, this meant that the predicates 'precededByClosingToken' and
'followedByOpeningToken' were recomputed several times before we could figure
out the whitespace context.

With this patch, we check for whitespace context directly in the lexer
action:

	<0> {
	  @varsym { with_op_ws varsym }
	}

The checking for opening/closing tokens happens in 'with_op_ws' now,
which is part of the lexer action rather than the lexer predicate.

- - - - -
c1f81b38 by M Farkas-Dyck at 2022-09-19T09:07:05-04:00
Scrub partiality about `NewOrData`.

Rather than a list of constructors and a `NewOrData` flag, we define `data DataDefnCons a = NewTypeCon a | DataTypeCons [a]`, which enforces a newtype to have exactly one constructor.

Closes #22070.

Bump haddock submodule.

- - - - -
1e1ed8c5 by Cheng Shao at 2022-09-19T09:07:43-04:00
CmmToC: emit __builtin_unreachable() after noreturn ccalls

Emit a __builtin_unreachable() call after a foreign call marked as
CmmNeverReturns. This is crucial to generate correctly typed code for
wasm; as for other archs, this is also beneficial for the C compiler
optimizations.

- - - - -
19f45a25 by Jan Hrček at 2022-09-20T03:49:29-04:00
Document :unadd GHCi command in user guide

- - - - -
545ff490 by sheaf at 2022-09-20T03:50:06-04:00
Hadrian: merge archives even in stage 0

We now always merge .a archives when ar supports -L.
This change is necessary in order to bootstrap GHC using GHC 9.4
on Windows, as nested archives aren't supported.
Not doing so triggered bug #21990 when trying to use the Win32
package, with errors such as:

  Not a x86_64 PE+ file.
  Unknown COFF 4 type in getHeaderInfo.

  ld.lld: error: undefined symbol: Win32zm2zi12zi0zi0_SystemziWin32ziConsoleziCtrlHandler_withConsoleCtrlHandler1_info

We have to be careful about which ar is meant: in stage 0, the check
should be done on the system ar (system-ar in system.config).

- - - - -
59fe128c by Vladislav Zavialov at 2022-09-20T03:50:42-04:00
Fix -Woperator-whitespace for consym (part of #19372)

Due to an oversight, the initial specification and implementation of
-Woperator-whitespace focused on varsym exclusively and completely
ignored consym.

This meant that expressions such as "x+ y" would produce a warning,
while "x:+ y" would not.

The specification was corrected in ghc-proposals pull request #404,
and this patch updates the implementation accordingly.

Regression test included.

- - - - -
c4c2cca0 by John Ericson at 2022-09-20T13:11:49-04:00
Add `Eq` and `Ord` instances for `Generically1`

These are needed so the subsequent commit overhauling the `*1` classes
type-checks.

- - - - -
7beb356e by John Ericson at 2022-09-20T13:11:50-04:00
Relax instances for Functor combinators; put superclass on Class1 and Class2 to make non-breaking

This change is approved by the Core Libraries commitee in
https://github.com/haskell/core-libraries-committee/issues/10

The first change makes the `Eq`, `Ord`, `Show`, and `Read` instances for
`Sum`, `Product`, and `Compose` match those for `:+:`, `:*:`, and `:.:`.
These have the proper flexible contexts that are exactly what the
instance needs:

For example, instead of
```haskell
instance (Eq1 f, Eq1 g, Eq a) => Eq (Compose f g a) where
  (==) = eq1
```
we do
```haskell
deriving instance Eq (f (g a)) => Eq (Compose f g a)
```

But, that change alone is rather breaking, because until now `Eq (f a)`
and `Eq1 f` (and respectively the other classes and their `*1`
equivalents too) are *incomparable* constraints. This has always been an
annoyance of working with the `*1` classes, and now it would rear it's
head one last time as an pesky migration.

Instead, we give the `*1` classes superclasses, like so:
```haskell
(forall a. Eq a => Eq (f a)) => Eq1 f
```
along with some laws that canonicity is preserved, like:
```haskell
liftEq (==) = (==)
```

and likewise for `*2` classes:
```haskell
(forall a. Eq a => Eq1 (f a)) => Eq2 f
```
and laws:
```haskell
liftEq2 (==) = liftEq1
```

The `*1` classes also have default methods using the `*2` classes where
possible.

What this means, as explained in the docs, is that `*1` classes really
are generations of the regular classes, indicating that the methods can
be split into a canonical lifting combined with a canonical inner, with
the super class "witnessing" the laws[1] in a fashion.

Circling back to the pragmatics of migrating, note that the superclass
means evidence for the old `Sum`, `Product`, and `Compose` instances is
(more than) sufficient, so breakage is less likely --- as long no
instances are "missing", existing polymorphic code will continue to
work.

Breakage can occur when a datatype implements the `*1` class but not the
corresponding regular class, but this is almost certainly an oversight.
For example, containers made that mistake for `Tree` and `Ord`, which I
fixed in https://github.com/haskell/containers/pull/761, but fixing the
issue by adding `Ord1` was extremely *un*controversial.

`Generically1` was also missing `Eq`, `Ord`, `Read,` and `Show`
instances. It is unlikely this would have been caught without
implementing this change.

-----

[1]: In fact, someday, when the laws are part of the language and not
only documentation, we might be able to drop the superclass field of the
dictionary by using the laws to recover the superclass in an
instance-agnostic manner, e.g. with a *non*-overloaded function with
type:

```haskell
DictEq1 f -> DictEq a -> DictEq (f a)
```

But I don't wish to get into optomizations now, just demonstrate the
close relationship between the law and the superclass.

Bump haddock submodule because of test output changing.

- - - - -
6a8c6b5e by Tom Ellis at 2022-09-20T13:12:27-04:00
Add notes to ghc-prim Haddocks that users should not import it

- - - - -
ee9d0f5c by matoro at 2022-09-20T13:13:06-04:00
docs: clarify that LLVM codegen is not available in unregisterised mode

The current docs are misleading and suggest that it is possible to use
LLVM codegen from an unregisterised build.  This is not the case;
attempting to pass `-fllvm` to an unregisterised build warns:

```
when making flags consistent: warning:
    Target platform uses unregisterised ABI, so compiling via C
```

and uses the C codegen anyway.

- - - - -
854224ed by Nicolas Trangez at 2022-09-20T20:14:29-04:00
rts: remove copy-paste error from `cabal.rts.in`

This was, likely accidentally, introduced in 4bf542bf1c.

See: 4bf542bf1cdf2fa468457fc0af21333478293476

- - - - -
c8ae3add by Matthew Pickering at 2022-09-20T20:15:04-04:00
hadrian: Add extra_dependencies edges for all different ways

The hack to add extra dependencies needed by DeriveLift extension missed
the cases for profiles and dynamic ways. For the profiled way this leads
to errors like:

```
GHC error in desugarer lookup in Data.IntSet.Internal:
  Failed to load interface for ‘Language.Haskell.TH.Lib.Internal’
  Perhaps you haven't installed the profiling libraries for package ‘template-haskell’?
  Use -v (or `:set -v` in ghci) to see a list of the files searched for.
ghc: panic! (the 'impossible' happened)
  GHC version 9.5.20220916:
        initDs
```

Therefore the fix is to add these extra edges in.

Fixes #22197

- - - - -
a971657d by Mon Aaraj at 2022-09-21T06:41:24+03:00
users-guide: fix incorrect ghcappdata folder for unix and windows

- - - - -
06ccad0d by sheaf at 2022-09-21T08:28:49-04:00
Don't use isUnliftedType in isTagged

The function GHC.Stg.InferTags.Rewrite.isTagged can be given
the Id of a join point, which might be representation polymorphic.
This would cause the call to isUnliftedType to crash. It's better
to use typeLevity_maybe instead.

Fixes #22212

- - - - -
c0ba775d by Teo Camarasu at 2022-09-21T14:30:37-04:00
Add fragmentation statistic to GHC.Stats

Implements #21537

- - - - -
2463df2f by Torsten Schmits at 2022-09-21T14:31:24-04:00
Rename Solo[constructor] to MkSolo

Part of proposal 475 (https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0475-tuple-syntax.rst)

Moves all tuples to GHC.Tuple.Prim
Updates ghc-prim version (and bumps bounds in dependents)

updates haddock submodule
updates deepseq submodule
updates text submodule

- - - - -
9034fada by Matthew Pickering at 2022-09-22T09:25:29-04:00
Update filepath to filepath-1.4.100.0

Updates submodule

* Always rely on vendored filepath
* filepath must be built as stage0 dependency because it uses
  template-haskell.

Towards #22098

- - - - -
615e2278 by Krzysztof Gogolewski at 2022-09-22T09:26:05-04:00
Minor refactor around Outputable

* Replace 'text . show' and 'ppr' with 'int'.
* Remove Outputable.hs-boot, no longer needed
* Use pprWithCommas
* Factor out instructions in AArch64 codegen

- - - - -
aeafdba5 by Sebastian Graf at 2022-09-27T15:14:54+02:00
Demand: Clear distinction between Call SubDmd and eval Dmd (#21717)

In #21717 we saw a reportedly unsound strictness signature due to an unsound
definition of plusSubDmd on Calls. This patch contains a description and the fix
to the unsoundness as outlined in `Note [Call SubDemand vs. evaluation Demand]`.

This fix means we also get rid of the special handling of `-fpedantic-bottoms`
in eta-reduction. Thanks to less strict and actually sound strictness results,
we will no longer eta-reduce the problematic cases in the first place, even
without `-fpedantic-bottoms`.

So fixing the unsoundness also makes our eta-reduction code simpler with less
hacks to explain. But there is another, more unfortunate side-effect:
We *unfix* #21085, but fortunately we have a new fix ready:
See `Note [mkCall and plusSubDmd]`.

There's another change:
I decided to make `Note [SubDemand denotes at least one evaluation]` a lot
simpler by using `plusSubDmd` (instead of `lubPlusSubDmd`) even if both argument
demands are lazy. That leads to less precise results, but in turn rids ourselves
from the need for 4 different `OpMode`s and the complication of
`Note [Manual specialisation of lub*Dmd/plus*Dmd]`. The result is simpler code
that is in line with the paper draft on Demand Analysis.

I left the abandoned idea in `Note [Unrealised opportunity in plusDmd]` for
posterity. The fallout in terms of regressions is negligible, as the testsuite
and NoFib shows.

```
        Program         Allocs    Instrs
--------------------------------------------------------------------------------
         hidden          +0.2%     -0.2%
         linear          -0.0%     -0.7%
--------------------------------------------------------------------------------
            Min          -0.0%     -0.7%
            Max          +0.2%     +0.0%
 Geometric Mean          +0.0%     -0.0%
```

Fixes #21717.

- - - - -
9b1595c8 by Ross Paterson at 2022-09-27T14:12:01-04:00
implement proposal 106 (Define Kinds Without Promotion) (fixes #6024)

includes corresponding changes to haddock submodule

- - - - -
c2d73cb4 by Andreas Klebinger at 2022-09-28T15:07:30-04:00
Apply some tricks to speed up core lint.

Below are the noteworthy changes and if given their impact on compiler
allocations for a type heavy module:

* Use the oneShot trick on LintM
* Use a unboxed tuple for the result of LintM: ~6% reduction
* Avoid a thunk for the result of typeKind in lintType: ~5% reduction
* lint_app: Don't allocate the error msg in the hot code path: ~4%
  reduction
* lint_app: Eagerly force the in scope set: ~4%
* nonDetCmpType: Try to short cut using reallyUnsafePtrEquality#: ~2%
* lintM: Use a unboxed maybe for the `a` result: ~12%
* lint_app: make go_app tail recursive to avoid allocating the go function
            as heap closure: ~7%
* expandSynTyCon_maybe: Use a specialized data type

For a less type heavy module like nofib/spectral/simple compiled with
-O -dcore-lint allocations went down by ~24% and compile time by ~9%.

-------------------------
Metric Decrease:
    T1969
-------------------------

- - - - -
b74b6191 by sheaf at 2022-09-28T15:08:10-04:00
matchLocalInst: do domination analysis

When multiple Given quantified constraints match a Wanted, and there is
a quantified constraint that dominates all others, we now pick it
to solve the Wanted.

See Note [Use only the best matching quantified constraint].

For example:

  [G] d1: forall a b. ( Eq a, Num b, C a b  ) => D a b
  [G] d2: forall a  .                C a Int  => D a Int
  [W] {w}: D a Int

When solving the Wanted, we find that both Givens match, but we pick
the second, because it has a weaker precondition, C a Int, compared
to (Eq a, Num Int, C a Int). We thus say that d2 dominates d1;
see Note [When does a quantified instance dominate another?].

This domination test is done purely in terms of superclass expansion,
in the function GHC.Tc.Solver.Interact.impliedBySCs. We don't attempt
to do a full round of constraint solving; this simple check suffices
for now.

Fixes #22216 and #22223

- - - - -
2a53ac18 by Simon Peyton Jones at 2022-09-28T17:49:09-04:00
Improve aggressive specialisation

This patch fixes #21286, by not unboxing dictionaries in
worker/wrapper (ever). The main payload is tiny:

* In `GHC.Core.Opt.DmdAnal.finaliseArgBoxities`, do not unbox
  dictionaries in `get_dmd`.  See Note [Do not unbox class dictionaries]
  in that module

* I also found that imported wrappers were being fruitlessly
  specialised, so I fixed that too, in canSpecImport.
  See Note [Specialising imported functions] point (2).

In doing due diligence in the testsuite I fixed a number of
other things:

* Improve Note [Specialising unfoldings] in GHC.Core.Unfold.Make,
  and Note [Inline specialisations] in GHC.Core.Opt.Specialise,
  and remove duplication between the two. The new Note describes
  how we specialise functions with an INLINABLE pragma.

  And simplify the defn of `spec_unf` in `GHC.Core.Opt.Specialise.specCalls`.

* Improve Note [Worker/wrapper for INLINABLE functions] in
  GHC.Core.Opt.WorkWrap.

  And (critially) make an actual change which is to propagate the
  user-written pragma from the original function to the wrapper; see
  `mkStrWrapperInlinePrag`.

* Write new Note [Specialising imported functions] in
  GHC.Core.Opt.Specialise

All this has a big effect on some compile times. This is
compiler/perf, showing only changes over 1%:

Metrics: compile_time/bytes allocated
-------------------------------------
                LargeRecord(normal)  -50.2% GOOD
           ManyConstructors(normal)   +1.0%
MultiLayerModulesTH_OneShot(normal)   +2.6%
                  PmSeriesG(normal)   -1.1%
                     T10547(normal)   -1.2%
                     T11195(normal)   -1.2%
                     T11276(normal)   -1.0%
                    T11303b(normal)   -1.6%
                     T11545(normal)   -1.4%
                     T11822(normal)   -1.3%
                     T12150(optasm)   -1.0%
                     T12234(optasm)   -1.2%
                     T13056(optasm)   -9.3% GOOD
                     T13253(normal)   -3.8% GOOD
                     T15164(normal)   -3.6% GOOD
                     T16190(normal)   -2.1%
                     T16577(normal)   -2.8% GOOD
                     T16875(normal)   -1.6%
                     T17836(normal)   +2.2%
                    T17977b(normal)   -1.0%
                     T18223(normal)  -33.3% GOOD
                     T18282(normal)   -3.4% GOOD
                     T18304(normal)   -1.4%
                    T18698a(normal)   -1.4% GOOD
                    T18698b(normal)   -1.3% GOOD
                     T19695(normal)   -2.5% GOOD
                      T5837(normal)   -2.3%
                      T9630(normal)  -33.0% GOOD
                      WWRec(normal)   -9.7% GOOD
             hard_hole_fits(normal)   -2.1% GOOD
                     hie002(normal)   +1.6%

                          geo. mean   -2.2%
                          minimum    -50.2%
                          maximum     +2.6%

I diligently investigated some of the big drops.

* Caused by not doing w/w for dictionaries:
    T13056, T15164, WWRec, T18223

* Caused by not fruitlessly specialising wrappers
    LargeRecord, T9630

For runtimes, here is perf/should+_run:

Metrics: runtime/bytes allocated
--------------------------------
               T12990(normal)   -3.8%
                T5205(normal)   -1.3%
                T9203(normal)  -10.7% GOOD
        haddock.Cabal(normal)   +0.1%
         haddock.base(normal)   -1.1%
     haddock.compiler(normal)   -0.3%
        lazy-bs-alloc(normal)   -0.2%
------------------------------------------
                    geo. mean   -0.3%
                    minimum    -10.7%
                    maximum     +0.1%

I did not investigate exactly what happens in T9203.

Nofib is a wash:

+-------------------------------++--+-----------+-----------+
|                               ||  | tsv (rel) | std. err. |
+===============================++==+===========+===========+
|                     real/anna ||  |    -0.13% |      0.0% |
|                      real/fem ||  |    +0.13% |      0.0% |
|                   real/fulsom ||  |    -0.16% |      0.0% |
|                     real/lift ||  |    -1.55% |      0.0% |
|                  real/reptile ||  |    -0.11% |      0.0% |
|                  real/smallpt ||  |    +0.51% |      0.0% |
|          spectral/constraints ||  |    +0.20% |      0.0% |
|               spectral/dom-lt ||  |    +1.80% |      0.0% |
|               spectral/expert ||  |    +0.33% |      0.0% |
+===============================++==+===========+===========+
|                     geom mean ||  |           |           |
+-------------------------------++--+-----------+-----------+

I spent quite some time investigating dom-lt, but it's pretty
complicated.  See my note on !7847.  Conclusion: it's just a delicate
inlining interaction, and we have plenty of those.

Metric Decrease:
    LargeRecord
    T13056
    T13253
    T15164
    T16577
    T18223
    T18282
    T18698a
    T18698b
    T19695
    T9630
    WWRec
    hard_hole_fits
    T9203

- - - - -
addeefc0 by Simon Peyton Jones at 2022-09-28T17:49:09-04:00
Refactor UnfoldingSource and IfaceUnfolding

I finally got tired of the way that IfaceUnfolding reflected
a previous structure of unfoldings, not the current one. This
MR refactors UnfoldingSource and IfaceUnfolding to be simpler
and more consistent.

It's largely just a refactor, but in UnfoldingSource (which moves
to GHC.Types.Basic, since it is now used in IfaceSyn too), I
distinguish between /user-specified/ and /system-generated/ stable
unfoldings.

    data UnfoldingSource
      = VanillaSrc
      | StableUserSrc   -- From a user-specified pragma
      | StableSystemSrc -- From a system-generated unfolding
      | CompulsorySrc

This has a minor effect in CSE (see the use of isisStableUserUnfolding
in GHC.Core.Opt.CSE), which I tripped over when working on
specialisation, but it seems like a Good Thing to know anyway.

- - - - -
7be6f9a4 by Simon Peyton Jones at 2022-09-28T17:49:09-04:00
INLINE/INLINEABLE pragmas in Foreign.Marshal.Array

Foreign.Marshal.Array contains many small functions, all of which are
overloaded, and which are critical for performance. Yet none of them
had pragmas, so it was a fluke whether or not they got inlined.

This patch makes them all either INLINE (small ones) or
INLINEABLE and hence specialisable (larger ones).

See Note [Specialising array operations] in that module.

- - - - -
b0c89dfa by Jade Lovelace at 2022-09-28T17:49:49-04:00
Export OnOff from GHC.Driver.Session

I was working on fixing an issue where HLS was trying to pass its
DynFlags to HLint, but didn't pass any of the disabled language
extensions, which HLint would then assume are on because of their
default values.

Currently it's not possible to get any of the "No" flags because the
`DynFlags.extensions` field can't really be used since it is [OnOff
Extension] and OnOff is not exported.

So let's export it.

- - - - -
2f050687 by Bodigrim at 2022-09-28T17:50:28-04:00
Avoid Data.List.group; prefer Data.List.NonEmpty.group

This allows to avoid further partiality, e. g., map head . group is
replaced by map NE.head . NE.group, and there are less panic calls.

- - - - -
bc0020fa by M Farkas-Dyck at 2022-09-28T22:51:59-04:00
Clean up `findWiredInUnit`. In particular, avoid `head`.

- - - - -
6a2eec98 by Bodigrim at 2022-09-28T22:52:38-04:00
Eliminate headFS, use unconsFS instead

A small step towards #22185 to avoid partial functions + safe implementation
of `startsWithUnderscore`.

- - - - -
5a535172 by Sebastian Graf at 2022-09-29T17:04:20+02:00
Demand: Format Call SubDemands `Cn(sd)` as `C(n,sd)` (#22231)

Justification in #22231. Short form: In a demand like `1C1(C1(L))`
it was too easy to confuse which `1` belongs to which `C`. Now
that should be more obvious.

Fixes #22231

- - - - -
ea0083bf by Bryan Richter at 2022-09-29T15:48:38-04:00
Revert "ci: enable parallel compression for xz"

Combined wxth XZ_OPT=9, this blew the memory capacity of CI runners.

This reverts commit a5f9c35f5831ef5108e87813a96eac62803852ab.

- - - - -
f5e8f493 by Sebastian Graf at 2022-09-30T18:42:13+02:00
Boxity: Don't update Boxity unless worker/wrapper follows (#21754)

A small refactoring in our Core Opt pipeline and some new functions for
transfering argument boxities from one signature to another to facilitate
`Note [Don't change boxity without worker/wrapper]`.

Fixes #21754.

- - - - -
4baf7b1c by M Farkas-Dyck at 2022-09-30T17:45:47-04:00
Scrub various partiality involving empty lists.

Avoids some uses of `head` and `tail`, and some panics when an argument is null.

- - - - -
95ead839 by Alexis King at 2022-10-01T00:37:43-04:00
Fix a bug in continuation capture across multiple stack chunks

- - - - -
22096652 by Bodigrim at 2022-10-01T00:38:22-04:00
Enforce internal invariant of OrdList and fix bugs in viewCons / viewSnoc

`viewCons` used to ignore `Many` constructor completely, returning `VNothing`.
`viewSnoc` violated internal invariant of `Many` being a non-empty list.

- - - - -
48ab9ca5 by Nicolas Trangez at 2022-10-04T20:34:10-04:00
chore: extend `.editorconfig` for C files

- - - - -
b8df5c72 by Brandon Chinn at 2022-10-04T20:34:46-04:00
Fix docs for pattern synonyms
- - - - -
463ffe02 by Oleg Grenrus at 2022-10-04T20:35:24-04:00
Use sameByteArray# in sameByteArray

- - - - -
fbe1e86e by Pierre Le Marre at 2022-10-05T15:58:43+02:00
Minor fixes following Unicode 15.0.0 update

- Fix changelog for Unicode 15.0.0
- Fix the checksums of the downloaded Unicode files, in base's tool: "ucd2haskell".

- - - - -
8a31d02e by Cheng Shao at 2022-10-05T20:40:41-04:00
rts: don't enforce aligned((8)) on 32-bit targets

We simply need to align to the word size for pointer tagging to work. On
32-bit targets, aligned((8)) is wasteful.

- - - - -
532de368 by Ryan Scott at 2022-10-06T07:45:46-04:00
Export symbolSing, SSymbol, and friends (CLC#85)

This implements this Core Libraries Proposal:
https://github.com/haskell/core-libraries-committee/issues/85

In particular, it:

1. Exposes the `symbolSing` method of `KnownSymbol`,
2. Exports the abstract `SSymbol` type used in `symbolSing`, and
3. Defines an API for interacting with `SSymbol`.

This also makes corresponding changes for `natSing`/`KnownNat`/`SNat` and
`charSing`/`KnownChar`/`SChar`. This fixes #15183 and addresses part (2)
of #21568.

- - - - -
d83a92e6 by sheaf at 2022-10-07T07:36:30-04:00
Remove mention of make from README.md

- - - - -
945e8e49 by Bodigrim at 2022-10-10T17:13:31-04:00
Add a newline before since pragma in Data.Array.Byte

- - - - -
44fcdb04 by Vladislav Zavialov at 2022-10-10T17:14:06-04:00
Parser/PostProcess: rename failOp* functions

There are three functions named failOp* in the parser:
	failOpNotEnabledImportQualifiedPost
	failOpImportQualifiedTwice
	failOpFewArgs
Only the last one has anything to do with operators. The other two
were named this way either by mistake or due to a misunderstanding of
what "op" stands for. This small patch corrects this.

- - - - -
96d32ff2 by Simon Peyton Jones at 2022-10-10T22:30:21+01:00
Make rewrite rules "win" over inlining

If a rewrite rule and a rewrite rule compete in the simplifier, this
patch makes sure that the rewrite rule "win".  That is, in general
a bit fragile, but it's a huge help when making specialisation work
reliably, as #21851 and #22097 showed.

The change is fairly straightforwad, and documented in
   Note [Rewrite rules and inlining]
in GHC.Core.Opt.Simplify.Iteration.

Compile-times change, up and down a bit -- in some cases because
we get better specialisation.  But the payoff (more reliable
specialisation) is large.

Metrics: compile_time/bytes allocated
-----------------------------------------------
    T10421(normal)   +3.7% BAD
   T10421a(normal)   +5.5%
    T13253(normal)   +1.3%
      T14052(ghci)   +1.8%
    T15304(normal)   -1.4%
    T16577(normal)   +3.1% BAD
    T17516(normal)   +2.3%
    T17836(normal)   -1.9%
    T18223(normal)   -1.8%
     T8095(normal)   -1.3%
     T9961(normal)   +2.5% BAD

         geo. mean   +0.0%
         minimum     -1.9%
         maximum     +5.5%

Nofib results are (bytes allocated)

+-------------------------------++----------+
|                               ||tsv (rel) |
+===============================++==========+
|           imaginary/paraffins ||   +0.27% |
|                imaginary/rfib ||   -0.04% |
|                     real/anna ||   +0.02% |
|                      real/fem ||   -0.04% |
|                    real/fluid ||   +1.68% |
|                   real/gamteb ||   -0.34% |
|                       real/gg ||   +1.54% |
|                   real/hidden ||   -0.01% |
|                      real/hpg ||   -0.03% |
|                    real/infer ||   -0.03% |
|                   real/prolog ||   +0.02% |
|                  real/veritas ||   -0.47% |
|       shootout/fannkuch-redux ||   -0.03% |
|         shootout/k-nucleotide ||   -0.02% |
|               shootout/n-body ||   -0.06% |
|        shootout/spectral-norm ||   -0.01% |
|         spectral/cryptarithm2 ||   +1.25% |
|             spectral/fibheaps ||  +18.33% |
|           spectral/last-piece ||   -0.34% |
+===============================++==========+
|                     geom mean ||   +0.17% |

There are extensive notes in !8897 about the regressions.
Briefly

* fibheaps: there was a very delicately balanced inlining that
  tipped over the wrong way after this change.

* cryptarithm2 and paraffins are caused by #22274, which is
  a separate issue really.  (I.e. the right fix is *not* to
  make inlining "win" over rules.)

So I'm accepting these changes

Metric Increase:
    T10421
    T16577
    T9961

- - - - -
ed4b5885 by Joachim Breitner at 2022-10-10T23:16:11-04:00
Utils.JSON: do not escapeJsonString in ToJson String instance

as `escapeJsonString` is used in `renderJSON`, so the `JSString`
constructor is meant to carry the unescaped string.

- - - - -
fbb88740 by Matthew Pickering at 2022-10-11T12:48:45-04:00
Tidy implicit binds

We want to put implicit binds into fat interface files, so the easiest
thing to do seems to be to treat them uniformly with other binders.

- - - - -
e058b138 by Matthew Pickering at 2022-10-11T12:48:45-04:00
Interface Files with Core Definitions

This commit adds three new flags

* -fwrite-if-simplified-core: Writes the whole core program into an interface
  file
* -fbyte-code-and-object-code: Generate both byte code and object code
  when compiling a file
* -fprefer-byte-code: Prefer to use byte-code if it's available when
  running TH splices.

The goal for including the core bindings in an interface file is to be able to restart the compiler pipeline
at the point just after simplification and before code generation. Once compilation is
restarted then code can be created for the byte code backend.
This can significantly speed up
start-times for projects in GHCi. HLS already implements its own version of these extended interface
files for this reason.

Preferring to use byte-code means that we can avoid some potentially
expensive code generation steps (see #21700)

* Producing object code is much slower than producing bytecode, and normally you
  need to compile with `-dynamic-too` to produce code in the static and dynamic way, the
  dynamic way just for Template Haskell execution when using a dynamically linked compiler.

* Linking many large object files, which happens once per splice, can be quite
  expensive compared to linking bytecode.

And you can get GHC to compile the necessary byte code so
`-fprefer-byte-code` has access to it by using
`-fbyte-code-and-object-code`.

Fixes #21067

- - - - -
9789ea8e by Matthew Pickering at 2022-10-11T12:48:45-04:00
Teach -fno-code about -fprefer-byte-code

This patch teachs the code generation logic of -fno-code about
-fprefer-byte-code, so that if we need to generate code for a module
which prefers byte code, then we generate byte code rather than object
code.

We keep track separately which modules need object code and which byte
code and then enable the relevant code generation for each. Typically
the option will be enabled globally so one of these sets should be empty
and we will just turn on byte code or object code generation.

We also fix the bug where we would generate code for a module which
enables Template Haskell despite the fact it was unecessary.

Fixes #22016

- - - - -
caced757 by Simon Peyton Jones at 2022-10-11T12:49:21-04:00
Don't keep exit join points so much

We were religiously keeping exit join points throughout, which
had some bad effects (#21148, #22084).

This MR does two things:

* Arranges that exit join points are inhibited from inlining
  only in /one/ Simplifier pass (right after Exitification).

  See Note [Be selective about not-inlining exit join points]
  in GHC.Core.Opt.Exitify

  It's not a big deal, but it shaves 0.1% off compile times.

* Inline used-once non-recursive join points very aggressively
  Given join j x = rhs in
        joinrec k y = ....j x....

  where this is the only occurrence of `j`, we want to inline `j`.
  (Unless sm_keep_exits is on.)

  See Note [Inline used-once non-recursive join points] in
  GHC.Core.Opt.Simplify.Utils

  This is just a tidy-up really.  It doesn't change allocation, but
  getting rid of a binding is always good.

Very effect on nofib -- some up and down.

- - - - -
284cf387 by Simon Peyton Jones at 2022-10-11T12:49:21-04:00
Make SpecConstr bale out less often

When doing performance debugging on #22084 / !8901, I found that the
algorithm in SpecConstr.decreaseSpecCount was so aggressive that if
there were /more/ specialisations available for an outer function,
that could more or less kill off specialisation for an /inner/
function.  (An example was in nofib/spectral/fibheaps.)

This patch makes it a bit more aggressive, by dividing by 2, rather
than by the number of outer specialisations.

This makes the program bigger, temporarily:

   T19695(normal) ghc/alloc   +11.3% BAD

because we get more specialisation.  But lots of other programs
compile a bit faster and the geometric mean in perf/compiler
is 0.0%.

Metric Increase:
    T19695

- - - - -
66af1399 by Cheng Shao at 2022-10-11T12:49:59-04:00
CmmToC: emit explicit tail calls when the C compiler supports it

Clang 13+ supports annotating a return statement using the musttail
attribute, which guarantees that it lowers to a tail call if compilation
succeeds.

This patch takes advantage of that feature for the unregisterised code
generator. The configure script tests availability of the musttail
attribute, if it's available, the Cmm tail calls will become C tail
calls that avoids the mini interpreter trampoline overhead. Nothing is
affected if the musttail attribute is not supported.

Clang documentation:
https://clang.llvm.org/docs/AttributeReference.html#musttail

- - - - -
7f0decd5 by Matthew Pickering at 2022-10-11T12:50:40-04:00
Don't include BufPos in interface files

Ticket #22162 pointed out that the build directory was leaking into the
ABI hash of a module because the BufPos depended on the location of the
build tree.

BufPos is only used in GHC.Parser.PostProcess.Haddock, and the
information doesn't need to be propagated outside the context of a
module.

Fixes #22162

- - - - -
dce9f320 by Cheng Shao at 2022-10-11T12:51:19-04:00
CLabel: fix isInfoTableLabel

isInfoTableLabel does not take Cmm info table into account. This patch is required for data section layout of wasm32 NCG to work.

- - - - -
da679f2e by Bodigrim at 2022-10-11T18:02:59-04:00
Extend documentation for Data.List, mostly wrt infinite lists

- - - - -
9c099387 by jwaldmann at 2022-10-11T18:02:59-04:00
Expand comment for Data.List.permutations
- - - - -
d3863cb7 by Bodigrim at 2022-10-11T18:03:37-04:00
ByteArray# is unlifted, not unboxed

- - - - -
f6260e8b by Ben Gamari at 2022-10-11T23:45:10-04:00
rts: Add missing declaration of stg_noDuplicate

- - - - -
69ccec2c by Ben Gamari at 2022-10-11T23:45:10-04:00
base: Move CString, CStringLen to GHC.Foreign

- - - - -
f6e8feb4 by Ben Gamari at 2022-10-11T23:45:10-04:00
base: Move IPE helpers to GHC.InfoProv

- - - - -
866c736e by Ben Gamari at 2022-10-11T23:45:10-04:00
rts: Refactor IPE tracing support

- - - - -
6b0d2022 by Ben Gamari at 2022-10-11T23:45:10-04:00
Refactor IPE initialization

Here we refactor the representation of info table provenance information
in object code to significantly reduce its size and link-time impact.
Specifically, we deduplicate strings and represent them as 32-bit
offsets into a common string table.

In addition, we rework the registration logic to eliminate allocation
from the registration path, which is run from a static initializer where
things like allocation are technically undefined behavior (although it
did previously seem to work). For similar reasons we eliminate lock
usage from registration path, instead relying on atomic CAS.

Closes #22077.

- - - - -
9b572d54 by Ben Gamari at 2022-10-11T23:45:10-04:00
Separate IPE source file from span

The source file name can very often be shared across many IPE entries
whereas the source coordinates are generally unique. Separate the two to
exploit sharing of the former.

- - - - -
27978ceb by Krzysztof Gogolewski at 2022-10-11T23:45:46-04:00
Make Cmm Lint messages use dump style

Lint errors indicate an internal error in GHC, so it makes sense to use
it instead of the user style. This is consistent with Core Lint and STG Lint:

https://gitlab.haskell.org/ghc/ghc/-/blob/22096652/compiler/GHC/Core/Lint.hs#L429

https://gitlab.haskell.org/ghc/ghc/-/blob/22096652/compiler/GHC/Stg/Lint.hs#L144

Fixes #22218.

- - - - -
64a390d9 by Bryan Richter at 2022-10-12T09:52:51+03:00
Mark T7919 as fragile

On x86_64-linux, T7919 timed out ~30 times during July 2022.

And again ~30 times in September 2022.

- - - - -
481467a5 by Ben Gamari at 2022-10-12T08:08:37-04:00
rts: Don't hint inlining of appendToRunQueue

These hints have resulted in compile-time warnings due to failed
inlinings for quite some time. Moreover, it's quite unlikely that
inlining them is all that beneficial given that they are rather sizeable
functions.

Resolves #22280.

- - - - -
81915089 by Curran McConnell at 2022-10-12T16:32:26-04:00
remove name shadowing

- - - - -
626652f7 by Tamar Christina at 2022-10-12T16:33:13-04:00
winio: do not re-translate input when handle is uncooked

- - - - -
5172789a by Charles Taylor at 2022-10-12T16:33:57-04:00
Unrestricted OverloadedLabels (#11671)

Implements GHC proposal:
https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0170-unrestricted-overloadedlabels.rst

- - - - -
ce293908 by Andreas Klebinger at 2022-10-13T05:58:19-04:00
Add a perf test for the generics code pattern from #21839.

This code showed a strong shift between compile time (got worse) and
run time (got a lot better) recently which is perfectly acceptable.

However it wasn't clear why the compile time regression was happening
initially so I'm adding this test to make it easier to track such changes
in the future.

- - - - -
78ab7afe by Ben Gamari at 2022-10-13T05:58:56-04:00
rts/linker: Consolidate initializer/finalizer handling

Here we extend our treatment of initializer/finalizer priorities to
include ELF and in so doing refactor things to share the implementation
with PEi386. As well, I fix a subtle misconception of the ordering
behavior for `.ctors`.

Fixes #21847.

- - - - -
44692713 by Ben Gamari at 2022-10-13T05:58:56-04:00
rts/linker: Add support for .fini sections

- - - - -
beebf546 by Simon Hengel at 2022-10-13T05:59:37-04:00
Update phases.rst

(the name of the original source file is $1, not $2)
- - - - -
eda6c05e by Finley McIlwaine at 2022-10-13T06:00:17-04:00
Clearer error msg for newtype GADTs with defaulted kind

When a newtype introduces GADT eq_specs due to a defaulted
RuntimeRep, we detect this and print the error message with
explicit kinds.

This also refactors newtype type checking to use the new
diagnostic infra.

Fixes #21447

- - - - -
43ab435a by Pierre Le Marre at 2022-10-14T07:45:43-04:00
Add standard Unicode case predicates isUpperCase and isLowerCase.

These predicates use the standard Unicode case properties and are more intuitive than isUpper and isLower.

Approved by CLC in https://github.com/haskell/core-libraries-committee/issues/90#issuecomment-1276649403.

Fixes #14589

- - - - -
aec5a443 by Bodigrim at 2022-10-14T07:46:21-04:00
Add type signatures in where-clause of Data.List.permutations

The type of interleave' is very much revealing, otherwise it's extremely tough to decipher.

- - - - -
ee0deb80 by Ben Gamari at 2022-10-14T18:29:20-04:00
rts: Use pthread_setname_np correctly on Darwin

As noted in #22206, pthread_setname_np on Darwin only supports
setting the name of the calling thread. Consequently we must introduce
a trampoline which first sets the thread name before entering the thread
entrypoint.
- - - - -
8eff62a4 by Ben Gamari at 2022-10-14T18:29:57-04:00
testsuite: Add test for #22282

This will complement mpickering's more general port of foundation's
numerical testsuite, providing a test for the specific case found
in #22282.

- - - - -
62a55001 by Ben Gamari at 2022-10-14T18:29:57-04:00
ncg/aarch64: Fix sub-word sign extension yet again

In adc7f108141a973b6dcb02a7836eed65d61230e8 we fixed a number of issues
to do with sign extension in the AArch64 NCG found by ghc/test-primops>.
However, this patch made a critical error, assuming that getSomeReg
would allocate a fresh register for the result of its evaluation.
However, this is not the case as `getSomeReg (CmmReg r) == r`.
Consequently, any mutation of the register returned by `getSomeReg` may
have unwanted side-effects on other expressions also mentioning `r`. In
the fix listed above, this manifested as the registers containing the
operands of binary arithmetic operations being incorrectly
sign-extended. This resulted in #22282.

Sadly, the rather simple structure of the tests generated
by `test-primops` meant that this particular case was not exercised.
Even more surprisingly, none of our testsuite caught this case.

Here we fix this by ensuring that intermediate sign extension is
performed in a fresh register.

Fixes #22282.

- - - - -
54e41b16 by Teo Camarasu at 2022-10-15T18:09:24+01:00
rts: ensure we are below maxHeapSize after returning megablocks

When the heap is heavily block fragmented the live byte size might be
low while the memory usage is high. We want to ensure that heap overflow
triggers in these cases.

We do so by checking that we can return enough megablocks to
under maxHeapSize at the end of GC.

- - - - -
29bb90db by Teo Camarasu at 2022-10-15T18:09:24+01:00
rts: trigger a major collection if megablock usage exceeds maxHeapSize

When the heap is suffering from block fragmentation, live bytes might be
low while megablock usage is high.

If megablock usage exceeds maxHeapSize, we want to trigger a major GC to
try to recover some memory otherwise we will die from a heapOverflow at
the end of the GC.

Fixes #21927

- - - - -
4a4641ca by Teo Camarasu at 2022-10-15T18:11:29+01:00
Add realease note for #21927

- - - - -
c1e5719a by Sebastian Graf at 2022-10-17T11:58:46-04:00
DmdAnal: Look through unfoldings of DataCon wrappers (#22241)

Previously, the demand signature we computed upfront for a DataCon wrapper

lacked boxity information and was much less precise than the demand transformer

for the DataCon worker.

In this patch we adopt the solution to look through unfoldings of DataCon

wrappers during Demand Analysis, but still attach a demand signature for other

passes such as the Simplifier.

See `Note [DmdAnal for DataCon wrappers]` for more details.

Fixes #22241.

- - - - -
8c72411d by Gergo ERDI at 2022-10-17T19:20:04-04:00
Add `Enum (Down a)` instance that swaps `succ` and `pred`

See https://github.com/haskell/core-libraries-committee/issues/51 for
discussion. The key points driving the implementation are the following
two ideas:

* For the `Int` type, `comparing (complement @Int)` behaves exactly as
  an order-swapping `compare @Int`.
* `enumFrom @(Down a)` can be implemented in terms of `enumFromThen @a`,
  if only the corner case of starting at the very end is handled specially

- - - - -
d80ad2f4 by Alan Zimmerman at 2022-10-17T19:20:40-04:00
Update the check-exact infrastructure to match ghc-exactprint

GHC tests the exact print annotations using the contents of
utils/check-exact.

The same functionality is provided via
https://github.com/alanz/ghc-exactprint

The latter was updated to ensure it works with all of the files on
hackage when 9.2 was released, as well as updated to ensure users of
the library could work properly (apply-refact, retrie, etc).

This commit brings the changes from ghc-exactprint into
GHC/utils/check-exact, adapting for the changes to master.

Once it lands, it will form the basis for the 9.4 version of
ghc-exactprint.

See also discussion around this process at #21355

- - - - -
08ab5419 by Andreas Klebinger at 2022-10-17T19:21:15-04:00
Avoid allocating intermediate lists for non recursive bindings.

We do so by having an explicit folding function that doesn't need to
allocate intermediate lists first.

Fixes #22196

- - - - -
ff6275ef by Andreas Klebinger at 2022-10-17T19:21:52-04:00
Testsuite: Add a new tables_next_to_code predicate.

And use it to avoid T21710a failing on non-tntc archs.

Fixes #22169

- - - - -
abb82f38 by Eric Lindblad at 2022-10-17T19:22:33-04:00
example rewrite
- - - - -
39beb801 by Eric Lindblad at 2022-10-17T19:22:33-04:00
remove redirect
- - - - -
0d9fb651 by Eric Lindblad at 2022-10-17T19:22:33-04:00
use heredoc
- - - - -
0fa2d185 by Matthew Pickering at 2022-10-17T19:23:10-04:00
testsuite: Fix typo when setting llvm_ways

Since 2014 llvm_ways has been set to [] so none of the tests which use
only_ways(llvm_ways) have worked as expected.

Hopefully the tests still pass with this typo fix!

- - - - -
ced664a2 by Krzysztof Gogolewski at 2022-10-17T19:23:10-04:00
Fix T15155l not getting -fllvm

- - - - -
0ac60423 by Andreas Klebinger at 2022-10-18T03:34:47-04:00
Fix GHCis interaction with tag inference.

I had assumed that wrappers were not inlined in interactive mode.
Meaning we would always execute the compiled wrapper which properly
takes care of upholding the strict field invariant.
This turned out to be wrong. So instead we now run tag inference even
when we generate bytecode. In that case only for correctness not
performance reasons although it will be still beneficial for runtime
in some cases.

I further fixed a bug where GHCi didn't tag nullary constructors
properly when used as arguments. Which caused segfaults when calling
into compiled functions which expect the strict field invariant to
be upheld.

Fixes #22042 and #21083

-------------------------
Metric Increase:
    T4801

Metric Decrease:
    T13035
-------------------------

- - - - -
9ecd1ac0 by M Farkas-Dyck at 2022-10-18T03:35:38-04:00
Make `Functor` a superclass of `TrieMap`, which lets us derive the `map` functions.

- - - - -
f60244d7 by Ben Gamari at 2022-10-18T03:36:15-04:00
configure: Bump minimum bootstrap GHC version

Fixes #22245

- - - - -
ba4bd4a4 by Matthew Pickering at 2022-10-18T03:36:55-04:00
Build System: Remove out-of-date comment about make build system

Both make and hadrian interleave compilation of modules of different
modules and don't respect the package boundaries. Therefore I just
remove this comment which points out this "difference".

Fixes #22253

- - - - -
e1bbd368 by Matthew Pickering at 2022-10-18T16:15:49+02:00
Allow configuration of error message printing

This MR implements the idea of #21731 that the printing of a diagnostic
method should be configurable at the printing time.

The interface of the `Diagnostic` class is modified from:

```
class Diagnostic a where
  diagnosticMessage :: a -> DecoratedSDoc
  diagnosticReason  :: a -> DiagnosticReason
  diagnosticHints   :: a -> [GhcHint]
```

to

```
class Diagnostic a where
  type DiagnosticOpts a
  defaultDiagnosticOpts :: DiagnosticOpts a
  diagnosticMessage :: DiagnosticOpts a -> a -> DecoratedSDoc
  diagnosticReason  :: a -> DiagnosticReason
  diagnosticHints   :: a -> [GhcHint]
```

and so each `Diagnostic` can implement their own configuration record
which can then be supplied by a client in order to dictate how to print
out the error message.

At the moment this only allows us to implement #21722 nicely but in
future it is more natural to separate the configuration of how much
information we put into an error message and how much we decide to print
out of it.

Updates Haddock submodule

- - - - -
99dc3e3d by Matthew Pickering at 2022-10-18T16:15:53+02:00
Add -fsuppress-error-contexts to disable printing error contexts in errors

In many development environments, the source span is the primary means
of seeing what an error message relates to, and the In the expression:
and In an equation for: clauses are not particularly relevant. However,
they can grow to be quite long, which can make the message itself both
feel overwhelming and interact badly with limited-space areas.

It's simple to implement this flag so we might as well do it and give
the user control about how they see their messages.

Fixes #21722

- - - - -
5b3a992f by Dai at 2022-10-19T10:45:45-04:00
Add VecSlot for unboxed sums of SIMD vectors

This patch adds the missing `VecRep` case to `primRepSlot` function and
all the necessary machinery to carry this new `VecSlot` through code
generation. This allows programs involving unboxed sums of SIMD vectors
to be written and compiled.

Fixes #22187

- - - - -
6d7d9181 by sheaf at 2022-10-19T10:45:45-04:00
Remove SIMD conversions

This patch makes it so that packing/unpacking SIMD
vectors always uses the right sized types, e.g.
unpacking a Word16X4# will give a tuple of Word16#s.

As a result, we can get rid of the conversion instructions
that were previously required.

Fixes #22296

- - - - -
3be48877 by sheaf at 2022-10-19T10:45:45-04:00
Cmm Lint: relax SIMD register assignment check

As noted in #22297, SIMD vector registers can be used
to store different kinds of values, e.g. xmm1 can be used
both to store integer and floating point values.
The Cmm type system doesn't properly account for this, so
we weaken the Cmm register assignment lint check to only
compare widths when comparing a vector type with its
allocated vector register.

- - - - -
f7b7a312 by sheaf at 2022-10-19T10:45:45-04:00
Disable some SIMD tests on non-X86 architectures

- - - - -
83638dce by M Farkas-Dyck at 2022-10-19T10:46:29-04:00
Scrub various partiality involving lists (again).

Lets us avoid some use of `head` and `tail`, and some panics.

- - - - -
c3732c62 by M Farkas-Dyck at 2022-10-19T10:47:13-04:00
Enforce invariant of `ListBag` constructor.

- - - - -
488d3631 by Bodigrim at 2022-10-19T10:47:52-04:00
More precise types for fields of OverlappingInstances and UnsafeOverlap in TcSolverReportMsg

It's clear from asserts in `GHC.Tc.Errors` that `overlappingInstances_matches`
and `unsafeOverlapped` are supposed to be non-empty, and `unsafeOverlap_matches`
contains a single instance, but these invariants are immediately lost afterwards
and not encoded in types. This patch enforces the invariants by pattern matching
and makes types more precise, avoiding asserts and partial functions such as `head`.

- - - - -
607ce263 by sheaf at 2022-10-19T10:47:52-04:00
Rename unsafeOverlap_matches -> unsafeOverlap_match in UnsafeOverlap
- - - - -
1fab9598 by Matthew Pickering at 2022-10-19T10:48:29-04:00
Add SpliceTypes test for hie files

This test checks that typed splices and quotes get the right type
information when used in hiefiles.

See #21619

- - - - -
a8b52786 by Jan Hrček at 2022-10-19T10:49:09-04:00
Small language fixes in 'Using GHC'

- - - - -
1dab1167 by Gergő Érdi at 2022-10-19T10:49:51-04:00
Fix typo in `Opt_WriteIfSimplifiedCore`'s name

- - - - -
b17cfc9c by sheaf at 2022-10-19T10:50:37-04:00
TyEq:N assertion: only for saturated applications

The assertion that checked TyEq:N in canEqCanLHSFinish incorrectly
triggered in the case of an unsaturated newtype TyCon heading the RHS,
even though we can't unwrap such an application. Now, we only trigger
an assertion failure in case of a saturated application of a newtype
TyCon.

Fixes #22310

- - - - -
ff6f2228 by M Farkas-Dyck at 2022-10-20T16:15:51-04:00
CoreToStg: purge `DynFlags`.

- - - - -
1ebd521f by Matthew Pickering at 2022-10-20T16:16:27-04:00
ci: Make fat014 test robust

For some reason I implemented this as a makefile test rather than a
ghci_script test. Hopefully making it a ghci_script test makes it more
robust.

Fixes #22313

- - - - -
8cd6f435 by Curran McConnell at 2022-10-21T02:58:01-04:00
remove a no-warn directive from GHC.Cmm.ContFlowOpt

This patch is motivated by the desire to remove the {-# OPTIONS_GHC
-fno-warn-incomplete-patterns #-} directive at the top of
GHC.Cmm.ContFlowOpt. (Based on the text in this coding standards doc, I
understand it's a goal of the project to remove such directives.) I
chose this task because I'm a new contributor to GHC, and it seemed like
a good way to get acquainted with the patching process.

In order to address the warning that arose when I removed the no-warn
directive, I added a case to removeUnreachableBlocksProc to handle the
CmmData constructor. Clearly, since this partial function has not been
erroring out in the wild, its inputs are always in practice wrapped by
the CmmProc constructor. Therefore the CmmData case is handled by a
precise panic (which is an improvement over the partial pattern match
from before).

- - - - -
a2af7c4c by Nicolas Trangez at 2022-10-21T02:58:39-04:00
build: get rid of `HAVE_TIME_H`

As advertized by `autoreconf`:

> All current systems provide time.h; it need not be checked for.

Hence, remove the check for it in `configure.ac` and remove conditional
inclusion of the header in `HAVE_TIME_H` blocks where applicable.

The `time.h` header was being included in various source files without a
`HAVE_TIME_H` guard already anyway.

- - - - -
25cdc630 by Nicolas Trangez at 2022-10-21T02:58:39-04:00
rts: remove use of `TIME_WITH_SYS_TIME`

`autoreconf` will insert an `m4_warning` when the obsolescent
`AC_HEADER_TIME` macro is used:

> Update your code to rely only on HAVE_SYS_TIME_H,
> then remove this warning and the obsolete code below it.
> All current systems provide time.h; it need not be checked for.
> Not all systems provide sys/time.h, but those that do, all allow
> you to include it and time.h simultaneously.

Presence of `sys/time.h` was already checked in an earlier
`AC_CHECK_HEADERS` invocation, so `AC_HEADER_TIME` can be dropped and
guards relying on `TIME_WITH_SYS_TIME` can be reworked to
(unconditionally) include `time.h` and include `sys/time.h` based on
`HAVE_SYS_TIME_H`.

Note the documentation of `AC_HEADER_TIME` in (at least) Autoconf 2.67
says

> This macro is obsolescent, as current systems can include both files
> when they exist. New programs need not use this macro.

- - - - -
1fe7921c by Eric Lindblad at 2022-10-21T02:59:21-04:00
runhaskell
- - - - -
e3b3986e by David Feuer at 2022-10-21T03:00:00-04:00
Document how to quote certain names with spaces

Quoting a name for Template Haskell is a bit tricky if the second
character of that name is a single quote. The User's Guide falsely
claimed that it was impossible. Document how to do it.

Fixes #22236
- - - - -
0eba81e8 by Krzysztof Gogolewski at 2022-10-21T03:00:00-04:00
Fix syntax
- - - - -
a4dbd102 by Ben Gamari at 2022-10-21T09:11:12-04:00
Fix manifest filename when writing Windows .rc files

As noted in #12971, we previously used `show` which resulted in
inappropriate escaping of non-ASCII characters.

- - - - -
30f0d9a9 by Ben Gamari at 2022-10-21T09:11:12-04:00
Write response files in UTF-8 on Windows

This reverts the workaround introduced in
f63c8ef33ec9666688163abe4ccf2d6c0428a7e7, which taught our response file
logic to write response files with the `latin1` encoding to workaround
`gcc`'s lacking Unicode support. This is now no longer necessary (and in
fact actively unhelpful) since we rather use Clang.

- - - - -
b8304648 by M Farkas-Dyck at 2022-10-21T09:11:56-04:00
Scrub some partiality in `GHC.Core.Opt.Simplify.Utils`.

- - - - -
09ec7de2 by Teo Camarasu at 2022-10-21T13:23:07-04:00
template-haskell: Improve documentation of strictness annotation types

Before it was undocumentated that DecidedLazy can be returned by
reifyConStrictness for strict fields. This can happen when a field has
an unlifted type or its the single field of a newtype constructor.

Fixes #21380

- - - - -
88172069 by M Farkas-Dyck at 2022-10-21T13:23:51-04:00
Delete `eqExpr`, since GHC 9.4 has been released.

- - - - -
86e6549e by Ömer Sinan Ağacan at 2022-10-22T07:41:30-04:00
Introduce a standard thunk for allocating strings

Currently for a top-level closure in the form

    hey = unpackCString# x

we generate code like this:

    Main.hey_entry() //  [R1]
             { info_tbls: [(c2T4,
                            label: Main.hey_info
                            rep: HeapRep static { Thunk }
                            srt: Nothing)]
               stack_info: arg_space: 8 updfr_space: Just 8
             }
         {offset
           c2T4: // global
               _rqm::P64 = R1;
               if ((Sp + 8) - 24 < SpLim) (likely: False) goto c2T5; else goto c2T6;
           c2T5: // global
               R1 = _rqm::P64;
               call (stg_gc_enter_1)(R1) args: 8, res: 0, upd: 8;
           c2T6: // global
               (_c2T1::I64) = call "ccall" arg hints:  [PtrHint,
                                                        PtrHint]  result hints:  [PtrHint] newCAF(BaseReg, _rqm::P64);
               if (_c2T1::I64 == 0) goto c2T3; else goto c2T2;
           c2T3: // global
               call (I64[_rqm::P64])() args: 8, res: 0, upd: 8;
           c2T2: // global
               I64[Sp - 16] = stg_bh_upd_frame_info;
               I64[Sp - 8] = _c2T1::I64;
               R2 = hey1_r2Gg_bytes;
               Sp = Sp - 16;
               call GHC.CString.unpackCString#_info(R2) args: 24, res: 0, upd: 24;
         }
     }

This code is generated for every string literal. Only difference between
top-level closures like this is the argument for the bytes of the string
(hey1_r2Gg_bytes in the code above).

With this patch we introduce a standard thunk in the RTS, called
stg_MK_STRING_info, that does what `unpackCString# x` does, except it
gets the bytes address from the payload. Using this, for the closure
above, we generate this:

    Main.hey_closure" {
        Main.hey_closure:
            const stg_MK_STRING_info;
            const 0; // padding for indirectee
            const 0; // static link
            const 0; // saved info
            const hey1_r1Gg_bytes; // the payload
    }

This is much smaller in code.

Metric Decrease:
    T10421
    T11195
    T12150
    T12425
    T16577
    T18282
    T18698a
    T18698b

Co-Authored By: Ben Gamari <ben at well-typed.com>

- - - - -
1937016b by Andreas Klebinger at 2022-10-22T07:42:06-04:00
hadrian: Improve error for wrong key/value errors.

- - - - -
11fe42d8 by Vladislav Zavialov at 2022-10-23T00:11:50+03:00
Class layout info (#19623)

Updates the haddock submodule.

- - - - -
f0a90c11 by Sven Tennie at 2022-10-24T00:12:51-04:00
Pin used way for test cloneMyStack (#21977)

cloneMyStack checks the order of closures on the cloned stack. This may
change for different ways. Thus we limit this test to one way (normal).

- - - - -
0614e74d by Aaron Allen at 2022-10-24T17:11:21+02:00
Convert Diagnostics in GHC.Tc.Gen.Splice (#20116)

Replaces uses of `TcRnUnknownMessage` in `GHC.Tc.Gen.Splice` with
structured diagnostics.

closes #20116

- - - - -
8d2dbe2d by Andreas Klebinger at 2022-10-24T15:59:41-04:00
Improve stg lint for unboxed sums.

It now properly lints cases where sums end up distributed
over multiple args after unarise.

Fixes #22026.

- - - - -
41406da5 by Simon Peyton Jones at 2022-10-25T18:07:03-04:00
Fix binder-swap bug

This patch fixes #21229 properly, by avoiding doing a
binder-swap on dictionary Ids.  This is pretty subtle, and explained
in Note [Care with binder-swap on dictionaries].

Test is already in simplCore/should_run/T21229

This allows us to restore a feature to the specialiser that we had
to revert: see Note [Specialising polymorphic dictionaries].
(This is done in a separate patch.)

I also modularised things, using a new function scrutBinderSwap_maybe
in all the places where we are (effectively) doing a binder-swap,
notably

* Simplify.Iteration.addAltUnfoldings
* SpecConstr.extendCaseBndrs

In Simplify.Iteration.addAltUnfoldings I also eliminated a guard
    Many <- idMult case_bndr
because we concluded, in #22123, that it was doing no good.

- - - - -
5a997e16 by Simon Peyton Jones at 2022-10-25T18:07:03-04:00
Make the specialiser handle polymorphic specialisation

Ticket #13873 unexpectedly showed that a SPECIALISE pragma made a
program run (a lot) slower, because less specialisation took place
overall. It turned out that the specialiser was missing opportunities
because of quantified type variables.

It was quite easy to fix. The story is given in
    Note [Specialising polymorphic dictionaries]

Two other minor fixes in the specialiser

* There is no benefit in specialising data constructor /wrappers/.
  (They can appear overloaded because they are given a dictionary
  to store in the constructor.)  Small guard in canSpecImport.

* There was a buglet in the UnspecArg case of specHeader, in the
  case where there is a dead binder. We need a LitRubbish filler
  for the specUnfolding stuff.  I expanded
  Note [Drop dead args from specialisations] to explain.

There is a 4% increase in compile time for T15164, because we generate
more specialised code.  This seems OK.

Metric Increase:
    T15164

- - - - -
7f203d00 by Sylvain Henry at 2022-10-25T18:07:43-04:00
Numeric exceptions: replace FFI calls with primops

ghc-bignum needs a way to raise numerical exceptions defined in base
package. At the time we used FFI calls into primops defined in the RTS.
These FFI calls had to be wrapped into hacky bottoming functions because
"foreign import prim" syntax doesn't support giving a bottoming demand
to the foreign call (cf #16929).

These hacky wrapper functions trip up the JavaScript backend (#21078)
because they are polymorphic in their return type. This commit
replaces them with primops very similar to raise# but raising predefined
exceptions.

- - - - -
0988a23d by Sylvain Henry at 2022-10-25T18:08:24-04:00
Enable popcount rewrite rule when cross-compiling

The comment applies only when host's word size < target's word size.
So we can relax the guard.

- - - - -
a2f53ac8 by Sylvain Henry at 2022-10-25T18:09:05-04:00
Add GHC.SysTools.Cpp module

Move doCpp out of the driver to be able to use it in the upcoming JS backend.

- - - - -
1fd7f201 by Ben Gamari at 2022-10-25T18:09:42-04:00
llvm-targets: Add datalayouts for big-endian AArch64 targets

Fixes #22311.

Thanks to @zeldin for the patch.

- - - - -
f5a486eb by Krzysztof Gogolewski at 2022-10-25T18:10:19-04:00
Cleanup String/FastString conversions

Remove unused mkPtrString and isUnderscoreFS.
We no longer use mkPtrString since 1d03d8bef96.

Remove unnecessary conversions between FastString and String and back.

- - - - -
f7bfb40c by Ryan Scott at 2022-10-26T00:01:24-04:00
Broaden the in-scope sets for liftEnvSubst and composeTCvSubst

This patch fixes two distinct (but closely related) buglets that were uncovered
in #22235:

* `liftEnvSubst` used an empty in-scope set, which was not wide enough to cover
  the variables in the range of the substitution. This patch fixes this by
  populating the in-scope set from the free variables in the range of the
  substitution.
* `composeTCvSubst` applied the first substitution argument to the range of the
  second substitution argument, but the first substitution's in-scope set was
  not wide enough to cover the range of the second substutition. We similarly
  fix this issue in this patch by widening the first substitution's in-scope set
  before applying it.

Fixes #22235.

- - - - -
0270cc54 by Vladislav Zavialov at 2022-10-26T00:02:01-04:00
Introduce TcRnWithHsDocContext (#22346)

Before this patch, GHC used withHsDocContext to attach an HsDocContext
to an error message:

	addErr $ mkTcRnUnknownMessage $ mkPlainError noHints (withHsDocContext ctxt msg)

The problem with this approach is that it only works with
TcRnUnknownMessage. But could we attach an HsDocContext to a
structured error message in a generic way? This patch solves
the problem by introducing a new constructor to TcRnMessage:

	data TcRnMessage where
	  ...
	  TcRnWithHsDocContext :: !HsDocContext -> !TcRnMessage -> TcRnMessage
	  ...

- - - - -
9ab31f42 by Sylvain Henry at 2022-10-26T09:32:20+02:00
Testsuite: more precise test options

Necessary for newer cross-compiling backends (JS, Wasm) that don't
support TH yet.

- - - - -
f60a1a62 by Vladislav Zavialov at 2022-10-26T12:17:14-04:00
Use TcRnVDQInTermType in noNestedForallsContextsErr (#20115)

When faced with VDQ in the type of a term, GHC generates the following
error message:

	Illegal visible, dependent quantification in the type of a term
	(GHC does not yet support this)

Prior to this patch, there were two ways this message could have been
generated and represented:

	1. with the dedicated constructor TcRnVDQInTermType
	    (see check_type in GHC.Tc.Validity)
	2. with the transitional constructor TcRnUnknownMessage
	    (see noNestedForallsContextsErr in GHC.Rename.Utils)

Not only this led to duplication of code generating the final SDoc,
it also made it tricky to track the origin of the error message.

This patch fixes the problem by using TcRnVDQInTermType exclusively.

- - - - -
223e159d by Owen Shepherd at 2022-10-27T13:54:33-04:00
Remove source location information from interface files

This change aims to minimize source location information leaking
into interface files, which makes ABI hashes dependent on the
build location.

The `Binary (Located a)` instance has been removed completely.

It seems that the HIE interface still needs the ability to
serialize SrcSpans, but by wrapping the instances, it should
be a lot more difficult to inadvertently add source location
information.

- - - - -
22e3deb9 by Simon Peyton Jones at 2022-10-27T13:55:37-04:00
Add missing dict binds to specialiser

I had forgotten to add the auxiliary dict bindings to the
/unfolding/ of a specialised function.  This caused #22358,
which reports failures when compiling Hackage packages
     fixed-vector
     indexed-traversable

Regression test T22357 is snarfed from indexed-traversable

- - - - -
a8ed36f9 by Evan Relf at 2022-10-27T13:56:36-04:00
Fix broken link to `async` package

- - - - -
750846cd by Zubin Duggal at 2022-10-28T00:49:22-04:00
Pass correct package db when testing stage1.

It used to pick the db for stage-2 which obviously didn't work.

- - - - -
ad612f55 by Krzysztof Gogolewski at 2022-10-28T00:50:00-04:00
Minor SDoc-related cleanup

* Rename pprCLabel to pprCLabelStyle, and use the name pprCLabel
  for a function using CStyle (analogous to pprAsmLabel)
* Move LabelStyle to the CLabel module, it no longer needs to be in Outputable.
* Move calls to 'text' right next to literals, to make sure the text/str
  rule is triggered.
* Remove FastString/String roundtrip in Tc.Deriv.Generate
* Introduce showSDocForUser', which abstracts over a pattern in
  GHCi.UI

- - - - -
c2872f3f by Bryan Richter at 2022-10-28T11:36:34+03:00
CI: Don't run lint-submods on nightly

Fixes #22325

- - - - -
270037fa by Hécate Moonlight at 2022-10-28T19:46:12-04:00
Start the deprecation process for GHC.Pack

- - - - -
d45d8cb3 by M Farkas-Dyck at 2022-11-01T12:47:21-04:00
Drop a kludge for binutils<2.17, which is now over 10 years old.

- - - - -
8ee8b418 by Nicolas Trangez at 2022-11-01T12:47:58-04:00
rts: `name` argument of `createOSThread` can be `const`

Since we don't intend to ever change the incoming string, declare this
to be true.

Also, in the POSIX implementation, the argument is no longer `STG_UNUSED`
(since ee0deb8054da2a597fc5624469b4c44fd769ada2) in any code path.

See: https://gitlab.haskell.org/ghc/ghc/-/commit/ee0deb8054da2a597fc5624469b4c44fd769ada2#note_460080

- - - - -
13b5f102 by Nicolas Trangez at 2022-11-01T12:47:58-04:00
rts: fix lifetime of `start_thread`s `name` value

Since, unlike the code in ee0deb8054da2^, usage of the `name` value
passed to `createOSThread` now outlives said function's lifetime, and
could hence be released by the caller by the time the new thread runs
`start_thread`, it needs to be copied.

See: https://gitlab.haskell.org/ghc/ghc/-/commit/ee0deb8054da2a597fc5624469b4c44fd769ada2#note_460080
See: https://gitlab.haskell.org/ghc/ghc/-/merge_requests/9066

- - - - -
edd175c9 by Nicolas Trangez at 2022-11-01T12:47:58-04:00
rts: fix OS thread naming in ticker

Since ee0deb805, the use of `pthread_setname_np` on Darwin was fixed
when invoking `createOSThread`. However, the 'ticker' has some
thread-creation code which doesn't rely on `createOSThread`, yet also
uses `pthread_setname_np`.

This patch enforces all thread creation to go through a single
function, which uses the (correct) thread-naming code introduced in
ee0deb805.

See: https://gitlab.haskell.org/ghc/ghc/-/commit/ee0deb8054da2a597fc5624469b4c44fd769ada2
See: https://gitlab.haskell.org/ghc/ghc/-/issues/22206
See: https://gitlab.haskell.org/ghc/ghc/-/merge_requests/9066

- - - - -
b7a00113 by Krzysztof Gogolewski at 2022-11-01T12:48:35-04:00
Typo: rename -fwrite-if-simplfied-core to -fwrite-if-simplified-core

- - - - -
30e625e6 by Vladislav Zavialov at 2022-11-01T12:49:10-04:00
ThToHs: fix overzealous parenthesization

Before this patch, when converting from TH.Exp to LHsExpr GhcPs,
the compiler inserted more parentheses than required:

	((f a) (b + c)) d

This was happening because the LHS of the function application was
parenthesized as if it was the RHS.

Now we use funPrec and appPrec appropriately and produce sensibly
parenthesized expressions:

	f a (b + c) d

I also took the opportunity to remove the special case for LamE,
which was not special at all and simply duplicated code.

- - - - -
0560821f by Simon Peyton Jones at 2022-11-01T12:49:47-04:00
Add accurate skolem info when quantifying

Ticket #22379 revealed that skolemiseQuantifiedTyVar was
dropping the passed-in skol_info on the floor when it encountered
a SkolemTv.  Bad!  Several TyCons thereby share a single SkolemInfo
on their binders, which lead to bogus error reports.

- - - - -
38d19668 by Fendor at 2022-11-01T12:50:25-04:00
Expose UnitEnvGraphKey for user-code

- - - - -
77e24902 by Simon Peyton Jones at 2022-11-01T12:51:00-04:00
Shrink test case for #22357

Ryan Scott offered a cut-down repro case
(60 lines instead of more than 700 lines)

- - - - -
4521f649 by Simon Peyton Jones at 2022-11-01T12:51:00-04:00
Add two tests for #17366

- - - - -
6b400d26 by Nicolas Trangez at 2022-11-02T12:06:48-04:00
rts: introduce (and use) `STG_NORETURN`

Instead of sprinkling the codebase with
`GNU(C3)_ATTRIBUTE(__noreturn__)`, add a `STG_NORETURN` macro (for,
basically, the same thing) similar to `STG_UNUSED` and others, and
update the code to use this macro where applicable.

- - - - -
f9638654 by Nicolas Trangez at 2022-11-02T12:06:48-04:00
rts: consistently use `STG_UNUSED`

- - - - -
81a58433 by Nicolas Trangez at 2022-11-02T12:06:48-04:00
rts: introduce (and use) `STG_USED`

Similar to `STG_UNUSED`, have a specific macro for
`__attribute__(used)`.

- - - - -
41e1f748 by Nicolas Trangez at 2022-11-02T12:06:48-04:00
rts: introduce (and use) `STG_MALLOC`

Instead of using `GNUC3_ATTRIBUTE(__malloc__)`, provide a `STG_MALLOC`
macro definition and use it instead.

- - - - -
3a9a8bde by Nicolas Trangez at 2022-11-02T12:06:48-04:00
rts: use `STG_UNUSED`

- - - - -
9ab999de by Nicolas Trangez at 2022-11-02T12:06:48-04:00
rts: specify deallocator of allocating functions

This patch adds a new `STG_MALLOC1` macro (and its counterpart
`STG_MALLOC2` for completeness) which allows to specify the deallocation
function to be used with allocations of allocating functions, and
applies it to `stg*allocBytes`.

It also fixes a case where `free` was used to free up an
`stgMallocBytes` allocation, found by the above change.

See: https://gcc.gnu.org/onlinedocs/gcc/Common-Function-Attributes.html#index-malloc-function-attribute
See: https://gitlab.haskell.org/ghc/ghc/-/issues/22381

- - - - -
81c0c7c9 by Nicolas Trangez at 2022-11-02T12:06:48-04:00
rts: use `alloc_size` attribute

This patch adds the `STG_ALLOC_SIZE1` and `STG_ALLOC_SIZE2` macros which
allow to set the `alloc_size` attribute on functions, when available.

See: https://gcc.gnu.org/onlinedocs/gcc/Common-Function-Attributes.html#index-alloc_005fsize-function-attribute
See: https://gitlab.haskell.org/ghc/ghc/-/issues/22381

- - - - -
99a1d896 by Nicolas Trangez at 2022-11-02T12:06:48-04:00
rts: add and use `STG_RETURNS_NONNULL`

See: https://gcc.gnu.org/onlinedocs/gcc/Common-Function-Attributes.html#index-returns_005fnonnull-function-attribute
See: https://gitlab.haskell.org/ghc/ghc/-/issues/22381

- - - - -
c235b399 by Nicolas Trangez at 2022-11-02T12:06:48-04:00
rts: tag `stgStrndup` as `STG_MALLOC`

See: https://gitlab.haskell.org/ghc/ghc/-/issues/22381

- - - - -
ed81b448 by Oleg Grenrus at 2022-11-02T12:07:27-04:00
Move Symbol implementation note out of public haddock

- - - - -
284fd39c by Ben Gamari at 2022-11-03T01:58:54-04:00
gen-dll: Drop it

Currently it is only used by the make build system, which is soon to be
retired, and it has not built since 41cf758b. We may need to reintroduce
it when dynamic-linking support is introduced on Windows, but we will
cross that bridge once we get there.

Fixes #21753.

- - - - -
24f4f54f by Matthew Pickering at 2022-11-03T01:59:30-04:00
Port foundation numeric tests to GHC testsuite

This commit ports the numeric tests which found a regression in GHC-9.4.

https://github.com/haskell-foundation/foundation/issues/571

Included in the commit is a simple random number generator and
simplified QuickCheck implementation. In future these could be factored
out of this standalone file and reused as a general purpose library
which could be used for other QuickCheck style tests in the testsuite.

See #22282

- - - - -
d51bf7bd by M Farkas-Dyck at 2022-11-03T02:00:13-04:00
git: ignore HIE files.

Cleans up git status if one sets -fwrite-ide-info in hadrian/ghci.

- - - - -
a9fc15b1 by Matthew Pickering at 2022-11-03T02:00:49-04:00
Clarify status of bindings in WholeCoreBindings

Gergo points out that these bindings are tidied, rather than prepd as
the variable claims. Therefore we update the name of the variable to
reflect reality and add a comment to the data type to try to erase any
future confusion.

Fixes #22307

- - - - -
634da448 by Bodigrim at 2022-11-03T21:25:02+00:00
Fix haddocks for GHC.IORef

- - - - -
31125154 by Andreas Klebinger at 2022-11-03T23:08:09-04:00
Export pprTrace and friends from GHC.Prelude.

Introduces GHC.Prelude.Basic which can be used in modules which are a
dependency of the ppr code.

- - - - -
bdc8cbb3 by Bryan Richter at 2022-11-04T10:27:37+02:00
CI: Allow hadrian-ghc-in-ghci to run in nightlies

Since lint-submods doesn't run in nightlies, hadrian-ghc-in-ghci needs
to mark it as "optional" so it can run if the job doesn't exist.

Fixes #22396.

- - - - -
3c0e3793 by Krzysztof Gogolewski at 2022-11-05T00:29:57-04:00
Minor refactor around FastStrings

Pass FastStrings to functions directly, to make sure the rule
for fsLit "literal" fires.

Remove SDoc indirection in GHCi.UI.Tags and GHC.Unit.Module.Graph.

- - - - -
e41b2f55 by Matthew Pickering at 2022-11-05T14:18:10+00:00
Bump unix submodule to 2.8.0.0

Also bumps process and ghc-boot bounds on unix.

For hadrian, when cross-compiling, we add -Wwarn=unused-imports
-Wwarn=unused-top-binds to validation flavour. Further fixes in unix
and/or hsc2hs is needed to make it completely free of warnings; for
the time being, this change is needed to unblock other
cross-compilation related work.

- - - - -
42938a58 by Matthew Pickering at 2022-11-05T14:18:10+00:00
Bump Win32 submodule to 2.13.4.0

Fixes #22098

- - - - -
e7372bc5 by Cheng Shao at 2022-11-06T13:15:22+00:00
Bump ci-images revision

ci-images has recently been updated, including changes needed for wasm32-wasi CI.

- - - - -
88cb9492 by Cheng Shao at 2022-11-06T13:15:22+00:00
Bump gmp-tarballs submodule

Includes a fix for wasm support, doesn't impact other targets.

- - - - -
69427ce9 by Cheng Shao at 2022-11-06T13:15:22+00:00
Bump haskeline submodule

Includes a fix for wasm support, doesn't impact other targets.

- - - - -
5fe11fe6 by Carter Schonwald at 2022-11-07T13:22:14-05:00
bump llvm upper bound
- - - - -
68f49874 by M Farkas-Dyck at 2022-11-08T12:53:55-05:00
Define `Infinite` list and use where appropriate.

Also add perf test for infinite list fusion.

In particular, in `GHC.Core`, often we deal with infinite lists of roles. Also in a few locations we deal with infinite lists of names.

Thanks to simonpj for helping to write the Note [Fusion for `Infinite` lists].

- - - - -
ce726cd2 by Ross Paterson at 2022-11-08T12:54:34-05:00
Fix TypeData issues (fixes #22315 and #22332)

There were two bugs here:

1. Treating type-level constructors as PromotedDataCon doesn't always
   work, in particular because constructors promoted via DataKinds are
   called both T and 'T. (Tests T22332a, T22332b, T22315a, T22315b)
   Fix: guard these cases with isDataKindsPromotedDataCon.

2. Type-level constructors were sent to the code generator, producing
   things like constructor wrappers. (Tests T22332a, T22332b)
   Fix: test for them in isDataTyCon.

Other changes:

* changed the marking of "type data" DataCon's as suggested by SPJ.

* added a test TDGADT for a type-level GADT.

* comment tweaks

* change tcIfaceTyCon to ignore IfaceTyConInfo, so that IfaceTyConInfo
  is used only for pretty printing, not for typechecking. (SPJ)

- - - - -
132f8908 by Jade Lovelace at 2022-11-08T12:55:18-05:00
Clarify msum/asum documentation

- - - - -
bb5888c5 by Jade Lovelace at 2022-11-08T12:55:18-05:00
Add example for (<$)

- - - - -
080fffa1 by Jade Lovelace at 2022-11-08T12:55:18-05:00
Document what Alternative/MonadPlus instances actually do

- - - - -
92ccb8de by Giles Anderson at 2022-11-09T09:27:52-05:00
Use TcRnDiagnostic in GHC.Tc.TyCl.Instance (#20117)

The following `TcRnDiagnostic` messages have been introduced:

TcRnWarnUnsatisfiedMinimalDefinition
TcRnMisplacedInstSig
TcRnBadBootFamInstDeclErr
TcRnIllegalFamilyInstance
TcRnAssocInClassErr
TcRnBadFamInstDecl
TcRnNotOpenFamily

- - - - -
90c5abd4 by Hécate Moonlight at 2022-11-09T09:28:30-05:00
GHCi tags generation phase 2

see #19884

- - - - -
f9f17b68 by Simon Peyton Jones at 2022-11-10T12:20:03+00:00
Fire RULES in the Specialiser

The Specialiser has, for some time, fires class-op RULES in the
specialiser itself: see
   Note [Specialisation modulo dictionary selectors]

This MR beefs it up a bit, so that it fires /all/ RULES in the
specialiser, not just class-op rules.  See
   Note [Fire rules in the specialiser]
The result is a bit more specialisation; see test
   simplCore/should_compile/T21851_2

This pushed me into a bit of refactoring.  I made a new data types
GHC.Core.Rules.RuleEnv, which combines
  - the several source of rules (local, home-package, external)
  - the orphan-module dependencies

in a single record for `getRules` to consult.  That drove a bunch of
follow-on refactoring, including allowing me to remove
cr_visible_orphan_mods from the CoreReader data type.

I moved some of the RuleBase/RuleEnv stuff into GHC.Core.Rule.

The reorganisation in the Simplifier improve compile times a bit
(geom mean -0.1%), but T9961 is an outlier

Metric Decrease:
    T9961

- - - - -
2b3d0bee by Simon Peyton Jones at 2022-11-10T12:21:13+00:00
Make indexError work better

The problem here is described at some length in
Note [Boxity for bottoming functions] and
Note [Reboxed crud for bottoming calls] in GHC.Core.Opt.DmdAnal.

This patch adds a SPECIALISE pragma for indexError, which
makes it much less vulnerable to the problem described in
these Notes.

(This came up in another line of work, where a small change made
indexError do reboxing (in nofib/spectral/simple/table_sort)
that didn't happen before my change.  I've opened #22404
to document the fagility.

- - - - -
399e921b by Simon Peyton Jones at 2022-11-10T12:21:14+00:00
Fix DsUselessSpecialiseForClassMethodSelector msg

The error message for DsUselessSpecialiseForClassMethodSelector
was just wrong (a typo in some earlier work); trivial fix

- - - - -
dac0682a by Sebastian Graf at 2022-11-10T21:16:01-05:00
WorkWrap: Unboxing unboxed tuples is not always useful (#22388)

See Note [Unboxing through unboxed tuples].

Fixes #22388.

- - - - -
1230c268 by Sebastian Graf at 2022-11-10T21:16:01-05:00
Boxity: Handle argument budget of unboxed tuples correctly (#21737)

Now Budget roughly tracks the combined width of all arguments after unarisation.
See the changes to `Note [Worker argument budgets]`.

Fixes #21737.

- - - - -
2829fd92 by Cheng Shao at 2022-11-11T00:26:54-05:00
autoconf: check getpid getuid raise

This patch adds checks for getpid, getuid and raise in autoconf. These
functions are absent in wasm32-wasi and thus needs to be checked.

- - - - -
f5dfd1b4 by Cheng Shao at 2022-11-11T00:26:55-05:00
hadrian: add -Wwarn only for cross-compiling unix

- - - - -
2e6ab453 by Cheng Shao at 2022-11-11T00:26:55-05:00
hadrian: add targetSupportsThreadedRts flag

This patch adds a targetSupportsThreadedRts flag to indicate whether
the target supports the threaded rts at all, different from existing
targetSupportsSMP that checks whether -N is supported by the RTS. All
existing flavours have also been updated accordingly to respect this
flags.

Some targets (e.g. wasm32-wasi) does not support the threaded rts,
therefore this flag is needed for the default flavours to work. It
makes more sense to have proper autoconf logic to check for threading
support, but for the time being, we just set the flag to False iff the
target is wasm32.

- - - - -
8104f6f5 by Cheng Shao at 2022-11-11T00:26:55-05:00
Fix Cmm symbol kind

- - - - -
b2035823 by Norman Ramsey at 2022-11-11T00:26:55-05:00
add the two key graph modules from Martin Erwig's FGL

Martin Erwig's FGL (Functional Graph Library) provides an "inductive"
representation of graphs.  A general graph has labeled nodes and
labeled edges.  The key operation on a graph is to decompose it by
removing one node, together with the edges that connect the node to
the rest of the graph.  There is also an inverse composition
operation.

The decomposition and composition operations make this representation
of graphs exceptionally well suited to implement graph algorithms in
which the graph is continually changing, as alluded to in #21259.

This commit adds `GHC.Data.Graph.Inductive.Graph`, which defines the
interface, and `GHC.Data.Graph.Inductive.PatriciaTree`, which provides
an implementation.  Both modules are taken from `fgl-5.7.0.3` on
Hackage, with these changes:

  - Copyright and license text have been copied into the files
    themselves, not stored separately.

  - Some calls to `error` have been replaced with calls to `panic`.

  - Conditional-compilation support for older versions of GHC,
    `containers`, and `base` has been removed.

- - - - -
3633a5f5 by Norman Ramsey at 2022-11-11T00:26:55-05:00
add new modules for reducibility and WebAssembly translation

- - - - -
df7bfef8 by Cheng Shao at 2022-11-11T00:26:55-05:00
Add support for the wasm32-wasi target tuple

This patch adds the wasm32-wasi tuple support to various places in the
tree: autoconf, hadrian, ghc-boot and also the compiler. The codegen
logic will come in subsequent commits.

- - - - -
32ae62e6 by Cheng Shao at 2022-11-11T00:26:55-05:00
deriveConstants: parse .ll output for wasm32 due to broken nm

This patch makes deriveConstants emit and parse an .ll file when
targeting wasm. It's a necessary workaround for broken llvm-nm on
wasm, which isn't capable of reporting correct constant values when
parsing an object.

- - - - -
07e92c92 by Cheng Shao at 2022-11-11T00:26:55-05:00
rts: workaround cmm's improper variadic ccall breaking wasm32 typechecking

Unlike other targets, wasm requires the function signature of the call
site and callee to strictly match. So in Cmm, when we call a C
function that actually returns a value, we need to add an _unused
local variable to receive it, otherwise type error awaits.

An even bigger problem is calling variadic functions like barf() and
such. Cmm doesn't support CAPI calling convention yet, so calls to
variadic functions just happen to work in some cases with some
target's ABI. But again, it doesn't work with wasm. Fortunately, the
wasm C ABI lowers varargs to a stack pointer argument, and it can be
passed NULL when no other arguments are expected to be passed. So we
also add the additional unused NULL arguments to those functions, so
to fix wasm, while not affecting behavior on other targets.

- - - - -
00124d12 by Cheng Shao at 2022-11-11T00:26:55-05:00
testsuite: correct sleep() signature in T5611

In libc, sleep() returns an integer. The ccall type signature should
match the libc definition, otherwise it causes linker error on wasm.

- - - - -
d72466a9 by Cheng Shao at 2022-11-11T00:26:55-05:00
rts: prefer ffi_type_void over FFI_TYPE_VOID

This patch uses ffi_type_void instead of FFI_TYPE_VOID in the
interpreter code, since the FFI_TYPE_* macros are not available in
libffi-wasm32 yet. The libffi public documentation also only mentions
the lower-case ffi_type_* symbols, so we should prefer the lower-case
API here.

- - - - -
4d36a1d3 by Cheng Shao at 2022-11-11T00:26:55-05:00
rts: don't define RTS_USER_SIGNALS when signal.h is not present

In the rts, we have a RTS_USER_SIGNALS macro, and most signal-related
logic is guarded with RTS_USER_SIGNALS. This patch extends the range
of code guarded with RTS_USER_SIGNALS, and define RTS_USER_SIGNALS iff
signal.h is actually detected by autoconf. This is required for
wasm32-wasi to work, which lacks signals.

- - - - -
3f1e164f by Cheng Shao at 2022-11-11T00:26:55-05:00
rts: use HAVE_GETPID to guard subprocess related logic

We've previously added detection of getpid() in autoconf. This patch
uses HAVE_GETPID to guard some subprocess related logic in the RTS.
This is required for certain targets like wasm32-wasi, where there
isn't a process model at all.

- - - - -
50bf5e77 by Cheng Shao at 2022-11-11T00:26:55-05:00
rts: IPE.c: don't do mutex stuff when THREADED_RTS is not defined

This patch adds the missing THREADED_RTS CPP guard to mutex logic in
IPE.c.

- - - - -
ed3b3da0 by Cheng Shao at 2022-11-11T00:26:55-05:00
rts: genericRaise: use exit() instead when not HAVE_RAISE

We check existence of raise() in autoconf, and here, if not
HAVE_RAISE, we should use exit() instead in genericRaise.

- - - - -
c0ba1547 by Cheng Shao at 2022-11-11T00:26:55-05:00
rts: checkSuid: don't do it when not HAVE_GETUID

When getuid() is not present, don't do checkSuid since it doesn't make
sense anyway on that target.

- - - - -
d2d6dfd2 by Cheng Shao at 2022-11-11T00:26:55-05:00
rts: wasm32 placeholder linker

This patch adds minimal placeholder linker logic for wasm32, just
enough to unblock compiling rts on wasm32. RTS linker functionality is
not properly implemented yet for wasm32.

- - - - -
65ba3285 by Cheng Shao at 2022-11-11T00:26:55-05:00
rts: RtsStartup: chdir to PWD on wasm32

This patch adds a wasm32-specific behavior to RtsStartup logic. When
the PWD environment variable is present, we chdir() to it first.

The point is to workaround an issue in wasi-libc: it's currently not
possible to specify the initial working directory, it always defaults
to / (in the virtual filesystem mapped from some host directory). For
some use cases this is sufficient, but there are some other cases
(e.g. in the testsuite) where the program needs to access files
outside.

- - - - -
65b82542 by Cheng Shao at 2022-11-11T00:26:55-05:00
rts: no timer for wasm32

Due to the lack of threads, on wasm32 there can't be a background
timer that periodically resets the context switch flag. This patch
disables timer for wasm32, and also makes the scheduler default to -C0
on wasm32 to avoid starving threads.

- - - - -
e007586f by Cheng Shao at 2022-11-11T00:26:55-05:00
rts: RtsSymbols: empty RTS_POSIX_ONLY_SYMBOLS for wasm32

The default RTS_POSIX_ONLY_SYMBOLS doesn't make sense on wasm32.

- - - - -
0e33f667 by Cheng Shao at 2022-11-11T00:26:55-05:00
rts: Schedule: no FORKPROCESS_PRIMOP_SUPPORTED on wasm32

On wasm32 there isn't a process model at all, so no
FORKPROCESS_PRIMOP_SUPPORTED.

- - - - -
88bbdb31 by Cheng Shao at 2022-11-11T00:26:55-05:00
rts: LibffiAdjustor: adapt to ffi_alloc_prep_closure interface for wasm32

libffi-wasm32 only supports non-standard libffi closure api via
ffi_alloc_prep_closure(). This patch implements
ffi_alloc_prep_closure() via standard libffi closure api on other
targets, and uses it to implement adjustor functionality.

- - - - -
15138746 by Cheng Shao at 2022-11-11T00:26:55-05:00
rts: don't return memory to OS on wasm32

This patch makes the storage manager not return any memory on wasm32.
The detailed reason is described in Note [Megablock allocator on
wasm].

- - - - -
631af3cc by Cheng Shao at 2022-11-11T00:26:55-05:00
rts: make flushExec a no-op on wasm32

This patch makes flushExec a no-op on wasm32, since there's no such
thing as executable memory on wasm32 in the first place.

- - - - -
654a3d46 by Cheng Shao at 2022-11-11T00:26:55-05:00
rts: RtsStartup: don't call resetTerminalSettings, freeThreadingResources on wasm32

This patch prevents resetTerminalSettings and freeThreadingResources
to be called on wasm32, since there is no TTY or threading on wasm32
at all.

- - - - -
f271e7ca by Cheng Shao at 2022-11-11T00:26:55-05:00
rts: OSThreads.h: stub types for wasm32

This patch defines stub Condition/Mutex/OSThreadId/ThreadLocalKey
types for wasm32, just enough to unblock compiling RTS. Any
threading-related functionality has been patched to be disabled on
wasm32.

- - - - -
a6ac67b0 by Cheng Shao at 2022-11-11T00:26:55-05:00
Add register mapping for wasm32

This patch adds register mapping logic for wasm32. See Note [Register
mapping on WebAssembly] in wasm32 NCG for more description.

- - - - -
d7b33982 by Cheng Shao at 2022-11-11T00:26:55-05:00
rts: wasm32 specific logic

This patch adds the rest of wasm32 specific logic in rts.

- - - - -
7f59b0f3 by Cheng Shao at 2022-11-11T00:26:55-05:00
base: fall back to using monotonic clock to emulate cputime on wasm32

On wasm32, we have to fall back to using monotonic clock to emulate
cputime, since there's no native support for cputime as a clock id.

- - - - -
5fcbae0b by Cheng Shao at 2022-11-11T00:26:55-05:00
base: more autoconf checks for wasm32

This patch adds more autoconf checks to base, since those functions
and headers may exist on other POSIX systems but don't exist on
wasm32.

- - - - -
00a9359f by Cheng Shao at 2022-11-11T00:26:55-05:00
base: avoid using unsupported posix functionality on wasm32

This base patch avoids using unsupported posix functionality on
wasm32.

- - - - -
34b8f611 by Cheng Shao at 2022-11-11T00:26:55-05:00
autoconf: set CrossCompiling=YES in cross bindist configure

This patch fixes the bindist autoconf logic to properly set
CrossCompiling=YES when it's a cross GHC bindist.

- - - - -
5ebeaa45 by Cheng Shao at 2022-11-11T00:26:55-05:00
compiler: add util functions for UniqFM and UniqMap

This patch adds addToUFM_L (backed by insertLookupWithKey),
addToUniqMap_L and intersectUniqMap_C. These UniqFM/UniqMap util
functions are used by the wasm32 NCG.

- - - - -
177c56c1 by Cheng Shao at 2022-11-11T00:26:55-05:00
driver: avoid -Wl,--no-as-needed for wasm32

The driver used to pass -Wl,--no-as-needed for LLD linking. This is
actually only supported for ELF targets, and must be avoided when
linking for wasm32.

- - - - -
06f01c74 by Cheng Shao at 2022-11-11T00:26:55-05:00
compiler: allow big arith for wasm32

This patch enables Cmm big arithmetic on wasm32, since 64-bit
arithmetic can be efficiently lowered to wasm32 opcodes.

- - - - -
df6bb112 by Cheng Shao at 2022-11-11T00:26:55-05:00
driver: pass -Wa,--no-type-check for wasm32 when runAsPhase

This patch passes -Wa,--no-type-check for wasm32 when compiling
assembly. See the added note for more detailed explanation.

- - - - -
c1fe4ab6 by Cheng Shao at 2022-11-11T00:26:55-05:00
compiler: enforce cmm switch planning for wasm32

This patch forcibly enable Cmm switch planning for wasm32, since
otherwise the switch tables we generate may exceed the br_table
maximum allowed size.

- - - - -
a8adc71e by Cheng Shao at 2022-11-11T00:26:55-05:00
compiler: annotate CmmFileEmbed with blob length

This patch adds the blob length field to CmmFileEmbed. The wasm32 NCG
needs to know the precise size of each data segment.

- - - - -
36340328 by Cheng Shao at 2022-11-11T00:26:55-05:00
compiler: wasm32 NCG

This patch adds the wasm32 NCG.

- - - - -
435f42ea by Cheng Shao at 2022-11-11T00:26:55-05:00
ci: add wasm32-wasi release bindist job

- - - - -
d8262fdc by Cheng Shao at 2022-11-11T00:26:55-05:00
ci: add a stronger test for cross bindists

This commit adds a simple GHC API program that parses and reprints the
original hello world program used for basic testing of cross bindists.
Before there's full cross-compilation support in the test suite
driver, this provides better coverage than the original test.

- - - - -
8e6ae882 by Cheng Shao at 2022-11-11T00:26:55-05:00
CODEOWNERS: add wasm-specific maintainers

- - - - -
707d5651 by Zubin Duggal at 2022-11-11T00:27:31-05:00
Clarify that LLVM upper bound is non-inclusive during configure (#22411)

- - - - -
430eccef by Ben Gamari at 2022-11-11T13:16:45-05:00
rts: Check for program_invocation_short_name via autoconf

Instead of assuming support on all Linuxes.

- - - - -
6dab0046 by Matthew Pickering at 2022-11-11T13:17:22-05:00
driver: Fix -fdefer-diagnostics flag

The `withDeferredDiagnostics` wrapper wasn't doing anything because the
session it was modifying wasn't used in hsc_env. Therefore the fix is
simple, just push the `getSession` call into the scope of
`withDeferredDiagnostics`.

Fixes #22391

- - - - -
d0c691b6 by Simon Peyton Jones at 2022-11-11T13:18:07-05:00
Add a fast path for data constructor workers

See Note [Fast path for data constructors] in
GHC.Core.Opt.Simplify.Iteration

This bypasses lots of expensive logic, in the special case of
applications of data constructors.  It is a surprisingly worthwhile
improvement, as you can see in the figures below.

Metrics: compile_time/bytes allocated
------------------------------------------------
          CoOpt_Read(normal)   -2.0%
    CoOpt_Singletons(normal)   -2.0%
    ManyConstructors(normal)   -1.3%
              T10421(normal)   -1.9% GOOD
             T10421a(normal)   -1.5%
              T10858(normal)   -1.6%
              T11545(normal)   -1.7%
              T12234(optasm)   -1.3%
              T12425(optasm)   -1.9% GOOD
              T13035(normal)   -1.0% GOOD
              T13056(optasm)   -1.8%
              T13253(normal)   -3.3% GOOD
              T15164(normal)   -1.7%
              T15304(normal)   -3.4%
              T15630(normal)   -2.8%
              T16577(normal)   -4.3% GOOD
              T17096(normal)   -1.1%
              T17516(normal)   -3.1%
              T18282(normal)   -1.9%
              T18304(normal)   -1.2%
             T18698a(normal)   -1.2% GOOD
             T18698b(normal)   -1.5% GOOD
              T18923(normal)   -1.3%
               T1969(normal)   -1.3% GOOD
              T19695(normal)   -4.4% GOOD
             T21839c(normal)   -2.7% GOOD
             T21839r(normal)   -2.7% GOOD
               T4801(normal)   -3.8% GOOD
               T5642(normal)   -3.1% GOOD
               T6048(optasm)   -2.5% GOOD
               T9020(optasm)   -2.7% GOOD
               T9630(normal)   -2.1% GOOD
               T9961(normal)  -11.7% GOOD
               WWRec(normal)   -1.0%

                   geo. mean   -1.1%
                   minimum    -11.7%
                   maximum     +0.1%

Metric Decrease:
    T10421
    T12425
    T13035
    T13253
    T16577
    T18698a
    T18698b
    T1969
    T19695
    T21839c
    T21839r
    T4801
    T5642
    T6048
    T9020
    T9630
    T9961

- - - - -
3c37d30b by Krzysztof Gogolewski at 2022-11-11T19:18:39+01:00
Use a more efficient printer for code generation (#21853)

The changes in `GHC.Utils.Outputable` are the bulk of the patch
and drive the rest.
The types `HLine` and `HDoc` in Outputable can be used instead of `SDoc`
and support printing directly to a handle with `bPutHDoc`.
See Note [SDoc versus HDoc] and Note [HLine versus HDoc].

The classes `IsLine` and `IsDoc` are used to make the existing code polymorphic
over `HLine`/`HDoc` and `SDoc`. This is done for X86, PPC, AArch64, DWARF
and dependencies (printing module names, labels etc.).

Co-authored-by: Alexis King <lexi.lambda at gmail.com>

Metric Decrease:
    CoOpt_Read
    ManyAlternatives
    ManyConstructors
    T10421
    T12425
    T12707
    T13035
    T13056
    T13253
    T13379
    T18140
    T18282
    T18698a
    T18698b
    T1969
    T20049
    T21839c
    T21839r
    T3064
    T3294
    T4801
    T5321FD
    T5321Fun
    T5631
    T6048
    T783
    T9198
    T9233

- - - - -
6b92b47f by Matthew Craven at 2022-11-11T18:32:14-05:00
Weaken wrinkle 1 of Note [Scrutinee Constant Folding]

Fixes #22375.

Co-authored-by:  Simon Peyton Jones <simon.peytonjones at gmail.com>

- - - - -
154c70f6 by Simon Peyton Jones at 2022-11-11T23:40:10+00:00
Fix fragile RULE setup in GHC.Float

In testing my type-vs-constraint patch I found that the handling
of Natural literals was very fragile -- and I somehow tripped that
fragility in my work.

So this patch fixes the fragility.
See Note [realToFrac natural-to-float]

This made a big (9%) difference in one existing test in
perf/should_run/T1-359

Metric Decrease:
    T10359

- - - - -
778c6adc by Simon Peyton Jones at 2022-11-11T23:40:10+00:00
Type vs Constraint: finally nailed

This big patch addresses the rats-nest of issues that have plagued
us for years, about the relationship between Type and Constraint.
See #11715/#21623.

The main payload of the patch is:
* To introduce CONSTRAINT :: RuntimeRep -> Type
* To make TYPE and CONSTRAINT distinct throughout the compiler

Two overview Notes in GHC.Builtin.Types.Prim

* Note [TYPE and CONSTRAINT]

* Note [Type and Constraint are not apart]
  This is the main complication.

The specifics

* New primitive types (GHC.Builtin.Types.Prim)
  - CONSTRAINT
  - ctArrowTyCon (=>)
  - tcArrowTyCon (-=>)
  - ccArrowTyCon (==>)
  - funTyCon     FUN     -- Not new
  See Note [Function type constructors and FunTy]
  and Note [TYPE and CONSTRAINT]

* GHC.Builtin.Types:
  - New type Constraint = CONSTRAINT LiftedRep
  - I also stopped nonEmptyTyCon being built-in; it only needs to be wired-in

* Exploit the fact that Type and Constraint are distinct throughout GHC
  - Get rid of tcView in favour of coreView.
  - Many tcXX functions become XX functions.
    e.g. tcGetCastedTyVar --> getCastedTyVar

* Kill off Note [ForAllTy and typechecker equality], in (old)
  GHC.Tc.Solver.Canonical.  It said that typechecker-equality should ignore
  the specified/inferred distinction when comparein two ForAllTys.  But
  that wsa only weakly supported and (worse) implies that we need a separate
  typechecker equality, different from core equality. No no no.

* GHC.Core.TyCon: kill off FunTyCon in data TyCon.  There was no need for it,
  and anyway now we have four of them!

* GHC.Core.TyCo.Rep: add two FunTyFlags to FunCo
  See Note [FunCo] in that module.

* GHC.Core.Type.  Lots and lots of changes driven by adding CONSTRAINT.
  The key new function is sORTKind_maybe; most other changes are built
  on top of that.

  See also `funTyConAppTy_maybe` and `tyConAppFun_maybe`.

* Fix a longstanding bug in GHC.Core.Type.typeKind, and Core Lint, in
  kinding ForAllTys.  See new tules (FORALL1) and (FORALL2) in GHC.Core.Type.
  (The bug was that before (forall (cv::t1 ~# t2). blah), where
  blah::TYPE IntRep, would get kind (TYPE IntRep), but it should be
  (TYPE LiftedRep).  See Note [Kinding rules for types] in GHC.Core.Type.

* GHC.Core.TyCo.Compare is a new module in which we do eqType and cmpType.
  Of course, no tcEqType any more.

* GHC.Core.TyCo.FVs. I moved some free-var-like function into this module:
  tyConsOfType, visVarsOfType, and occCheckExpand.  Refactoring only.

* GHC.Builtin.Types.  Compiletely re-engineer boxingDataCon_maybe to
  have one for each /RuntimeRep/, rather than one for each /Type/.
  This dramatically widens the range of types we can auto-box.
  See Note [Boxing constructors] in GHC.Builtin.Types
  The boxing types themselves are declared in library ghc-prim:GHC.Types.

  GHC.Core.Make.  Re-engineer the treatment of "big" tuples (mkBigCoreVarTup
  etc) GHC.Core.Make, so that it auto-boxes unboxed values and (crucially)
  types of kind Constraint. That allows the desugaring for arrows to work;
  it gathers up free variables (including dictionaries) into tuples.
  See  Note [Big tuples] in GHC.Core.Make.

  There is still work to do here: #22336. But things are better than
  before.

* GHC.Core.Make.  We need two absent-error Ids, aBSENT_ERROR_ID for types of
  kind Type, and aBSENT_CONSTRAINT_ERROR_ID for vaues of kind Constraint.
  Ditto noInlineId vs noInlieConstraintId in GHC.Types.Id.Make;
  see Note [inlineId magic].

* GHC.Core.TyCo.Rep. Completely refactor the NthCo coercion.  It is now called
  SelCo, and its fields are much more descriptive than the single Int we used to
  have.  A great improvement.  See Note [SelCo] in GHC.Core.TyCo.Rep.

* GHC.Core.RoughMap.roughMatchTyConName.  Collapse TYPE and CONSTRAINT to
  a single TyCon, so that the rough-map does not distinguish them.

* GHC.Core.DataCon
  - Mainly just improve documentation

* Some significant renamings:
  GHC.Core.Multiplicity: Many -->  ManyTy (easier to grep for)
                         One  -->  OneTy
  GHC.Core.TyCo.Rep TyCoBinder      -->   GHC.Core.Var.PiTyBinder
  GHC.Core.Var      TyCoVarBinder   -->   ForAllTyBinder
                    AnonArgFlag     -->   FunTyFlag
                    ArgFlag         -->   ForAllTyFlag
  GHC.Core.TyCon    TyConTyCoBinder --> TyConPiTyBinder
  Many functions are renamed in consequence
  e.g. isinvisibleArgFlag becomes isInvisibleForAllTyFlag, etc

* I refactored FunTyFlag (was AnonArgFlag) into a simple, flat data type
    data FunTyFlag
      = FTF_T_T           -- (->)  Type -> Type
      | FTF_T_C           -- (-=>) Type -> Constraint
      | FTF_C_T           -- (=>)  Constraint -> Type
      | FTF_C_C           -- (==>) Constraint -> Constraint

* GHC.Tc.Errors.Ppr.  Some significant refactoring in the TypeEqMisMatch case
  of pprMismatchMsg.

* I made the tyConUnique field of TyCon strict, because I
  saw code with lots of silly eval's.  That revealed that
  GHC.Settings.Constants.mAX_SUM_SIZE can only be 63, because
  we pack the sum tag into a 6-bit field.  (Lurking bug squashed.)

Fixes
* #21530

Updates haddock submodule slightly.

Performance changes
~~~~~~~~~~~~~~~~~~~
I was worried that compile times would get worse, but after
some careful profiling we are down to a geometric mean 0.1%
increase in allocation (in perf/compiler).  That seems fine.

There is a big runtime improvement in T10359

Metric Decrease:
    LargeRecord
    MultiLayerModulesTH_OneShot
    T13386
    T13719
Metric Increase:
    T8095

- - - - -
360f5fec by Simon Peyton Jones at 2022-11-11T23:40:11+00:00
Indent closing "#-}" to silence HLint

- - - - -
e160cf47 by Krzysztof Gogolewski at 2022-11-12T08:05:28-05:00
Fix merge conflict in T18355.stderr

Fixes #22446

- - - - -
294f9073 by Simon Peyton Jones at 2022-11-12T23:14:13+00:00
Fix a trivial typo in dataConNonlinearType

Fixes #22416

- - - - -
268a3ce9 by Ben Gamari at 2022-11-14T09:36:57-05:00
eventlog: Ensure that IPE output contains actual info table pointers

The refactoring in 866c736e introduced a rather subtle change in the
semantics of the IPE eventlog output, changing the eventlog field from
encoding info table pointers to "TNTC pointers" (which point to entry
code when tables-next-to-code is enabled). Fix this.

Fixes #22452.

- - - - -
d91db679 by Matthew Pickering at 2022-11-14T16:48:10-05:00
testsuite: Add tests for T22347

These are fixed in recent versions but might as well add regression
tests.

See #22347

- - - - -
8f6c576b by Matthew Pickering at 2022-11-14T16:48:45-05:00
testsuite: Improve output from tests which have failing pre_cmd

There are two changes:

* If a pre_cmd fails, then don't attempt to run the test.
* If a pre_cmd fails, then print the stdout and stderr from running that
  command (which hopefully has a nice error message).

For example:

```
=====> 1 of 1 [0, 0, 0]
*** framework failure for test-defaulting-plugin(normal) pre_cmd failed: 2
** pre_cmd was "$MAKE -s --no-print-directory -C defaulting-plugin package.test-defaulting-plugin TOP={top}".
stdout:
stderr:
DefaultLifted.hs:19:13: error: [GHC-76037]
    Not in scope: type constructor or class ‘Typ’
    Suggested fix:
      Perhaps use one of these:
        ‘Type’ (imported from GHC.Tc.Utils.TcType),
        data constructor ‘Type’ (imported from GHC.Plugins)
   |
19 | instance Eq Typ where
   |             ^^^
make: *** [Makefile:17: package.test-defaulting-plugin] Error 1

Performance Metrics (test environment: local):
```

Fixes #22329

- - - - -
2b7d5ccc by Madeline Haraj at 2022-11-14T22:44:17+00:00
Implement UNPACK support for sum types.

This is based on osa's unpack_sums PR from ages past.

The meat of the patch is implemented in dataConArgUnpackSum
and described in Note [UNPACK for sum types].

- - - - -
78f7ecb0 by Andreas Klebinger at 2022-11-14T22:20:29-05:00
Expand on the need to clone local binders.

Fixes #22402.

- - - - -
65ce43cc by Krzysztof Gogolewski at 2022-11-14T22:21:05-05:00
Fix :i Constraint printing "type Constraint = Constraint"

Since Constraint became a synonym for CONSTRAINT 'LiftedRep,
we need the same code for handling printing as for the synonym
Type = TYPE 'LiftedRep.
This addresses the same bug as #18594, so I'm reusing the test.

- - - - -
94549f8f by ARATA Mizuki at 2022-11-15T21:36:03-05:00
configure: Don't check for an unsupported version of LLVM

The upper bound is not inclusive.

Fixes #22449

- - - - -
02d3511b by Bodigrim at 2022-11-15T21:36:41-05:00
Fix capitalization in haddock for TestEquality

- - - - -
08bf2881 by Cheng Shao at 2022-11-16T09:16:29+00:00
base: make Foreign.Marshal.Pool use RTS internal arena for allocation

`Foreign.Marshal.Pool` used to call `malloc` once for each allocation
request. Each `Pool` maintained a list of allocated pointers, and
traverses the list to `free` each one of those pointers. The extra O(n)
overhead is apparently bad for a `Pool` that serves a lot of small
allocation requests.

This patch uses the RTS internal arena to implement `Pool`, with these
benefits:

- Gets rid of the extra O(n) overhead.
- The RTS arena is simply a bump allocator backed by the block
  allocator, each allocation request is likely faster than a libc
  `malloc` call.

Closes #14762 #18338.

- - - - -
37cfe3c0 by Krzysztof Gogolewski at 2022-11-16T14:50:06-05:00
Misc cleanup

* Replace catMaybes . map f with mapMaybe f
* Use concatFS to concatenate multiple FastStrings
* Fix documentation of -exclude-module
* Cleanup getIgnoreCount in GHCi.UI

- - - - -
b0ac3813 by Lawton Nichols at 2022-11-19T03:22:14-05:00
Give better errors for code corrupted by Unicode smart quotes (#21843)

Previously, we emitted a generic and potentially confusing error during lexical
analysis on programs containing smart quotes (“/”/‘/’). This commit adds
smart quote-aware lexer errors.

- - - - -
cb8430f8 by Sebastian Graf at 2022-11-19T03:22:49-05:00
Make OpaqueNo* tests less noisy to unrelated changes

- - - - -
b1a8af69 by Sebastian Graf at 2022-11-19T03:22:49-05:00
Simplifier: Consider `seq` as a `BoringCtxt` (#22317)

See `Note [Seq is boring]` for the rationale.

Fixes #22317.

- - - - -
9fd11585 by Sebastian Graf at 2022-11-19T03:22:49-05:00
Make T21839c's ghc/max threshold more forgiving

- - - - -
4b6251ab by Simon Peyton Jones at 2022-11-19T03:23:24-05:00
Be more careful when reporting unbound RULE binders

See Note [Variables unbound on the LHS] in GHC.HsToCore.Binds.

Fixes #22471.

- - - - -
e8f2b80d by Peter Trommler at 2022-11-19T03:23:59-05:00
PPC NCG: Fix generating assembler code

Fixes #22479

- - - - -
f2f9ef07 by Bodigrim at 2022-11-20T18:39:30-05:00
Extend documentation for Data.IORef

- - - - -
ef511b23 by Simon Peyton Jones at 2022-11-20T18:40:05-05:00
Buglet in GHC.Tc.Module.checkBootTyCon

This lurking bug used the wrong function to compare two
types in GHC.Tc.Module.checkBootTyCon

It's hard to trigger the bug, which only came up during
!9343, so there's no regression test in this MR.

- - - - -
451aeac3 by Bodigrim at 2022-11-20T18:40:44-05:00
Add since pragmas for c_interruptible_open and hostIsThreaded

- - - - -
8d6aaa49 by Duncan Coutts at 2022-11-22T02:06:16-05:00
Introduce CapIOManager as the per-cap I/O mangager state

Rather than each I/O manager adding things into the Capability structure
ad-hoc, we should have a common CapIOManager iomgr member of the
Capability structure, with a common interface to initialise etc.

The content of the CapIOManager struct will be defined differently for
each I/O manager implementation. Eventually we should be able to have
the CapIOManager be opaque to the rest of the RTS, and known just to the
I/O manager implementation. We plan for that by making the Capability
contain a pointer to the CapIOManager rather than containing the
structure directly.

Initially just move the Unix threaded I/O manager's control FD.

- - - - -
8901285e by Duncan Coutts at 2022-11-22T02:06:17-05:00
Add hook markCapabilityIOManager

To allow I/O managers to have GC roots in the Capability, within the
CapIOManager structure.

Not yet used in this patch.

- - - - -
5cf709c5 by Duncan Coutts at 2022-11-22T02:06:17-05:00
Move APPEND_TO_BLOCKED_QUEUE from cmm to C

The I/O and delay blocking primitives for the non-threaded way
currently access the blocked_queue and sleeping_queue directly.

We want to move where those queues are to make their ownership clearer:
to have them clearly belong to the I/O manager impls rather than to the
scheduler. Ultimately we will want to change their representation too.

It's inconvenient to do that if these queues are accessed directly from
cmm code. So as a first step, replace the APPEND_TO_BLOCKED_QUEUE with a
C version appendToIOBlockedQueue(), and replace the open-coded
sleeping_queue insertion with insertIntoSleepingQueue().

- - - - -
ced9acdb by Duncan Coutts at 2022-11-22T02:06:17-05:00
Move {blocked,sleeping}_queue from scheduler global vars to CapIOManager

The blocked_queue_{hd,tl} and the sleeping_queue are currently
cooperatively managed between the scheduler and (some but not all of)
the non-threaded I/O manager implementations.

They lived as global vars with the scheduler, but are poked by I/O
primops and the I/O manager backends.

This patch is a step on the path towards making the management of I/O or
timer blocking belong to the I/O managers and not the scheduler.

Specifically, this patch moves the {blocked,sleeping}_queue from being
global vars in the scheduler to being members of the CapIOManager struct
within each Capability. They are not yet exclusively used by the I/O
managers: they are still poked from a couple other places, notably in
the scheduler before calling awaitEvent.

- - - - -
0f68919e by Duncan Coutts at 2022-11-22T02:06:17-05:00
Remove the now-unused markScheduler

The global vars {blocked,sleeping}_queue are now in the Capability and
so get marked there via markCapabilityIOManager.

- - - - -
39a91f60 by Duncan Coutts at 2022-11-22T02:06:17-05:00
Move macros for checking for pending IO or timers

from Schedule.h to Schedule.c and IOManager.h

This is just moving, the next step will be to rejig them slightly.

For the non-threaded RTS the scheduler needs to be able to test for
there being pending I/O operation or pending timers. The implementation
of these tests should really be considered to be part of the I/O
managers and not part of the scheduler.

- - - - -
664b034b by Duncan Coutts at 2022-11-22T02:06:17-05:00
Replace EMPTY_{BLOCKED,SLEEPING}_QUEUE macros by function

These are the macros originaly from Scheduler.h, previously moved to
IOManager.h, and now replaced with a single inline function
anyPendingTimeoutsOrIO(). We can use a single function since the two
macros were always checked together.

Note that since anyPendingTimeoutsOrIO is defined for all IO manager
cases, including threaded, we do not need to guard its use by cpp
 #if !defined(THREADED_RTS)

- - - - -
32946220 by Duncan Coutts at 2022-11-22T02:06:17-05:00
Expand emptyThreadQueues inline for clarity

It was not really adding anything. The name no longer meant anything
since those I/O and timeout queues do not belong to the scheuler.

In one of the two places it was used, the comments already had to
explain what it did, whereas now the code matches the comment nicely.

- - - - -
9943baf9 by Duncan Coutts at 2022-11-22T02:06:17-05:00
Move the awaitEvent declaration into IOManager.h

And add or adjust comments at the use sites of awaitEvent.

- - - - -
054dcc9d by Duncan Coutts at 2022-11-22T02:06:17-05:00
Pass the Capability *cap explicitly to awaitEvent

It is currently only used in the non-threaded RTS so it works to use
MainCapability, but it's a bit nicer to pass the cap anyway. It's
certainly shorter.

- - - - -
667fe5a4 by Duncan Coutts at 2022-11-22T02:06:17-05:00
Pass the Capability *cap explicitly to appendToIOBlockedQueue

And to insertIntoSleepingQueue. Again, it's a bit cleaner and simpler
though not strictly necessary given that these primops are currently
only used in the non-threaded RTS.

- - - - -
7181b074 by Duncan Coutts at 2022-11-22T02:06:17-05:00
Reveiew feedback: improve one of the TODO comments

The one about the nonsense (const False) test on WinIO for there being any IO
or timers pending, leading to unnecessary complication later in the
scheduler.

- - - - -
e5b68183 by Andreas Klebinger at 2022-11-22T02:06:52-05:00
Optimize getLevity.

Avoid the intermediate data structures allocated by splitTyConApp.
This avoids ~0.5% of allocations for a build using -O2.

Fixes #22254

- - - - -
de5fb348 by Andreas Klebinger at 2022-11-22T02:07:28-05:00
hadrian:Set TNTC when running testsuite.

- - - - -
9d61c182 by Oleg Grenrus at 2022-11-22T15:59:34-05:00
Add unsafePtrEquality# restricted to UnliftedTypes

- - - - -
e817c871 by Jonathan Dowland at 2022-11-22T16:00:14-05:00
utils/unlit: adjust parser to match Report spec

The Haskell 2010 Report says that, for Latex-style Literate format,
"Program code begins on the first line following a line that begins
\begin{code}". (This is unchanged from the 98 Report)

However the unlit.c implementation only matches a line that contains
"\begin{code}" and nothing else. One consequence of this is that one
cannot suffix Latex options to the code environment. I.e., this does
not work:

\begin{code}[label=foo,caption=Foo Code]

Adjust the matcher to conform to the specification from the Report.

The Haskell Wiki currently recommends suffixing a '%' to \begin{code}
in order to deliberately hide a code block from Haskell. This is bad
advice, as it's relying on an implementation quirk rather than specified
behaviour. None-the-less, some people have tried to use it, c.f.
<https://mail.haskell.org/pipermail/haskell-cafe/2009-September/066780.html>

An alternative solution is to define a separate, equivalent Latex
environment to "code", that is functionally identical in Latex but
ignored by unlit. This should not be a burden: users are required to
manually define the code environment anyway, as it is not provided
by the Latex verbatim or lstlistings packages usually used for
presenting code in documents.

Fixes #3549.

- - - - -
0b7fef11 by Teo Camarasu at 2022-11-23T12:44:33-05:00
Fix eventlog all option

Previously it didn't enable/disable nonmoving_gc and ticky event types

Fixes #21813

- - - - -
04d0618c by Arnaud Spiwack at 2022-11-23T12:45:14-05:00
Expand Note [Linear types] with the stance on linting linearity

Per the discussion on #22123

- - - - -
e1538516 by Lawton Nichols at 2022-11-23T12:45:55-05:00
Add documentation on custom Prelude modules (#22228)

Specifically, custom Prelude modules that are named `Prelude`.

- - - - -
b5c71454 by Sylvain Henry at 2022-11-23T12:46:35-05:00
Don't let configure perform trivial substitutions (#21846)

Hadrian now performs substitutions, especially to generate .cabal files
from .cabal.in files. Two benefits:

1. We won't have to re-configure when we modify thing.cabal.in. Hadrian
   will take care of this for us.

2. It paves the way to allow the same package to be configured
   differently by Hadrian in the same session. This will be useful to
   fix #19174: we want to build a stage2 cross-compiler for the host
   platform and a stage1 compiler for the cross target platform in the
   same Hadrian session.

- - - - -
99aca26b by nineonine at 2022-11-23T12:47:11-05:00
CApiFFI: add ConstPtr for encoding const-qualified pointer return types (#22043)

Previously, when using `capi` calling convention in foreign declarations,
code generator failed to handle const-cualified pointer return types.
This resulted in CC toolchain throwing `-Wincompatible-pointer-types-discards-qualifiers`
warning.

`Foreign.C.Types.ConstPtr` newtype was introduced to handle these cases -
special treatment was put in place to generate appropritetly qualified C
wrapper that no longer triggers the above mentioned warning.

Fixes #22043

- - - - -
040bfdc3 by M Farkas-Dyck at 2022-11-23T21:59:03-05:00
Scrub some no-warning pragmas.

- - - - -
178c1fd8 by Vladislav Zavialov at 2022-11-23T21:59:39-05:00
Check if the SDoc starts with a single quote (#22488)

This patch fixes pretty-printing of character literals
inside promoted lists and tuples.

When we pretty-print a promoted list or tuple whose first element
starts with a single quote, we want to add a space between the opening
bracket and the element:

	'[True]    -- ok
	'[ 'True]  -- ok
	'['True]   -- not ok

If we don't add the space, we accidentally produce a character
literal '['.

Before this patch, pprSpaceIfPromotedTyCon inspected the type as an AST
and tried to guess if it would be rendered with a single quote. However,
it missed the case when the inner type was itself a character literal:

	'[ 'x']  -- ok
	'['x']   -- not ok

Instead of adding this particular case, I opted for a more future-proof
solution: check the SDoc directly. This way we can detect if the single
quote is actually there instead of trying to predict it from the AST.
The new function is called spaceIfSingleQuote.

- - - - -
11627c42 by Matthew Pickering at 2022-11-23T22:00:15-05:00
notes: Fix references to HPT space leak note

Updating this note was missed when updating the HPT to the HUG.

Fixes #22477

- - - - -
86ff1523 by Andrei Borzenkov at 2022-11-24T17:24:51-05:00
Convert diagnostics in GHC.Rename.Expr to proper TcRnMessage (#20115)

Problem: avoid usage of TcRnMessageUnknown

Solution:
The following `TcRnMessage` messages has been introduced:
  TcRnNoRebindableSyntaxRecordDot
  TcRnNoFieldPunsRecordDot
  TcRnIllegalStaticExpression
  TcRnIllegalStaticFormInSplice
  TcRnListComprehensionDuplicateBinding
  TcRnEmptyStmtsGroup
  TcRnLastStmtNotExpr
  TcRnUnexpectedStatementInContext
  TcRnIllegalTupleSection
  TcRnIllegalImplicitParameterBindings
  TcRnSectionWithoutParentheses

Co-authored-by: sheaf <sam.derbyshire at gmail.com>

- - - - -
d198a19a by Cheng Shao at 2022-11-24T17:25:29-05:00
rts: fix missing Arena.h symbols in RtsSymbols.c

It was an unfortunate oversight in !8961 and broke devel2 builds.

- - - - -
5943e739 by Bodigrim at 2022-11-25T04:38:28-05:00
Assorted fixes to avoid Data.List.{head,tail}

- - - - -
1f1b99b8 by sheaf at 2022-11-25T04:38:28-05:00
Review suggestions for assorted fixes to avoid Data.List.{head,tail}

- - - - -
13d627bb by Vladislav Zavialov at 2022-11-25T04:39:04-05:00
Print unticked promoted data constructors (#20531)

Before this patch, GHC unconditionally printed ticks before promoted
data constructors:

	ghci> type T = True  -- unticked (user-written)
	ghci> :kind! T
	T :: Bool
	= 'True              -- ticked (compiler output)

After this patch, GHC prints ticks only when necessary:

	ghci> type F = False    -- unticked (user-written)
	ghci> :kind! F
	F :: Bool
	= False                 -- unticked (compiler output)

	ghci> data False        -- introduce ambiguity
	ghci> :kind! F
	F :: Bool
	= 'False                -- ticked by necessity (compiler output)

The old behavior can be enabled by -fprint-redundant-promotion-ticks.

Summary of changes:
* Rename PrintUnqualified to NamePprCtx
* Add QueryPromotionTick to it
* Consult the GlobalRdrEnv to decide whether to print a tick (see mkPromTick)
* Introduce -fprint-redundant-promotion-ticks

Co-authored-by: Artyom Kuznetsov <hi at wzrd.ht>

- - - - -
d10dc6bd by Simon Peyton Jones at 2022-11-25T22:31:27+00:00
Fix decomposition of TyConApps

Ticket #22331 showed that we were being too eager to decompose
a Wanted TyConApp, leading to incompleteness in the solver.

To understand all this I ended up doing a substantial rewrite
of the old Note [Decomposing equalities], now reborn as
Note [Decomposing TyConApp equalities]. Plus rewrites of other
related Notes.

The actual fix is very minor and actually simplifies the code: in
`can_decompose` in `GHC.Tc.Solver.Canonical.canTyConApp`, we now call
`noMatchableIrreds`.  A closely related refactor: we stop trying to
use the same "no matchable givens" function here as in
`matchClassInst`.  Instead split into two much simpler functions.

- - - - -
2da5c38a by Will Hawkins at 2022-11-26T04:05:04-05:00
Redirect output of musttail attribute test

Compilation output from test for support of musttail attribute leaked to
the console.

- - - - -
0eb1c331 by Cheng Shao at 2022-11-28T08:55:53+00:00
Move hs_mulIntMayOflo cbits to ghc-prim

It's only used by wasm NCG at the moment, but ghc-prim is a more
reasonable place for hosting out-of-line primops. Also, we only need a
single version of hs_mulIntMayOflo.

- - - - -
36b53a9d by Cheng Shao at 2022-11-28T09:05:57+00:00
compiler: generate ccalls for clz/ctz/popcnt in wasm NCG

We used to generate a single wasm clz/ctz/popcnt opcode, but it's
wrong when it comes to subwords, so might as well generate ccalls for
them. See #22470 for details.

- - - - -
d4134e92 by Cheng Shao at 2022-11-28T23:48:14-05:00
compiler: remove unused MO_U_MulMayOflo

We actually only emit MO_S_MulMayOflo and never emit MO_U_MulMayOflo anywhere.

- - - - -
8d15eadc by Apoorv Ingle at 2022-11-29T03:09:31-05:00
Killing cc_fundeps, streamlining kind equality orientation, and type equality processing order

Fixes: #217093
Associated to #19415

This change
* Flips the orientation of the the generated kind equality coercion in canEqLHSHetero;
* Removes `cc_fundeps` in CDictCan as the check was incomplete;
* Changes `canDecomposableTyConAppOk` to ensure we process kind equalities before type equalities and avoiding a call to `canEqLHSHetero` while processing wanted TyConApp equalities
* Adds 2 new tests for validating the change
   - testsuites/typecheck/should_compile/T21703.hs and
   - testsuites/typecheck/should_fail/T19415b.hs (a simpler version of T19415.hs)
* Misc: Due to the change in the equality direction some error messages now have flipped type mismatch errors
* Changes in Notes:
  - Note [Fundeps with instances, and equality orientation] supercedes Note [Fundeps with instances]
  - Added Note [Kind Equality Orientation] to visualize the kind flipping
  - Added Note [Decomposing Dependent TyCons and Processing Wanted Equalties]

- - - - -
646969d4 by Krzysztof Gogolewski at 2022-11-29T03:10:13-05:00
Change printing of sized literals to match the proposal

Literals in Core were printed as e.g. 0xFF#16 :: Int16#.
The proposal 451 now specifies syntax 0xFF#Int16.
This change affects the Core printer only - more to be done later.

Part of #21422.

- - - - -
02e282ec by Simon Peyton Jones at 2022-11-29T03:10:48-05:00
Be a bit more selective about floating bottoming expressions

This MR arranges to float a bottoming expression to the top
only if it escapes a value lambda.

See #22494 and Note [Floating to the top] in SetLevels.

This has a generally beneficial effect in nofib

+-------------------------------++----------+
|                               ||tsv (rel) |
+===============================++==========+
|           imaginary/paraffins ||   -0.93% |
|                imaginary/rfib ||   -0.05% |
|                      real/fem ||   -0.03% |
|                    real/fluid ||   -0.01% |
|                   real/fulsom ||   +0.05% |
|                   real/gamteb ||   -0.27% |
|                       real/gg ||   -0.10% |
|                   real/hidden ||   -0.01% |
|                      real/hpg ||   -0.03% |
|                      real/scs ||  -11.13% |
|         shootout/k-nucleotide ||   -0.01% |
|               shootout/n-body ||   -0.08% |
|   shootout/reverse-complement ||   -0.00% |
|        shootout/spectral-norm ||   -0.02% |
|             spectral/fibheaps ||   -0.20% |
|           spectral/hartel/fft ||   -1.04% |
|         spectral/hartel/solid ||   +0.33% |
|     spectral/hartel/wave4main ||   -0.35% |
|                 spectral/mate ||   +0.76% |
+===============================++==========+
|                     geom mean ||   -0.12% |

The effect on compile time is generally slightly beneficial

Metrics: compile_time/bytes allocated
----------------------------------------------
MultiLayerModulesTH_OneShot(normal)  +0.3%
                  PmSeriesG(normal)  -0.2%
                  PmSeriesT(normal)  -0.1%
                     T10421(normal)  -0.1%
                    T10421a(normal)  -0.1%
                     T10858(normal)  -0.1%
                     T11276(normal)  -0.1%
                    T11303b(normal)  -0.2%
                     T11545(normal)  -0.1%
                     T11822(normal)  -0.1%
                     T12150(optasm)  -0.1%
                     T12234(optasm)  -0.3%
                     T13035(normal)  -0.2%
                     T16190(normal)  -0.1%
                     T16875(normal)  -0.4%
                    T17836b(normal)  -0.2%
                     T17977(normal)  -0.2%
                    T17977b(normal)  -0.2%
                     T18140(normal)  -0.1%
                     T18282(normal)  -0.1%
                     T18304(normal)  -0.2%
                    T18698a(normal)  -0.1%
                     T18923(normal)  -0.1%
                     T20049(normal)  -0.1%
                    T21839r(normal)  -0.1%
                      T5837(normal)  -0.4%
                      T6048(optasm)  +3.2% BAD
                      T9198(normal)  -0.2%
                      T9630(normal)  -0.1%
       TcPlugin_RewritePerf(normal)  -0.4%
             hard_hole_fits(normal)  -0.1%

                          geo. mean  -0.0%
                          minimum    -0.4%
                          maximum    +3.2%

The T6048 outlier is hard to pin down, but it may be the effect of
reading in more interface files definitions. It's a small program for
which compile time is very short, so I'm not bothered about it.

Metric Increase:
    T6048

- - - - -
ab23dc5e by Ben Gamari at 2022-11-29T03:11:25-05:00
testsuite: Mark unpack_sums_6 as fragile due to #22504

This test is explicitly dependent upon runtime, which is generally not
appropriate given that the testsuite is run in parallel and generally
saturates the CPU.

- - - - -
def47dd3 by Ben Gamari at 2022-11-29T03:11:25-05:00
testsuite: Don't use grep -q in unpack_sums_7

`grep -q` closes stdin as soon as it finds the pattern it is looking
for, resulting in #22484.

- - - - -
cc25d52e by Sylvain Henry at 2022-11-29T09:44:31+01:00
Add Javascript backend

Add JS backend adapted from the GHCJS project by Luite Stegeman.

Some features haven't been ported or implemented yet. Tests for these
features have been disabled with an associated gitlab ticket.

Bump array submodule

Work funded by IOG.

Co-authored-by: Jeffrey Young <jeffrey.young at iohk.io>
Co-authored-by: Luite Stegeman <stegeman at gmail.com>
Co-authored-by: Josh Meredith <joshmeredith2008 at gmail.com>

- - - - -
68c966cd by sheaf at 2022-11-30T09:31:25-05:00
Fix @since annotations on WithDict and Coercible

Fixes #22453

- - - - -
a3a8e9e9 by Simon Peyton Jones at 2022-11-30T09:32:03-05:00
Be more careful in GHC.Tc.Solver.Interact.solveOneFromTheOther

We were failing to account for the cc_pend_sc flag in this
important function, with the result that we expanded superclasses
forever.

Fixes #22516.

- - - - -
a9d9b8c0 by Simon Peyton Jones at 2022-11-30T09:32:03-05:00
Use mkNakedFunTy in tcPatSynSig

As #22521 showed, in tcPatSynSig we make a "fake type" to
kind-generalise; and that type has unzonked type variables in it. So
we must not use `mkFunTy` (which checks FunTy's invariants) via
`mkPhiTy` when building this type.  Instead we need to use
`mkNakedFunTy`.

Easy fix.

- - - - -
31462d98 by Andreas Klebinger at 2022-11-30T14:50:58-05:00
Properly cast values when writing/reading unboxed sums.

Unboxed sums might store a Int8# value as Int64#. This patch
makes sure we keep track of the actual value type.

See Note [Casting slot arguments] for the details.

- - - - -
10a2a7de by Oleg Grenrus at 2022-11-30T14:51:39-05:00
Move Void to GHC.Base...

This change would allow `Void` to be used deeper in module graph.
For example exported from `Prelude` (though that might be already
possible).

Also this change includes a change `stimes @Void _ x = x`,
https://github.com/haskell/core-libraries-committee/issues/95

While the above is not required, maintaining old stimes behavior
would be tricky as `GHC.Base` doesn't know about `Num` or `Integral`,
which would require more hs-boot files.

- - - - -
b4cfa8e2 by Sebastian Graf at 2022-11-30T14:52:24-05:00
DmdAnal: Reflect the `seq` of strict fields of a DataCon worker (#22475)

See the updated `Note [Data-con worker strictness]`
and the new `Note [Demand transformer for data constructors]`.

Fixes #22475.

- - - - -
d87f28d8 by Baldur Blöndal at 2022-11-30T21:16:36+01:00
Make Functor a quantified superclass of Bifunctor.

See https://github.com/haskell/core-libraries-committee/issues/91 for
discussion.

This change relates Bifunctor with Functor by requiring second = fmap.
Moreover this change is a step towards unblocking the major version bump
of bifunctors and profunctors to major version 6. This paves the way to
move the Profunctor class into base. For that Functor first similarly
becomes a superclass of Profunctor in the new major version 6.

- - - - -
72cf4c5d by doyougnu at 2022-12-01T12:36:44-05:00
FastString: SAT bucket_match

Metric Decrease:
    MultiLayerModulesTH_OneShot

- - - - -
afc2540d by Simon Peyton Jones at 2022-12-01T12:37:20-05:00
Add a missing varToCoreExpr in etaBodyForJoinPoint

This subtle bug showed up when compiling a library with 9.4.
See #22491.  The bug is present in master, but it is hard to
trigger; the new regression test T22491 fails in 9.4.

The fix was easy: just add a missing varToCoreExpr in
etaBodyForJoinPoint.

The fix is definitely right though!

I also did some other minor refatoring:
* Moved the preInlineUnconditionally test in simplExprF1 to
  before the call to joinPointBinding_maybe, to avoid fruitless
  eta-expansion.
* Added a boolean from_lam flag to simplNonRecE, to avoid two
  fruitless tests, and commented it a bit better.

These refactorings seem to save 0.1% on compile-time allocation in
perf/compiler; with a max saving of 1.4% in T9961

Metric Decrease:
    T9961

- - - - -
81eeec7f by M Farkas-Dyck at 2022-12-01T12:37:56-05:00
CI: Forbid the fully static build on Alpine to fail.

To do so, we mark some tests broken in this configuration.

- - - - -
c5d1bf29 by Bryan Richter at 2022-12-01T12:37:56-05:00
CI: Remove ARMv7 jobs

These jobs fail (and are allowed to fail) nearly every time.

Soon they won't even be able to run at all, as we won't currently have
runners that can run them.

Fixing the latter problem is tracked in #22409.

I went ahead and removed all settings and configurations.

- - - - -
d82992fd by Bryan Richter at 2022-12-01T12:37:56-05:00
CI: Fix CI lint

Failure was introduced by conflicting changes to gen_ci.hs that did
*not* trigger git conflicts.

- - - - -
ce126993 by Simon Peyton Jones at 2022-12-02T01:22:12-05:00
Refactor TyCon to have a top-level product

This patch changes the representation of TyCon so that it has
a top-level product type, with a field that gives the details
(newtype, type family etc), #22458.

Not much change in allocation, but execution seems to be a bit
faster.

Includes a change to the haddock submodule to adjust for API changes.

- - - - -
74c767df by Matthew Pickering at 2022-12-02T01:22:48-05:00
ApplicativeDo: Set pattern location before running exhaustiveness checker

This improves the error messages of the exhaustiveness checker when
checking statements which have been moved around with ApplicativeDo.

Before:

Test.hs:2:3: warning: [GHC-62161] [-Wincomplete-uni-patterns]
    Pattern match(es) are non-exhaustive
    In a pattern binding:
        Patterns of type ‘Maybe ()’ not matched: Nothing
  |
2 |   let x = ()
  |   ^^^^^^^^^^

After:

Test.hs:4:3: warning: [GHC-62161] [-Wincomplete-uni-patterns]
    Pattern match(es) are non-exhaustive
    In a pattern binding:
        Patterns of type ‘Maybe ()’ not matched: Nothing
  |
4 |   ~(Just res1) <- seq x (pure $ Nothing @())
  |

Fixes #22483

- - - - -
85ecc1a0 by Matthew Pickering at 2022-12-02T19:46:43-05:00
Add special case for :Main module in `GHC.IfaceToCore.mk_top_id`

See Note [Root-main Id]

The `:Main` special binding is actually defined in the current module
(hence don't go looking for it externally) but the module name is rOOT_MAIN
rather than the current module so we need this special case.

There was already some similar logic in `GHC.Rename.Env` for
External Core, but now the "External Core" is in interface files it
needs to be moved here instead.

Fixes #22405

- - - - -
108c319f by Krzysztof Gogolewski at 2022-12-02T19:47:18-05:00
Fix linearity checking in Lint

Lint was not able to see that x*y <= x*y, because this inequality
was decomposed to x <= x*y && y <= x*y, but there was no rule
to see that x <= x*y.

Fixes #22546.

- - - - -
bb674262 by Bryan Richter at 2022-12-03T04:38:46-05:00
Mark T16916 fragile

See https://gitlab.haskell.org/ghc/ghc/-/issues/16966

- - - - -
5d267d46 by Vladislav Zavialov at 2022-12-03T04:39:22-05:00
Refactor: FreshOrReuse instead of addTyClTyVarBinds

This is a refactoring that should have no effect on observable behavior.

Prior to this change, GHC.HsToCore.Quote contained a few closely related
functions to process type variable bindings: addSimpleTyVarBinds,
addHsTyVarBinds, addQTyVarBinds, and addTyClTyVarBinds.

We can classify them by their input type and name generation strategy:

                              Fresh names only    Reuse bound names
                          +---------------------+-------------------+
                   [Name] | addSimpleTyVarBinds |                   |
[LHsTyVarBndr flag GhcRn] |     addHsTyVarBinds |                   |
        LHsQTyVars GhcRn  |      addQTyVarBinds | addTyClTyVarBinds |
                          +---------------------+-------------------+

Note how two functions are missing. Because of this omission, there were
two places where a LHsQTyVars value was constructed just to be able to pass it
to addTyClTyVarBinds:

1. mk_qtvs in addHsOuterFamEqnTyVarBinds    -- bad
2. mkHsQTvs in repFamilyDecl                -- bad

This prevented me from making other changes to LHsQTyVars, so the main
goal of this refactoring is to get rid of those workarounds.

The most direct solution would be to define the missing functions.
But that would lead to a certain amount of code duplication. To avoid
code duplication, I factored out the name generation strategy into a
function parameter:

	data FreshOrReuse
	  = FreshNamesOnly
	  | ReuseBoundNames

	addSimpleTyVarBinds :: FreshOrReuse -> ...
	addHsTyVarBinds     :: FreshOrReuse -> ...
	addQTyVarBinds      :: FreshOrReuse -> ...

- - - - -
c189b831 by Vladislav Zavialov at 2022-12-03T04:39:22-05:00
addHsOuterFamEqnTyVarBinds: use FreshNamesOnly for explicit binders

Consider this example:

	[d| instance forall a. C [a] where
	      type forall b. G [a] b = Proxy b |]

When we process "forall b." in the associated type instance, it is
unambiguously the binding site for "b" and we want a fresh name for it.
Therefore, FreshNamesOnly is more fitting than ReuseBoundNames.
This should not have any observable effect but it avoids pointless
lookups in the MetaEnv.

- - - - -
42512264 by Ross Paterson at 2022-12-03T10:32:45+00:00
Handle type data declarations in Template Haskell quotations and splices (fixes #22500)

This adds a TypeDataD constructor to the Template Haskell Dec type,
and ensures that the constructors it contains go in the TyCls namespace.

- - - - -
1a767fa3 by Vladislav Zavialov at 2022-12-05T05:18:50-05:00
Add BufSpan to EpaLocation (#22319, #22558)

The key part of this patch is the change to mkTokenLocation:

	- mkTokenLocation (RealSrcSpan r _)  = TokenLoc (EpaSpan r)
	+ mkTokenLocation (RealSrcSpan r mb) = TokenLoc (EpaSpan r mb)

mkTokenLocation used to discard the BufSpan, but now it is saved and can
be retrieved from LHsToken or LHsUniToken.

This is made possible by the following change to EpaLocation:

	- data EpaLocation = EpaSpan !RealSrcSpan
	+ data EpaLocation = EpaSpan !RealSrcSpan !(Strict.Maybe BufSpan)
	                   | ...

The end goal is to make use of the BufSpan in Parser/PostProcess/Haddock.

- - - - -
cd31acad by sheaf at 2022-12-06T15:45:58-05:00
Hadrian: fix ghcDebugAssertions off-by-one error

Commit 6b2f7ffe changed the logic that decided whether to enable debug
assertions. However, it had an off-by-one error, as the stage parameter
to the function inconsistently referred to the stage of the compiler
being used to build or the stage of the compiler we are building.

This patch makes it consistent. Now the parameter always refers to the
the compiler which is being built.

In particular, this patch re-enables
assertions in the stage 2 compiler when building with devel2 flavour,
and disables assertions in the stage 2 compiler when building with
validate flavour.

Some extra performance tests are now run in the "validate" jobs because
the stage2 compiler no longer contains assertions.

-------------------------
Metric Decrease:
    CoOpt_Singletons
    MultiComponentModules
    MultiComponentModulesRecomp
    MultiLayerModulesTH_OneShot
    T11374
    T12227
    T12234
    T13253-spj
    T13701
    T14683
    T14697
    T15703
    T17096
    T17516
    T18304
    T18478
    T18923
    T5030
    T9872b
    TcPlugin_RewritePerf
Metric Increase:
    MultiComponentModules
    MultiComponentModulesRecomp
    MultiLayerModules
    MultiLayerModulesRecomp
    MultiLayerModulesTH_Make
    T13386
    T13719
    T3294
    T9233
    T9675
    parsing001
-------------------------

- - - - -
21d66db1 by mrkun at 2022-12-06T15:46:38-05:00
Push DynFlags out of runInstallNameTool

- - - - -
aaaaa79b by mrkun at 2022-12-06T15:46:38-05:00
Push DynFlags out of askOtool

- - - - -
4e28f49e by mrkun at 2022-12-06T15:46:38-05:00
Push DynFlags out of runInjectRPaths

- - - - -
a7422580 by mrkun at 2022-12-06T15:46:38-05:00
Push DynFlags out of Linker.MacOS

- - - - -
e902d771 by Matthew Craven at 2022-12-08T08:30:23-05:00
Fix bounds-checking buglet in Data.Array.Byte

...another manifestation of #20851 which
I unfortunately missed in my first pass.

- - - - -
8d36c0c6 by Gergő Érdi at 2022-12-08T08:31:03-05:00
Remove copy-pasted definitions of `graphFromEdgedVertices*`

- - - - -
c5d8ed3a by Gergő Érdi at 2022-12-08T08:31:03-05:00
Add version of `reachableGraph` that avoids loop for cyclic inputs
by building its result connected component by component

Fixes #22512

- - - - -
90cd5396 by Krzysztof Gogolewski at 2022-12-08T08:31:39-05:00
Mark Type.Reflection.Unsafe as Unsafe

This module can be used to construct ill-formed TypeReps, so it should
be Unsafe.

- - - - -
2057c77d by Ian-Woo Kim at 2022-12-08T08:32:19-05:00
Truncate eventlog event for large payload (#20221)

RTS eventlog events for postCapsetVecEvent are truncated if payload
is larger than EVENT_PAYLOAD_SIZE_MAX
Previously, postCapsetVecEvent records eventlog event with payload
of variable size larger than EVENT_PAYLOAD_SIZE_MAX (2^16) without
any validation, resulting in corrupted data.
For example, this happens when a Haskell binary is invoked with very
long command line arguments exceeding 2^16 bytes (see #20221).
Now we check the size of accumulated payload messages incrementally,
and truncate the message just before the payload size exceeds
EVENT_PAYLOAD_SIZE_MAX. RTS will warn the user with a message showing
how many arguments are truncated.

- - - - -
9ec76f61 by Cheng Shao at 2022-12-08T08:32:59-05:00
hadrian: don't add debug info to non-debug ways of rts

Hadrian used to pass -g when building all ways of rts. It makes output
binaries larger (especially so for wasm backend), and isn't needed by
most users out there, so this patch removes that flag. In case the
debug info is desired, we still pass -g3 when building the debug way,
and there's also the debug_info flavour transformer which ensures -g3
is passed for all rts ways.

- - - - -
7658cdd4 by Krzysztof Gogolewski at 2022-12-08T08:33:36-05:00
Restore show (typeRep @[]) == "[]"

The Show instance for TypeRep [] has changed in 9.5 to output "List"
because the name of the type constructor changed.
This seems to be accidental and is inconsistent with TypeReps of saturated
lists, which are printed as e.g. "[Int]".
For now, I'm restoring the old behavior; in the future,
maybe we should show TypeReps without puns (List, Tuple, Type).

- - - - -
216deefd by Matthew Pickering at 2022-12-08T22:45:27-05:00
Add test for #22162

- - - - -
5d0a311f by Matthew Pickering at 2022-12-08T22:45:27-05:00
ci: Add job to test interface file determinism guarantees

In this job we can run on every commit we add a test which builds the
Cabal library twice and checks that the ABI hash and interface hash is
stable across the two builds.

* We run the test 20 times to try to weed out any race conditions due to
  `-j`
* We run the builds in different temporary directories to try to weed
  out anything related to build directory affecting ABI or interface
  file hash.

Fixes #22180

- - - - -
0a76d7d4 by Matthew Pickering at 2022-12-08T22:45:27-05:00
ci: Add job for testing interface stability across builds

The idea is that both the bindists should product libraries with the
same ABI and interface hash.
So the job checks with ghc-pkg to make sure the computed ABI
is the same.

In future this job can be extended to check for the other facets of
interface determinism.

Fixes #22180

- - - - -
74c9bf91 by Matthew Pickering at 2022-12-08T22:45:27-05:00
backpack: Be more careful when adding together ImportAvails

There was some code in the signature merging logic which added together
the ImportAvails of the signature and the signature which was merged
into it. This had the side-effect of making the merged signature depend
on the signature (via a normal module dependency). The intention was to
propagate orphan instances through the merge but this also messed up
recompilation logic because we shouldn't be attempting to load B.hi when
mergeing it.

The fix is to just combine the part of ImportAvails that we intended to
(transitive info, orphan instances and type family instances) rather
than the whole thing.

- - - - -
d122e022 by Matthew Pickering at 2022-12-08T22:45:27-05:00
Fix mk_mod_usage_info if the interface file is not already loaded

In #22217 it was observed that the order modules are compiled in affects
the contents of an interface file. This was because a module dependended
on another module indirectly, via a re-export but the interface file for
this module was never loaded because the symbol was never used in the
file.

If we decide that we depend on a module then we jolly well ought to
record this fact in the interface file! Otherwise it could lead to very
subtle recompilation bugs if the dependency is not tracked and the
module is updated.

Therefore the best thing to do is just to make sure the file is loaded
by calling the `loadSysInterface` function.  This first checks the
caches (like we did before) but then actually goes to find the interface
on disk if it wasn't loaded.

Fixes #22217

- - - - -
ea25088d by lrzlin at 2022-12-08T22:46:06-05:00
Add initial support for LoongArch Architecture.

- - - - -
9eb9d2f4 by Bodigrim at 2022-12-08T22:46:47-05:00
Update submodule mtl to 2.3.1, parsec to 3.1.15.1, haddock and Cabal to HEAD

- - - - -
08d8fe2a by Bodigrim at 2022-12-08T22:46:47-05:00
Allow mtl-2.3 in hadrian

- - - - -
3807a46c by Bodigrim at 2022-12-08T22:46:47-05:00
Support mtl-2.3 in check-exact

- - - - -
ef702a18 by Bodigrim at 2022-12-08T22:46:47-05:00
Fix tests

- - - - -
3144e8ff by Sebastian Graf at 2022-12-08T22:47:22-05:00
Make (^) INLINE (#22324)

So that we get to cancel away the allocation for the lazily used base.

We can move `powImpl` (which *is* strict in the base) to the top-level
so that we don't duplicate too much code and move the SPECIALISATION
pragmas onto `powImpl`.

The net effect of this change is that `(^)` plays along much better with
inlining thresholds and loopification (#22227), for example in `x2n1`.

Fixes #22324.

- - - - -
1d3a8b8e by Matthew Pickering at 2022-12-08T22:47:59-05:00
Typeable: Fix module locations of some definitions in GHC.Types

There was some confusion in Data.Typeable about which module certain
wired-in things were defined in. Just because something is wired-in
doesn't mean it comes from GHC.Prim, in particular things like LiftedRep
and RuntimeRep are defined in GHC.Types and that's the end of the story.

Things like Int#, Float# etc are defined in GHC.Prim as they have no
Haskell definition site at all so we need to generate type
representations for them (which live in GHC.Types).

Fixes #22510

- - - - -
0f7588b5 by Sebastian Graf at 2022-12-08T22:48:34-05:00
Make `drop` and `dropWhile` fuse (#18964)

I copied the fusion framework we have in place for `take`.
T18964 asserts that we regress neither when fusion fires nor when it doesn't.

Fixes #18964.

- - - - -
26e71562 by Sebastian Graf at 2022-12-08T22:49:10-05:00
Do not strictify a DFun's parameter dictionaries (#22549)

... thus fixing #22549.

The details are in the refurbished and no longer dead
`Note [Do not strictify a DFun's parameter dictionaries]`.

There's a regression test in T22549.

- - - - -
36093407 by John Ericson at 2022-12-08T22:49:45-05:00
Delete `rts/package.conf.in`

It is a relic of the Make build system. The RTS now uses a
`package.conf` file generated the usual way by Cabal.

- - - - -
b0cc2fcf by Krzysztof Gogolewski at 2022-12-08T22:50:21-05:00
Fixes around primitive literals

* The SourceText of primitive characters 'a'# did not include
  the #, unlike for other primitive literals 1#, 1##, 1.0#, 1.0##, "a"#.
  We can now remove the function pp_st_suffix, which was a hack
  to add the # back.
* Negative primitive literals shouldn't use parentheses, as described in
  Note [Printing of literals in Core]. Added a testcase to T14681.

- - - - -
aacf616d by Bryan Richter at 2022-12-08T22:50:56-05:00
testsuite: Mark conc024 fragile on Windows

- - - - -
ed239a24 by Ryan Scott at 2022-12-09T09:42:16-05:00
Document TH splices' interaction with INCOHERENT instances

Top-level declaration splices can having surprising interactions with
`INCOHERENT` instances, as observed in #22492. This patch
resolves #22492 by documenting this strange interaction in the GHC User's
Guide.

[ci skip]

- - - - -
1023b432 by Mike Pilgrem at 2022-12-09T09:42:56-05:00
Fix #22300 Document GHC's extensions to valid whitespace

- - - - -
79b0cec0 by Luite Stegeman at 2022-12-09T09:43:38-05:00
Add support for environments that don't have setImmediate

- - - - -
5b007ec5 by Luite Stegeman at 2022-12-09T09:43:38-05:00
Fix bound thread status

- - - - -
65335d10 by Matthew Pickering at 2022-12-09T20:15:45-05:00
Update containers submodule

This contains a fix necessary for the multi-repl to work on GHC's code
base where we try to load containers and template-haskell into the same
session.

- - - - -
4937c0bb by Matthew Pickering at 2022-12-09T20:15:45-05:00
hadrian-multi: Put interface files in separate directories

Before we were putting all the interface files in the same directory
which was leading to collisions if the files were called the same thing.

- - - - -
8acb5b7b by Matthew Pickering at 2022-12-09T20:15:45-05:00
hadrian-toolargs: Add filepath to allowed repl targets

- - - - -
5949d927 by Matthew Pickering at 2022-12-09T20:15:45-05:00
driver: Set correct UnitId when rehydrating modules

We were not setting the UnitId before rehydrating modules which just led
to us attempting to find things in the wrong HPT. The test for this is
the hadrian-multi command (which is now added as a CI job).

Fixes #22222

- - - - -
ab06c0f0 by Matthew Pickering at 2022-12-09T20:15:45-05:00
ci: Add job to test hadrian-multi command

I am not sure this job is good because it requires booting HEAD with
HEAD, but it should be fine.

- - - - -
fac3e568 by Matthew Pickering at 2022-12-09T20:16:20-05:00
hadrian: Update bootstrap plans to 9.2.* series and 9.4.* series.

This updates the build plans for the most recent compiler versions, as
well as fixing the hadrian-bootstrap-gen script to a specific GHC
version.

- - - - -
195b08b4 by Matthew Pickering at 2022-12-09T20:16:20-05:00
ci: Bump boot images to use ghc-9.4.3

Also updates the bootstrap jobs to test booting 9.2 and 9.4.

- - - - -
c658c580 by Matthew Pickering at 2022-12-09T20:16:20-05:00
hlint: Removed redundant UnboxedSums pragmas

UnboxedSums is quite confusingly implied by UnboxedTuples, alas, just
the way it is.

See #22485

- - - - -
b3e98a92 by Oleg Grenrus at 2022-12-11T12:26:17-05:00
Add heqT, a kind-heterogeneous variant of heq

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

- - - - -
bfd7c1e6 by Bodigrim at 2022-12-11T12:26:55-05:00
Document that Bifunctor instances for tuples are lawful only up to laziness

- - - - -
5d1a1881 by Bryan Richter at 2022-12-12T16:22:36-05:00
Mark T21336a fragile

- - - - -
c30accc2 by Matthew Pickering at 2022-12-12T16:23:11-05:00
Add test for #21476

This issues seems to have been fixed since the ticket was made, so let's
add a test and move on.

Fixes #21476

- - - - -
e9d74a3e by Sebastian Graf at 2022-12-13T22:18:39-05:00
Respect -XStrict in the pattern-match checker (#21761)

We were missing a call to `decideBangHood` in the pattern-match checker.
There is another call in `matchWrapper.mk_eqn_info` which seems redundant
but really is not; see `Note [Desugaring -XStrict matches in Pmc]`.

Fixes #21761.

- - - - -
884790e2 by Gergő Érdi at 2022-12-13T22:19:14-05:00
Fix loop in the interface representation of some `Unfolding` fields

As discovered in #22272, dehydration of the unfolding info of a
recursive definition used to involve a traversal of the definition
itself, which in turn involves traversing the unfolding info. Hence,
a loop.

Instead, we now store enough data in the interface that we can produce
the unfolding info without this traversal. See Note [Tying the 'CoreUnfolding' knot]
for details.

Fixes #22272

Co-authored-by: Simon Peyton Jones <simon.peytonjones at gmail.com>

- - - - -
9f301189 by Alan Zimmerman at 2022-12-13T22:19:50-05:00
EPA: When splitting out header comments, keep ones for first decl

Any comments immediately preceding the first declaration are no longer
kept as header comments, but attach to the first declaration instead.

- - - - -
8b1f1b45 by Sylvain Henry at 2022-12-13T22:20:28-05:00
JS: fix object file name comparison (#22578)

- - - - -
e9e161bb by Bryan Richter at 2022-12-13T22:21:03-05:00
configure: Bump min bootstrap GHC version to 9.2

- - - - -
75855643 by Ben Gamari at 2022-12-15T03:54:02-05:00
hadrian: Don't enable TSAN in stage0 build

- - - - -
da7b51d8 by Ben Gamari at 2022-12-15T03:54:02-05:00
cmm: Introduce blockConcat

- - - - -
34f6b09c by Ben Gamari at 2022-12-15T03:54:02-05:00
cmm: Introduce MemoryOrderings

- - - - -
43beaa7b by Ben Gamari at 2022-12-15T03:54:02-05:00
llvm: Respect memory specified orderings

- - - - -
8faf74fc by Ben Gamari at 2022-12-15T03:54:02-05:00
Codegen/x86: Eliminate barrier for relaxed accesses

- - - - -
6cc3944a by Ben Gamari at 2022-12-15T03:54:02-05:00
cmm/Parser: Reduce some repetition

- - - - -
6c9862c4 by Ben Gamari at 2022-12-15T03:54:02-05:00
cmm/Parser: Add syntax for ordered loads and stores

- - - - -
748490d2 by Ben Gamari at 2022-12-15T03:54:02-05:00
cmm/Parser: Atomic load syntax

Originally I had thought I would just use the `prim` call syntax instead
of introducing new syntax for atomic loads. However, it turns out that
`prim` call syntax tends to make things quite unreadable. This new
syntax seems quite natural.

- - - - -
28c6781a by Ben Gamari at 2022-12-15T03:54:02-05:00
codeGen: Introduce ThreadSanitizer instrumentation

This introduces a new Cmm pass which instruments the program with
ThreadSanitizer annotations, allowing full tracking of mutator memory
accesses via TSAN.

- - - - -
d97aa311 by Ben Gamari at 2022-12-15T03:54:02-05:00
Hadrian: Drop TSAN_ENABLED define from flavour

This is redundant since the TSANUtils.h already defines it.

- - - - -
86974ef1 by Ben Gamari at 2022-12-15T03:54:02-05:00
hadrian: Enable Cmm instrumentation in TSAN flavour

- - - - -
93723290 by Ben Gamari at 2022-12-15T03:54:02-05:00
rts: Ensure that global regs are never passed as fun call args

This is in general unsafe as they may be clobbered if they are mapped to
caller-saved machine registers. See Note [Register parameter passing].

- - - - -
2eb0fb87 by Matthew Pickering at 2022-12-15T03:54:39-05:00
Package Imports: Get candidate packages also from re-exported modules

Previously we were just looking at the direct imports to try and work
out what a package qualifier could apply to but #22333 pointed out we
also needed to look for reexported modules.

Fixes #22333

- - - - -
552b7908 by Ben Gamari at 2022-12-15T03:55:15-05:00
compiler: Ensure that MutVar operations have necessary barriers

Here we add acquire and release barriers in readMutVar# and
writeMutVar#, which are necessary for soundness.

Fixes #22468.

- - - - -
933d61a4 by Simon Peyton Jones at 2022-12-15T03:55:51-05:00
Fix bogus test in Lint

The Lint check for branch compatiblity within an axiom, in
GHC.Core.Lint.compatible_branches was subtly different to the
check made when contructing an axiom, in
GHC.Core.FamInstEnv.compatibleBranches.

The latter is correct, so I killed the former and am now using the
latter.

On the way I did some improvements to pretty-printing and documentation.

- - - - -
03ed0b95 by Ryan Scott at 2022-12-15T03:56:26-05:00
checkValidInst: Don't expand synonyms when splitting sigma types

Previously, the `checkValidInst` function (used when checking that an instance
declaration is headed by an actual type class, not a type synonym) was using
`tcSplitSigmaTy` to split apart the `forall`s and instance context. This is
incorrect, however, as `tcSplitSigmaTy` expands type synonyms, which can cause
instances headed by quantified constraint type synonyms to be accepted
erroneously.

This patch introduces `splitInstTyForValidity`, a variant of `tcSplitSigmaTy`
specialized for validity checking that does _not_ expand type synonyms, and
uses it in `checkValidInst`.

Fixes #22570.

- - - - -
ed056bc3 by Ben Gamari at 2022-12-16T16:12:44-05:00
rts/Messages: Refactor

This doesn't change behavior but makes the code a bit easier to follow.

- - - - -
7356f8e0 by Ben Gamari at 2022-12-16T16:12:44-05:00
rts/ThreadPaused: Ordering fixes

- - - - -
914f0025 by Ben Gamari at 2022-12-16T16:12:44-05:00
eventlog: Silence spurious data race

- - - - -
fbc84244 by Ben Gamari at 2022-12-16T16:12:44-05:00
Introduce SET_INFO_RELEASE for Cmm

- - - - -
821b5472 by Ben Gamari at 2022-12-16T16:12:44-05:00
rts: Use fences instead of explicit barriers

- - - - -
2228c999 by Ben Gamari at 2022-12-16T16:12:44-05:00
rts/stm: Fix memory ordering in readTVarIO#

See #22421.

- - - - -
99269b9f by Ben Gamari at 2022-12-16T16:12:44-05:00
Improve heap memory barrier Note

Also introduce MUT_FIELD marker in Closures.h to document mutable
fields.

- - - - -
70999283 by Ben Gamari at 2022-12-16T16:12:44-05:00
rts: Introduce getNumCapabilities

And ensure accesses to n_capabilities are atomic (although with relaxed
ordering). This is necessary as RTS API callers may concurrently call
into the RTS without holding a capability.

- - - - -
98689f77 by Ben Gamari at 2022-12-16T16:12:44-05:00
ghc: Fix data race in dump file handling

Previously the dump filename cache would use a non-atomic update which
could potentially result in lost dump contents. Note that this is still
a bit racy since the first writer may lag behind a later appending
writer.

- - - - -
605d9547 by Ben Gamari at 2022-12-16T16:12:45-05:00
rts: Always use atomics for context_switch and interrupt

Since these are modified by the timer handler.

- - - - -
86f20258 by Ben Gamari at 2022-12-16T16:12:45-05:00
rts/Timer: Always use atomic operations

As noted in #22447, the existence of the pthread-based ITimer
implementation means that we cannot assume that the program is
single-threaded.

- - - - -
f8e901dc by Ben Gamari at 2022-12-16T16:12:45-05:00
rts: Encapsulate recent_activity access

This makes it easier to ensure that it is accessed using the necessary
atomic operations.

- - - - -
e0affaa9 by Ben Gamari at 2022-12-16T16:12:45-05:00
rts: Encapsulate access to capabilities array

- - - - -
7ca683e4 by Ben Gamari at 2022-12-16T16:12:45-05:00
rts: Encapsulate sched_state

- - - - -
1cf13bd0 by Ben Gamari at 2022-12-16T16:12:45-05:00
PrimOps: Fix benign MutVar race

Relaxed ordering is fine here since the later CAS implies a release.

- - - - -
3d2a7e08 by Ben Gamari at 2022-12-16T16:12:45-05:00
rts: Style fix

- - - - -
82c62074 by Ben Gamari at 2022-12-16T16:12:45-05:00
compiler: Use release store in eager blackholing

- - - - -
eb1a0136 by Ben Gamari at 2022-12-16T16:12:45-05:00
rts: Fix ordering of makeStableName

- - - - -
ad0e260a by Ben Gamari at 2022-12-16T16:12:45-05:00
rts: Use ordered accesses instead of explicit barriers

- - - - -
a3eccf06 by Ben Gamari at 2022-12-16T16:12:45-05:00
rts: Statically allocate capabilities

This is a rather simplistic way of solving #17289.

- - - - -
287fa3fb by Ben Gamari at 2022-12-16T16:12:45-05:00
rts: Ensure that all accesses to pending_sync are atomic

- - - - -
351eae58 by Ben Gamari at 2022-12-16T16:12:45-05:00
rts: Note race with wakeBlockingQueue

- - - - -
5acf33dd by Bodigrim at 2022-12-16T16:13:22-05:00
Bump submodule directory to 1.3.8.0 and hpc to HEAD

- - - - -
0dd95421 by Bodigrim at 2022-12-16T16:13:22-05:00
Accept allocations increase on Windows

This is because of `filepath-1.4.100.0` and AFPP, causing increasing round-trips
between lists and ByteArray. See #22625 for discussion.

Metric Increase:
    MultiComponentModules
    MultiComponentModulesRecomp
    MultiLayerModules
    MultiLayerModulesRecomp
    T10421
    T10547
    T12150
    T12227
    T12234
    T12425
    T13035
    T13253
    T13253-spj
    T13701
    T13719
    T15703
    T16875
    T18140
    T18282
    T18304
    T18698a
    T18698b
    T18923
    T20049
    T21839c
    T21839r
    T5837
    T6048
    T9198
    T9961
    TcPlugin_RewritePerf
    hard_hole_fits

- - - - -
ef9ac9d2 by Cheng Shao at 2022-12-16T16:13:59-05:00
testsuite: Mark T9405 as fragile instead of broken on Windows

It's starting to pass again, and the unexpected pass blocks CI.

- - - - -
1f3abd85 by Cheng Shao at 2022-12-16T21:16:28+00:00
compiler: remove obsolete commented code in wasm NCG

It was just a temporary hack to workaround a bug in the relooper, that
bug has been fixed long before the wasm backend is merged.

- - - - -
e3104eab by Cheng Shao at 2022-12-16T21:16:28+00:00
compiler: add missing export list of GHC.CmmToAsm.Wasm.FromCmm

Also removes some unreachable code here.

- - - - -
1c6930bf by Cheng Shao at 2022-12-16T21:16:28+00:00
compiler: change fallback function signature to Cmm function signature in wasm NCG

In the wasm NCG, when handling a `CLabel` of undefined function
without knowing its function signature, we used to fallback to `() ->
()` which is accepted by `wasm-ld`. This patch changes it to the
signature of Cmm functions, which equally works, but would be required
when we emit tail call instructions.

- - - - -
8a81d9d9 by Cheng Shao at 2022-12-16T21:16:28+00:00
compiler: add optional tail-call support in wasm NCG

When the `-mtail-call` clang flag is passed at configure time, wasm
tail-call extension is enabled, and the wasm NCG will emit
`return_call`/`return_call_indirect` instructions to take advantage of
it and avoid the `StgRun` trampoline overhead.

Closes #22461.

- - - - -
d1431cc0 by Cheng Shao at 2022-12-17T08:07:15-05:00
base: add missing autoconf checks for waitpid/umask

These are not present in wasi-libc. Required for fixing #22589

- - - - -
da3f1e91 by Cheng Shao at 2022-12-17T08:07:51-05:00
compiler: make .wasm the default executable extension on wasm32

Following convention as in other wasm toolchains. Fixes #22594.

- - - - -
ad21f4ef by Cheng Shao at 2022-12-17T08:07:51-05:00
ci: support hello.wasm in ci.sh cross testing logic

- - - - -
6fe2d778 by amesgen at 2022-12-18T19:33:49-05:00
Correct `exitWith` Haddocks

The `IOError`-specific `catch` in the Prelude is long gone.

- - - - -
b3eacd64 by Ben Gamari at 2022-12-18T19:34:24-05:00
rts: Drop racy assertion

0e274c39bf836d5bb846f5fa08649c75f85326ac added an assertion in
`dirty_MUT_VAR` checking that the MUT_VAR being dirtied was clean.
However, this isn't necessarily the case since another thread may have
raced us to dirty the object.

- - - - -
761c1f49 by Ben Gamari at 2022-12-18T19:35:00-05:00
rts/libdw: Silence uninitialized usage warnings

As noted in #22538, previously some GCC versions warned that various
locals in Libdw.c may be used uninitialized. Although this wasn't
strictly true (since they were initialized in an inline assembler block)
we fix this by providing explicit empty initializers.

Fixes #22538
- - - - -
5e047eff by Matthew Pickering at 2022-12-20T15:12:04+00:00
testsuite: Mark T16392 as fragile on windows

See #22649

- - - - -
703a4665 by M Farkas-Dyck at 2022-12-20T21:14:46-05:00
Scrub some partiality in `GHC.Cmm.Info.Build`: `doSRTs` takes a `[(CAFSet, CmmDecl)]` but truly wants a `[(CAFSet, CmmStatics)]`.

- - - - -
9736ab74 by Matthew Pickering at 2022-12-20T21:15:22-05:00
packaging: Fix upload_ghc_libs.py script

This change reflects the changes where .cabal files are now generated by
hadrian rather than ./configure.

Fixes #22518

- - - - -
7c6de18d by Ben Gamari at 2022-12-20T21:15:57-05:00
configure: Drop uses of AC_PROG_CC_C99

As noted in #22566, this macro is deprecated as of autoconf-2.70
`AC_PROG_CC` now sets `ac_cv_prog_cc_c99` itself.

Closes #22566.

- - - - -
36c5d98e by Ben Gamari at 2022-12-20T21:15:57-05:00
configure: Use AS_HELP_STRING instead of AC_HELP_STRING

The latter has been deprecated.

See #22566.

- - - - -
befe6ff8 by Bodigrim at 2022-12-20T21:16:37-05:00
GHCi.UI: fix various usages of head and tail

- - - - -
666d0ba7 by Bodigrim at 2022-12-20T21:16:37-05:00
GHCi.UI: avoid head and tail in parseCallEscape and around

- - - - -
5d96fd50 by Bodigrim at 2022-12-20T21:16:37-05:00
Make GHC.Driver.Main.hscTcRnLookupRdrName to return NonEmpty

- - - - -
3ce2ab94 by Bodigrim at 2022-12-21T06:17:56-05:00
Allow transformers-0.6 in ghc, ghci, ghc-bin and hadrian

- - - - -
954de93a by Bodigrim at 2022-12-21T06:17:56-05:00
Update submodule haskeline to HEAD (to allow transformers-0.6)

- - - - -
cefbeec3 by Bodigrim at 2022-12-21T06:17:56-05:00
Update submodule transformers to 0.6.0.4

- - - - -
b4730b62 by Bodigrim at 2022-12-21T06:17:56-05:00
Fix tests

T13253 imports MonadTrans, which acquired a quantified constraint in transformers-0.6, thus increase in allocations

Metric Increase:
    T13253

- - - - -
0be75261 by Simon Peyton Jones at 2022-12-21T06:18:32-05:00
Abstract over the right free vars

Fix #22459, in two ways:

(1) Make the Specialiser not create a bogus specialisation if
    it is presented by strangely polymorphic dictionary.
    See Note [Weird special case in SpecDict] in
    GHC.Core.Opt.Specialise

(2) Be more careful in abstractFloats
    See Note [Which type variables to abstract over]
    in GHC.Core.Opt.Simplify.Utils.

So (2) stops creating the excessively polymorphic dictionary in
abstractFloats, while (1) stops crashing if some other pass should
nevertheless create a weirdly polymorphic dictionary.

- - - - -
df7bc6b3 by Ying-Ruei Liang (TheKK) at 2022-12-21T14:31:54-05:00
rts: explicitly store return value of ccall checkClosure to prevent type error (#22617)

- - - - -
e193e537 by Simon Peyton Jones at 2022-12-21T14:32:30-05:00
Fix shadowing lacuna in OccurAnal

Issue #22623 demonstrated another lacuna in the implementation
of wrinkle (BS3) in Note [The binder-swap substitution] in
the occurrence analyser.

I was failing to add TyVar lambda binders using
addInScope/addOneInScope and that led to a totally bogus binder-swap
transformation.

Very easy to fix.

- - - - -
3d55d8ab by Simon Peyton Jones at 2022-12-21T14:32:30-05:00
Fix an assertion check in addToEqualCtList

The old assertion saw that a constraint ct could rewrite itself
(of course it can) and complained (stupid).

Fixes #22645

- - - - -
ceb2e9b9 by Ben Gamari at 2022-12-21T15:26:08-05:00
configure: Bump version to 9.6

- - - - -
fb4d36c4 by Ben Gamari at 2022-12-21T15:27:49-05:00
base: Bump version to 4.18

Requires various submodule bumps.

- - - - -
93ee7e90 by Ben Gamari at 2022-12-21T15:27:49-05:00
ghc-boot: Fix bootstrapping

- - - - -
fc3a2232 by Ben Gamari at 2022-12-22T13:45:06-05:00
Bump GHC version to 9.7

- - - - -
914f7fe3 by Andreas Klebinger at 2022-12-22T23:36:10-05:00
Don't consider large byte arrays/compact regions pinned.

Workaround for #22255 which showed how treating large/compact regions
as pinned could cause segfaults.

- - - - -
32b32d7f by Matthew Pickering at 2022-12-22T23:36:46-05:00
hadrian bindist: Install manpages to share/man/man1/ghc.1

When the installation makefile was copied over the manpages were no
longer installed in the correct place. Now we install it into share/man/man1/ghc.1
as the make build system did.

Fixes #22371

- - - - -
b3ddf803 by Ben Gamari at 2022-12-22T23:37:23-05:00
rts: Drop paths from configure from cabal file

A long time ago we would rely on substitutions from the configure script
to inject paths of the include and library directories of libffi and
libdw. However, now these are instead handled inside Hadrian when
calling Cabal's `configure` (see the uses of `cabalExtraDirs` in
Hadrian's `Settings.Packages.packageArgs`).

While the occurrences in the cabal file were redundant, they did no
harm. However, since b5c714545abc5f75a1ffdcc39b4bfdc7cd5e64b4 they have
no longer been interpolated. @mpickering noticed the suspicious
uninterpolated occurrence of `@FFIIncludeDir@` in #22595,
prompting this commit to finally remove them.

- - - - -
b2c7523d by Ben Gamari at 2022-12-22T23:37:59-05:00
Bump libffi-tarballs submodule

We will now use libffi-3.4.4.

- - - - -
3699a554 by Alan Zimmerman at 2022-12-22T23:38:35-05:00
EPA: Make EOF position part of AnnsModule

Closes #20951
Closes #19697

- - - - -
99757ce8 by Sylvain Henry at 2022-12-22T23:39:13-05:00
JS: fix support for -outputdir (#22641)

The `-outputdir` option wasn't correctly handled with the JS backend
because the same code path was used to handle both objects produced by
the JS backend and foreign .js files. Now we clearly distinguish the
two in the pipeline, fixing the bug.

- - - - -
02ed7d78 by Simon Peyton Jones at 2022-12-22T23:39:49-05:00
Refactor mkRuntimeError

This patch fixes #22634.  Because we don't have TYPE/CONSTRAINT
polymorphism, we need two error functions rather than one.

I took the opportunity to rname runtimeError to impossibleError,
to line up with mkImpossibleExpr, and avoid confusion with the
genuine runtime-error-constructing functions.

- - - - -
35267f07 by Ben Gamari at 2022-12-22T23:40:32-05:00
base: Fix event manager shutdown race on non-Linux platforms

During shutdown it's possible that we will attempt to use a closed fd
to wakeup another capability's event manager. On the Linux eventfd path
we were careful to handle this. However on the non-Linux path we failed
to do so. Fix this.

- - - - -
317f45c1 by Simon Peyton Jones at 2022-12-22T23:41:07-05:00
Fix unifier bug: failing to decompose over-saturated type family

This simple patch fixes #22647

- - - - -
14b2e3d3 by Ben Gamari at 2022-12-22T23:41:42-05:00
rts/m32: Fix sanity checking

Previously we would attempt to clear pages which were marked as
read-only. Fix this.

- - - - -
16a1bcd1 by Matthew Pickering at 2022-12-23T09:15:24+00:00
ci: Move wasm pipelines into nightly rather than master

See #22664 for the changes which need to be made to bring one of these
back to the validate pipeline.

- - - - -
18d2acd2 by Ben Gamari at 2022-12-23T19:09:30-05:00
nonmoving: Fix race in marking of blackholes

We must use an acquire-fence when marking to ensure that the indirectee
is visible.

- - - - -
11241efa by Ben Gamari at 2022-12-23T19:09:30-05:00
nonmoving: Fix segment list races

- - - - -
602455c9 by Ben Gamari at 2022-12-23T19:09:30-05:00
nonmoving: Use atomic when looking at bd->gen

Since it may have been mutated by a moving GC.

- - - - -
9d63b160 by Ben Gamari at 2022-12-23T19:09:30-05:00
nonmoving: Eliminate race in bump_static_flag

To ensure that we don't race with a mutator entering a new CAF we take
the SM mutex before touching static_flag. The other option here would be
to instead modify newCAF to use a CAS but the present approach is a bit
safer.

- - - - -
26837523 by Ben Gamari at 2022-12-23T19:09:30-05:00
nonmoving: Ensure that mutable fields have acquire barrier

- - - - -
8093264a by Ben Gamari at 2022-12-23T19:09:30-05:00
nonmoving: Fix races in collector status tracking

Mark a number of accesses to do with tracking of the status of the
concurrent collection thread as atomic. No interesting races here,
merely necessary to satisfy TSAN.

- - - - -
387d4fcc by Ben Gamari at 2022-12-23T19:09:30-05:00
nonmoving: Make segment state updates atomic

- - - - -
543cae00 by Ben Gamari at 2022-12-23T19:09:30-05:00
nonmoving: Refactor update remembered set initialization

This avoids a lock inversion between the storage manager mutex and
the stable pointer table mutex by not dropping the SM_MUTEX in
nonmovingCollect. This requires quite a bit of rejiggering but it
does seem like a better strategy.

- - - - -
c9936718 by Ben Gamari at 2022-12-23T19:09:30-05:00
nonmoving: Ensure that we aren't holding locks when closing them

TSAN complains about this sort of thing.

- - - - -
0cd31f7d by Ben Gamari at 2022-12-23T19:09:30-05:00
nonmoving: Make bitmap accesses atomic

This is a benign race on any sensible hard since these are byte
accesses. Nevertheless, atomic accesses are necessary to satisfy
TSAN.

- - - - -
d3fe110a by Ben Gamari at 2022-12-23T19:09:30-05:00
nonmoving: Fix benign race in update remembered set check

Relaxed load is fine here since we will take the lock before looking at
the list.

- - - - -
ab6cf893 by Ben Gamari at 2022-12-23T19:09:30-05:00
nonmoving: Fix race in shortcutting

We must use an acquire load to read the info table pointer since if we
find an indirection we must be certain that we see the indirectee.

- - - - -
36c9f23c by Ben Gamari at 2022-12-23T19:09:30-05:00
nonmoving: Make free list counter accesses atomic

Since these may race with the allocator(s).

- - - - -
aebef31c by doyougnu at 2022-12-23T19:10:09-05:00
add GHC.Utils.Binary.foldGet' and use for Iface

A minor optimization to remove lazy IO and a lazy accumulator

strictify foldGet'

IFace.Binary: use strict foldGet'

remove superfluous bang

- - - - -
5eb357d9 by Ben Gamari at 2022-12-24T00:41:05-05:00
compiler: Ensure that GHC toolchain is first in search path

As noted in #22561, it is important that GHC's toolchain look
first for its own headers and libraries to ensure that the
system's are not found instead. If this happens things can
break in surprising ways (e.g. see #22561).

- - - - -
cbaebfb9 by Matthew Pickering at 2022-12-24T00:41:40-05:00
head.hackage: Use slow-validate bindist for linting jobs

This enables the SLOW_VALIDATE env var for the linting head.hackage
jobs, namely the jobs enabled manually, by the label or on the nightly
build now use the deb10-numa-slow-validate bindist which has assertions
enabled.

See #22623 for a ticket which was found by using this configuration
already!

The head.hackage jobs triggered by upstream CI are now thusly:

hackage-lint: Can be triggered on any MR, normal validate pipeline or nightly build.
              Runs head.hackage with -dlint and a slow-validate bindist

hackage-label-lint: Trigged on MRs with "user-facing" label, runs the slow-validate
                    head.hackage build with -dlint.

nightly-hackage-lint: Runs automatically on nightly pipelines with slow-validate + dlint config.

nightly-hackage-perf: Runs automaticaly on nightly pipelines with release build and eventlogging enabled.

release-hackage-lint: Runs automatically on release pipelines with -dlint on a release bindist.

- - - - -
f4850f36 by Matthew Pickering at 2022-12-24T00:41:40-05:00
ci: Don't run abi-test-nightly on release jobs

The test is not configured to get the correct dependencies for the
release pipelines (and indeed stops the release pipeline being run at
all)

- - - - -
c264b06b by Matthew Pickering at 2022-12-24T00:41:40-05:00
ci: Run head.hackage jobs on upstream-testing branch rather than master

This change allows less priviledged users to trigger head.hackage jobs
because less permissions are needed to trigger jobs on the
upstream-testing branch, which is not protected.

There is a CI job which updates upstream-testing each hour to the state
of the master branch so it should always be relatively up-to-date.

- - - - -
63b97430 by Ben Gamari at 2022-12-24T00:42:16-05:00
llvmGen: Fix relaxed ordering

Previously I used LLVM's `unordered` ordering for the C11 `relaxed`
ordering. However, this is wrong and should rather use the LLVM
`monotonic` ordering.

Fixes #22640
- - - - -
f42ba88f by Ben Gamari at 2022-12-24T00:42:16-05:00
gitlab-ci: Introduce aarch64-linux-llvm job

This nightly job will ensure that we don't break the LLVM backend on
AArch64/Linux by bootstrapping GHC.

This would have caught #22640.

- - - - -
6d62f6bf by Matthew Pickering at 2022-12-24T00:42:51-05:00
Store RdrName rather than OccName in Holes

In #20472 it was pointed out that you couldn't defer out of scope but
the implementation collapsed a RdrName into an OccName to stuff it into
a Hole. This leads to the error message for a deferred qualified name
dropping the qualification which affects the quality of the error
message.

This commit adds a bit more structure to a hole, so a hole can replace a
RdrName without losing information about what that RdrName was. This is
important when printing error messages.

I also added a test which checks the Template Haskell deferral of out of
scope qualified names works properly.

Fixes #22130

- - - - -
3c3060e4 by Richard Eisenberg at 2022-12-24T17:34:19+00:00
Drop support for kind constraints.

This implements proposal 547 and closes ticket #22298.
See the proposal and ticket for motivation.

Compiler perf improves a bit

Metrics: compile_time/bytes allocated
-------------------------------------
  CoOpt_Singletons(normal)   -2.4% GOOD
            T12545(normal)   +1.0%
            T13035(normal)  -13.5% GOOD
            T18478(normal)   +0.9%
            T9872d(normal)   -2.2% GOOD

                 geo. mean   -0.2%
                 minimum    -13.5%
                 maximum     +1.0%

Metric Decrease:
    CoOpt_Singletons
    T13035
    T9872d

- - - - -
6d7d4393 by Ben Gamari at 2022-12-24T21:09:56-05:00
hadrian: Ensure that linker scripts are used when merging objects

In #22527 @rui314 inadvertantly pointed out a glaring bug in Hadrian's
implementation of the object merging rules: unlike the old `make` build
system we utterly failed to pass the needed linker scripts. Fix this.

- - - - -
a5bd0eb8 by Bodigrim at 2022-12-24T21:10:34-05:00
Document infelicities of instance Ord Double and workarounds

- - - - -
62b9a7b2 by Zubin Duggal at 2023-01-03T12:22:11+00:00
Force the Docs structure to prevent leaks in GHCi with -haddock without -fwrite-interface

Involves adding many new NFData instances.

Without forcing Docs, references to the TcGblEnv for each module are retained
by the Docs structure. Usually these are forced when the ModIface is serialised
but not when we aren't writing the interface.

- - - - -
21bedd84 by Facundo Domínguez at 2023-01-03T23:27:30-05:00
Explain the auxiliary functions of permutations

- - - - -
32255d05 by Matthew Pickering at 2023-01-04T11:58:42+00:00
compiler: Add -f[no-]split-sections flags

Here we add a `-fsplit-sections` flag which may some day replace
`-split-sections`. This has the advantage of automatically providing a
`-fno-split-sections` flag, which is useful for our packaging because we
enable `-split-sections` by default but want to disable it in certain
configurations.

- - - - -
e640940c by Matthew Pickering at 2023-01-04T11:58:42+00:00
hadrian: Fix computation of tables_next_to_code for outOfTreeCompiler

This copy-pasto was introduced in de5fb3489f2a9bd6dc75d0cb8925a27fe9b9084b

- - - - -
15bee123 by Matthew Pickering at 2023-01-04T11:58:42+00:00
hadrian: Add test:all_deps to build just testsuite dependencies

Fixes #22534

- - - - -
fec6638e by Matthew Pickering at 2023-01-04T11:58:42+00:00
hadrian: Add no_split_sections tranformer

This transformer reverts the effect of `split_sections`, which we intend
to use for platforms which don't support split sections.

In order to achieve this we have to modify the implemntation of the
split_sections transformer to store whether we are enabling
split_sections directly in the `Flavour` definition. This is because
otherwise there's no convenient way to turn off split_sections due to
having to pass additional linker scripts when merging objects.

- - - - -
3dc05726 by Matthew Pickering at 2023-01-04T11:58:42+00:00
check-exact: Fix build with -Werror

- - - - -
53a6ae7a by Matthew Pickering at 2023-01-04T11:58:42+00:00
ci: Build all test dependencies with in-tree compiler

This means that these executables will honour flavour transformers such
as "werror".

Fixes #22555

- - - - -
32e264c1 by Matthew Pickering at 2023-01-04T11:58:42+00:00
hadrian: Document using GHC environment variable to select boot compiler

Fixes #22340

- - - - -
be9dd9b0 by Matthew Pickering at 2023-01-04T11:58:42+00:00
packaging: Build perf builds with -split-sections

In 8f71d958 the make build system was made to use split-sections on
linux systems but it appears this logic never made it to hadrian.
There is the split_sections flavour transformer but this doesn't appear
to be used for perf builds on linux.

This is disbled on deb9 and windows due to #21670

Closes #21135

- - - - -
00dc5106 by Matthew Pickering at 2023-01-04T14:32:45-05:00
sphinx: Use modern syntax for extlinks

This fixes the following build error:

```
  Command line: /opt/homebrew/opt/sphinx-doc/bin/sphinx-build -b man -d /private/tmp/extra-dir-55768274273/.doctrees-man -n -w /private/tmp/extra-dir-55768274273/.log docs/users_guide /private/tmp/extra-dir-55768274273
  ===> Command failed with error code: 2

  Exception occurred:
    File "/opt/homebrew/Cellar/sphinx-doc/6.0.0/libexec/lib/python3.11/site-packages/sphinx/ext/extlinks.py", line 101, in role
      title = caption % part
              ~~~~~~~~^~~~~~
  TypeError: not all arguments converted during string formatting
```

I tested on Sphinx-5.1.1 and Sphinx-6.0.0

Thanks for sterni for providing instructions about how to test using
sphinx-6.0.0.

Fixes #22690

- - - - -
541aedcd by Krzysztof Gogolewski at 2023-01-05T10:48:34-05:00
Misc cleanup

- Remove unused uniques and hs-boot declarations
- Fix types of seq and unsafeCoerce#
- Remove FastString/String roundtrip in JS
- Use TTG to enforce totality
- Remove enumeration in Heap/Inspect; the 'otherwise' clause
  serves the primitive types well.

- - - - -
22bb8998 by Alan Zimmerman at 2023-01-05T10:49:09-05:00
EPA: Do not collect comments from end of file

In Parser.y semis1 production triggers for the virtual semi at the end
of the file. This is detected by it being zero length.

In this case, do not extend the span being used to gather comments, so
any final comments are allocated at the module level instead.

- - - - -
9e077999 by Vladislav Zavialov at 2023-01-05T23:01:55-05:00
HsToken in TypeArg (#19623)

Updates the haddock submodule.

- - - - -
b2a2db04 by Matthew Pickering at 2023-01-05T23:02:30-05:00
Revert "configure: Drop uses of AC_PROG_CC_C99"

This reverts commit 7c6de18dd3151ead954c210336728e8686c91de6.

Centos7 using a very old version of the toolchain (autotools-2.69) where
the behaviour of these macros has not yet changed. I am reverting this
without haste as it is blocking the 9.6 branch.

Fixes #22704

- - - - -
28f8c0eb by Luite Stegeman at 2023-01-06T18:16:24+09:00
Add support for sized literals in the bytecode interpreter.

The bytecode interpreter only has branching instructions for
word-sized values. These are used for pattern matching.
Branching instructions for other types (e.g. Int16# or Word8#)
weren't needed, since unoptimized Core or STG never requires
branching on types like this.

It's now possible for optimized STG to reach the bytecode
generator (e.g. fat interface files or certain compiler flag
combinations), which requires dealing with various sized
literals in branches.

This patch improves support for generating bytecode from
optimized STG by adding the following new bytecode
instructions:

    TESTLT_I64
    TESTEQ_I64
    TESTLT_I32
    TESTEQ_I32
    TESTLT_I16
    TESTEQ_I16
    TESTLT_I8
    TESTEQ_I8
    TESTLT_W64
    TESTEQ_W64
    TESTLT_W32
    TESTEQ_W32
    TESTLT_W16
    TESTEQ_W16
    TESTLT_W8
    TESTEQ_W8

Fixes #21945

- - - - -
ac39e8e9 by Matthew Pickering at 2023-01-06T13:47:00-05:00
Only store Name in FunRhs rather than Id with knot-tied fields

All the issues here have been caused by #18758.
The goal of the ticket is to be able to talk about things like
`LTyClDecl GhcTc`. In the case of HsMatchContext,
the correct "context" is whatever we want, and in fact storing just a
`Name` is sufficient and correct context, even if the rest of the AST is
storing typechecker Ids.

So this reverts (#20415, !5579) which intended to get closed to #18758 but
didn't really and introduced a few subtle bugs.

Printing of an error message in #22695 would just hang, because we would
attempt to print the `Id` in debug mode to assertain whether it was
empty or not. Printing the Name is fine for the error message.

Another consequence is that when `-dppr-debug` was enabled the compiler would
hang because the debug printing of the Id would try and print fields
which were not populated yet.

This also led to 32070e6c2e1b4b7c32530a9566fe14543791f9a6 having to add
a workaround for the `checkArgs` function which was probably a very
similar bug to #22695.

Fixes #22695

- - - - -
c306d939 by Matthew Pickering at 2023-01-06T22:08:53-05:00
ci: Upgrade darwin, windows and freebsd CI to use GHC-9.4.3

Fixes #22599

- - - - -
0db496ff by Matthew Pickering at 2023-01-06T22:08:53-05:00
darwin ci: Explicitly pass desired build triple to configure

On the zw3rk machines for some reason the build machine was inferred to
be arm64. Setting the build triple appropiately resolve this confusion
and we produce x86 binaries.

- - - - -
2459c358 by Ben Gamari at 2023-01-06T22:09:29-05:00
rts: MUT_VAR is not a StgMutArrPtrs

There was previously a comment claiming that the MUT_VAR closure type
had the layout of StgMutArrPtrs.
- - - - -
6206cb92 by Simon Peyton Jones at 2023-01-07T12:14:40-05:00
Make FloatIn robust to shadowing

This MR fixes #22622. See the new
  Note [Shadowing and name capture]

I did a bit of refactoring in sepBindsByDropPoint too.

The bug doesn't manifest in HEAD, but it did show up in 9.4,
so we should backport this patch to 9.4

- - - - -
a960ca81 by Matthew Pickering at 2023-01-07T12:15:15-05:00
T10955: Set DYLD_LIBRARY_PATH for darwin

The correct path to direct the dynamic linker on darwin is
DYLD_LIBRARY_PATH rather than LD_LIBRARY_PATH. On recent versions of OSX
using LD_LIBRARY_PATH seems to have stopped working.

For more reading see:

https://stackoverflow.com/questions/3146274/is-it-ok-to-use-dyld-library-path-on-mac-os-x-and-whats-the-dynamic-library-s

- - - - -
73484710 by Matthew Pickering at 2023-01-07T12:15:15-05:00
Skip T18623 on darwin (to add to the long list of OSs)

On recent versions of OSX, running `ulimit -v` results in

```
ulimit: setrlimit failed: invalid argument
```

Time is too short to work out what random stuff Apple has been doing
with ulimit, so just skip the test like we do for other platforms.

- - - - -
8c0ea25f by Matthew Pickering at 2023-01-07T12:15:15-05:00
Pass -Wl,-no_fixup_chains to ld64 when appropiate

Recent versions of MacOS use a version of ld where `-fixup_chains` is on by default.
This is incompatible with our usage of `-undefined dynamic_lookup`. Therefore we
explicitly disable `fixup-chains` by passing `-no_fixup_chains` to the linker on
darwin. This results in a warning of the form:

ld: warning: -undefined dynamic_lookup may not work with chained fixups

The manual explains the incompatible nature of these two flags:

     -undefined treatment
             Specifies how undefined symbols are to be treated. Options are: error, warning,
             suppress, or dynamic_lookup.  The default is error. Note: dynamic_lookup that
             depends on lazy binding will not work with chained fixups.

A relevant ticket is #22429

Here are also a few other links which are relevant to the issue:

Official comment: https://developer.apple.com/forums/thread/719961

More relevant links:

https://openradar.appspot.com/radar?id=5536824084660224

https://github.com/python/cpython/issues/97524

Note in release notes: https://developer.apple.com/documentation/xcode-release-notes/xcode-13-releas    e-notes

- - - - -
365b3045 by Matthew Pickering at 2023-01-09T02:36:20-05:00
Disable split sections on aarch64-deb10 build

See #22722

Failure on this job:

https://gitlab.haskell.org/ghc/ghc/-/jobs/1287852

```
Unexpected failures:
   /builds/ghc/ghc/tmp/ghctest-s3d8g1hj/test   spaces/testsuite/tests/th/T10828.run  T10828 [exit code non-0] (ext-interp)
   /builds/ghc/ghc/tmp/ghctest-s3d8g1hj/test   spaces/testsuite/tests/th/T13123.run  T13123 [exit code non-0] (ext-interp)
   /builds/ghc/ghc/tmp/ghctest-s3d8g1hj/test   spaces/testsuite/tests/th/T20590.run  T20590 [exit code non-0] (ext-interp)
Appending 232 stats to file: /builds/ghc/ghc/performance-metrics.tsv
```

```
Compile failed (exit code 1) errors were:
data family D_0 a_1 :: * -> *
data instance D_0 GHC.Types.Int GHC.Types.Bool :: * where
    DInt_2 :: D_0 GHC.Types.Int GHC.Types.Bool
data E_3 where MkE_4 :: a_5 -> E_3
data Foo_6 a_7 b_8 where
    MkFoo_9, MkFoo'_10 :: a_11 -> Foo_6 a_11 b_12
newtype Bar_13 :: * -> GHC.Types.Bool -> * where
    MkBar_14 :: a_15 -> Bar_13 a_15 b_16
data T10828.T (a_0 :: *) where
    T10828.MkT :: forall (a_1 :: *) . a_1 -> a_1 -> T10828.T a_1
    T10828.MkC :: forall (a_2 :: *) (b_3 :: *) . (GHC.Types.~) a_2
                                                               GHC.Types.Int => {T10828.foo :: a_2,
                                                                                 T10828.bar :: b_3} -> T10828.T GHC.Types.Int
T10828.hs:1:1: error: [GHC-87897]
    Exception when trying to run compile-time code:
      ghc-iserv terminated (-4)
    Code: (do TyConI dec <- runQ $ reify (mkName "T")
              runIO $ putStrLn (pprint dec) >> hFlush stdout
              d <- runQ
                     $ [d| data T' a :: Type
                             where
                               MkT' :: a -> a -> T' a
                               MkC' :: forall a b. (a ~ Int) => {foo :: a, bar :: b} -> T' Int |]
              runIO $ putStrLn (pprint d) >> hFlush stdout
              ....)
*** unexpected failure for T10828(ext-interp)
=====> 7000 of 9215 [0, 1, 0]
=====> 7000 of 9215 [0, 1, 0]
=====> 7000 of 9215 [0, 1, 0]
=====> 7000 of 9215 [0, 1, 0]
Compile failed (exit code 1) errors were:
T13123.hs:1:1: error: [GHC-87897]
    Exception when trying to run compile-time code:
      ghc-iserv terminated (-4)
    Code: ([d| data GADT
                 where MkGADT :: forall k proxy (a :: k). proxy a -> GADT |])
*** unexpected failure for T13123(ext-interp)
=====> 7100 of 9215 [0, 2, 0]
=====> 7100 of 9215 [0, 2, 0]
=====> 7200 of 9215 [0, 2, 0]
Compile failed (exit code 1) errors were:
T20590.hs:1:1: error: [GHC-87897]
    Exception when trying to run compile-time code:
      ghc-iserv terminated (-4)
    Code: ([d| data T where MkT :: forall a. a -> T |])
*** unexpected failure for T20590(ext-interp)
```

Looks fairly worrying to me.

- - - - -
965a2735 by Alan Zimmerman at 2023-01-09T02:36:20-05:00
EPA: exact print HsDocTy

To match ghc-exactprint
https://github.com/alanz/ghc-exactprint/pull/121

- - - - -
5d65773e by John Ericson at 2023-01-09T20:39:27-05:00
Remove RTS hack for configuring

See the brand new Note [Undefined symbols in the RTS] for additional
details.

- - - - -
e3fff751 by Sebastian Graf at 2023-01-09T20:40:02-05:00
Handle shadowing in DmdAnal (#22718)

Previously, when we had a shadowing situation like
```hs
f x = ... -- demand signature <1L><1L>

main = ... \f -> f 1 ...
```
we'd happily use the shadowed demand signature at the call site inside the
lambda. Of course, that's wrong and solution is simply to remove the demand
signature from the `AnalEnv` when we enter the lambda.
This patch does so for all binding constructs Core.

In #22718 the issue was caused by LetUp not shadowing away the existing demand
signature for the let binder in the let body. The resulting absent error is
fickle to reproduce; hence no reproduction test case. #17478 would help.

Fixes #22718.

It appears that TcPlugin_Rewrite regresses by ~40% on Darwin. It is likely that
DmdAnal was exploiting ill-scoped analysis results.

Metric increase ['bytes allocated'] (test_env=x86_64-darwin-validate):
    TcPlugin_Rewrite

- - - - -
d53f6f4d by Oleg Grenrus at 2023-01-09T21:11:02-05:00
Add safe list indexing operator: !?

With Joachim's amendments.

Implements https://github.com/haskell/core-libraries-committee/issues/110

- - - - -
cfaf1ad7 by Nicolas Trangez at 2023-01-09T21:11:03-05:00
rts, tests: limit thread name length to 15 bytes

On Linux, `pthread_setname_np` (or rather, the kernel) only allows for
thread names up to 16 bytes, including the terminating null byte.

This commit adds a note pointing this out in `createOSThread`, and fixes
up two instances where a thread name of more than 15 characters long was
used (in the RTS, and in a test-case).

Fixes: #22366
Fixes: https://gitlab.haskell.org/ghc/ghc/-/issues/22366
See: https://gitlab.haskell.org/ghc/ghc/-/issues/22366#note_460796

- - - - -
64286132 by Matthew Pickering at 2023-01-09T21:11:03-05:00
Store bootstrap_llvm_target and use it to set LlvmTarget in bindists

This mirrors some existing logic for the bootstrap_target which
influences how TargetPlatform is set.

As described on #21970 not storing this led to `LlvmTarget` being set incorrectly
and hence the wrong `--target` flag being passed to the C compiler.

Towards #21970

- - - - -
4724e8d1 by Matthew Pickering at 2023-01-09T21:11:04-05:00
Check for FP_LD_NO_FIXUP_CHAINS in installation configure script

Otherwise, when installing from a bindist the C flag isn't passed to the
C compiler.

This completes the fix for #22429

- - - - -
2e926b88 by Georgi Lyubenov at 2023-01-09T21:11:07-05:00
Fix outdated link to Happy section on sequences

- - - - -
146a1458 by Matthew Pickering at 2023-01-09T21:11:07-05:00
Revert "NCG(x86): Compile add+shift as lea if possible."

This reverts commit 20457d775885d6c3df020d204da9a7acfb3c2e5a.

See #22666 and #21777

- - - - -
ad73e9f4 by Ben Gamari at 2023-01-10T21:51:06-05:00
Bump Windows toolchain

Updates to LLVM 14, hopefully fixing #21964.

- - - - -


9 changed files:

- − .appveyor.sh
- .editorconfig
- .gitignore
- .gitlab-ci.yml
- .gitlab/ci.sh
- .gitlab/darwin/toolchain.nix
- + .gitlab/gen_ci.hs
- + .gitlab/generate_jobs
- + .gitlab/hello.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/7f7b23698d0ee292927048ada4b74bcdce59544d...ad73e9f491b74b6ffff4cc663f4fdc780dfaf3cd

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/7f7b23698d0ee292927048ada4b74bcdce59544d...ad73e9f491b74b6ffff4cc663f4fdc780dfaf3cd
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/20230110/f9520ec9/attachment-0001.html>


More information about the ghc-commits mailing list