[Git][ghc/ghc][wip/tsan/all] 277 commits: Introduce OutputableP

Ben Gamari gitlab at gitlab.haskell.org
Sun Oct 25 01:11:23 UTC 2020



Ben Gamari pushed to branch wip/tsan/all at Glasgow Haskell Compiler / GHC


Commits:
ca48076a by Sylvain Henry at 2020-09-17T20:04:08-04:00
Introduce OutputableP

Some types need a Platform value to be pretty-printed: CLabel, Cmm
types, instructions, etc.

Before this patch they had an Outputable instance and the Platform value
was obtained via sdocWithDynFlags. It meant that the *renderer* of the
SDoc was responsible of passing the appropriate Platform value (e.g. via
the DynFlags given to showSDoc).  It put the burden of passing the
Platform value on the renderer while the generator of the SDoc knows the
Platform it is generating the SDoc for and there is no point passing a
different Platform at rendering time.

With this patch, we introduce a new OutputableP class:

   class OutputableP a where
      pdoc :: Platform -> a -> SDoc

With this class we still have some polymorphism as we have with `ppr`
(i.e. we can use `pdoc` on a variety of types instead of having a
dedicated `pprXXX` function for each XXX type).

One step closer removing `sdocWithDynFlags` (#10143) and supporting
several platforms (#14335).

- - - - -
e45c8544 by Sylvain Henry at 2020-09-17T20:04:08-04:00
Generalize OutputableP

Add a type parameter for the environment required by OutputableP. It
avoids tying Platform with OutputableP.

- - - - -
37aa224a by Sylvain Henry at 2020-09-17T20:04:08-04:00
Add note about OutputableP

- - - - -
7f2785f2 by Sylvain Henry at 2020-09-17T20:04:08-04:00
Remove pprPrec from Outputable (unused)

- - - - -
b689f3db by Sylvain Henry at 2020-09-17T20:04:46-04:00
Bignum: add clamping naturalToWord (fix #18697)

- - - - -
0799b3de by Ben Gamari at 2020-09-18T15:55:50-04:00
rts/nonmoving: Add missing STM write barrier

When updating a TRec for a TVar already part of a transaction we
previously neglected to add the old value to the update remembered set.
I suspect this was the cause of #18587.

- - - - -
c4921349 by Ben Gamari at 2020-09-18T15:56:25-04:00
rts: Refactor foreign export tracking

This avoids calling `libc` in the initializers which are responsible for
registering foreign exports. We believe this should avoid the corruption
observed in #18548.

See Note [Tracking foreign exports] in rts/ForeignExports.c for an
overview of the new scheme.

- - - - -
40dc9106 by Ben Gamari at 2020-09-18T15:56:25-04:00
rts: Refactor unloading of foreign export StablePtrs

Previously we would allocate a linked list cell for each foreign export.
Now we can avoid this by taking advantage of the fact that they are
already broken into groups.

- - - - -
45fa8218 by Simon Jakobi at 2020-09-19T06:57:36-04:00
Deprecate Data.Semigroup.Option

Libraries email: https://mail.haskell.org/pipermail/libraries/2018-April/028724.html

GHC issue: https://gitlab.haskell.org/ghc/ghc/issues/15028

Corresponding PRs for deepseq:
* https://github.com/haskell/deepseq/pull/55
* https://github.com/haskell/deepseq/pull/57

Bumps the deepseq submodule.

- - - - -
2229d570 by Vladislav Zavialov at 2020-09-19T15:47:24-04:00
Require happy >=1.20

- - - - -
a89c2fba by Ben Gamari at 2020-09-19T15:47:24-04:00
ci.sh: Enforce minimum happy/alex versions

Also, always invoke cabal-install to ensure that happy/alex symlinks are
up-to-date.

- - - - -
2f7ef2fb by Ben Gamari at 2020-09-19T15:47:24-04:00
gitlab-ci: Ensure that cabal-install overwrites existing executables

Previously cabal-install wouldn't overwrite toolchain executables if
they already existed (as they likely would due to caching).

- - - - -
ac213d26 by Ryan Scott at 2020-09-19T15:48:01-04:00
Wire in constraint tuples

This wires in the definitions of the constraint tuple classes. The
key changes are in:

* `GHC.Builtin.Types`, where the `mk_ctuple` function is used to
  define constraint tuple type constructors, data constructors, and
  superclass selector functions, and
* `GHC.Builtin.Uniques`. In addition to wiring in the `Unique`s for
  constraint tuple type and data constructors, we now must wire in
  the superclass selector functions. Luckily, this proves to be not
  that challenging. See the newly added comments.

Historical note: constraint tuples used to be wired-in until about
five years ago, when commit 130e93aab220bdf14d08028771f83df210da340b
turned them into known-key names. This was done as part of a larger
refactor to reduce the number of special cases for constraint tuples,
but the commit message notes that the main reason that constraint
tuples were made known-key (as opposed to boxed/unboxed tuples, which
are wired in) is because it was awkward to wire in the superclass
selectors. This commit solves the problem of wiring in superclass
selectors.

Fixes #18635.

-------------------------
Metric Decrease:
    T10421
    T12150
    T12227
    T12234
    T12425
    T13056
    T13253-spj
    T18282
    T18304
    T5321FD
    T5321Fun
    T5837
    T9961
Metric Decrease (test_env='x86_64-linux-deb9-unreg-hadrian'):
    T12707
Metric Decrease (test_env='x86_64-darwin'):
    T4029
-------------------------

- - - - -
e195dae6 by Wander Hillen at 2020-09-19T15:48:41-04:00
Export singleton function from Data.List

Data.OldList exports a monomorphized singleton function but
it is not re-exported by Data.List. Adding the export to
Data.List causes a conflict with a 14-year old function of the
same name and type by SPJ in GHC.Utils.Misc. We can't just remove
this function because that leads to a problems when building
GHC with a stage0 compiler that does not have singleton in
Data.List yet. We also can't hide the function in GHC.Utils.Misc
since it is not possible to hide a function from a module if the
module does not export the function. To work around this, all
places where the Utils.Misc singleton was used now use a qualified
version like Utils.singleton and in GHC.Utils.Misc we are very
specific about which version we export.

- - - - -
9c1b8ad9 by Sylvain Henry at 2020-09-19T15:49:19-04:00
Bump Stack resolver

- - - - -
d05d13ce by John Ericson at 2020-09-19T15:49:57-04:00
Cinch -fno-warn-name-shadowing down to specific GHCi module

- - - - -
f1accd00 by Sylvain Henry at 2020-09-19T15:49:57-04:00
Add quick-validate Hadrian flavour (quick + -Werror)

- - - - -
8f8d51f1 by Andreas Klebinger at 2020-09-19T15:50:33-04:00
Fix docs who misstated how the RTS treats size suffixes.

They are parsed as multiples of 1024. Not 1000. The docs
used to imply otherwise.

See decodeSize in rts/RtsFlags.c for the logic for this.

- - - - -
2ae0edbd by Andreas Klebinger at 2020-09-19T15:50:33-04:00
Fix a codeblock in ghci.rst

- - - - -
4df3aa95 by Ben Gamari at 2020-09-19T15:51:07-04:00
users guide: Fix various documentation issues

- - - - -
885ecd18 by Ben Gamari at 2020-09-19T15:51:07-04:00
hadrian: Fail on Sphinx syntax errors

Specifically the "Inline literal start-string without end-string"
warning, which typically means that the user neglected to separate
an inline code block from suffix text with a backslash.

- - - - -
b26cd867 by David Feuer at 2020-09-19T15:51:44-04:00
Unpack the MVar in Compact

The `MVar` lock in `Compact` was unnecessarily lazy, creating an extra indirection and wasting two words. Make it strict.
- - - - -
760307cf by Artyom Kuznetsov at 2020-09-19T15:52:21-04:00
Remove GADT self-reference check (#11554, #12081, #12174, fixes #15942)

Reverts 430f5c84dac1eab550110d543831a70516b5cac8

- - - - -
057db94c by Ben Gamari at 2020-09-19T15:52:56-04:00
rts: Drop field initializer on thread_basic_info_data_t

This struct has a number of fields and we only care that the value is
initialized with zeros. This eliminates the warnings noted in #17905.

- - - - -
87e2e2b1 by Vladislav Zavialov at 2020-09-19T23:55:30+03:00
Resolve shift/reduce conflicts with %shift (#17232)

- - - - -
66cba46e by Ben Gamari at 2020-09-20T20:30:57-04:00
testsuite: Unmark T12971 as broken on Windows

It's unclear why, but this no longer seems to fail.

Closes #17945.

- - - - -
816811d4 by Ben Gamari at 2020-09-20T20:30:57-04:00
testsuite: Unmark T5975[ab] as broken on Windows

Sadly it's unclear *why* they have suddenly started working.

Closes #7305.

- - - - -
43a43d39 by Ben Gamari at 2020-09-20T20:30:57-04:00
base/testsuite: Add missing LANGUAGE pragma in ThreadDelay001

Only affected the Windows codepath.

- - - - -
ced8f113 by Ben Gamari at 2020-09-20T20:30:57-04:00
testsuite: Update expected output for outofmem on Windows

The error originates from osCommitMemory rather than getMBlocks.

- - - - -
ea08aead by Ben Gamari at 2020-09-20T20:30:57-04:00
testsuite: Mark some GHCi/Makefile tests as broken on Windows

See #18718.

- - - - -
caf6a5a3 by GHC GitLab CI at 2020-09-20T20:30:57-04:00
testsuite: Fix WinIO error message normalization

This wasn't being applied to stderr.

- - - - -
93ab3e8d by GHC GitLab CI at 2020-09-20T20:30:57-04:00
testsuite: Mark tempfiles as broken on Win32 without WinIO

The old POSIX emulation appears to ignore the user-requested prefix.

- - - - -
9df77fed by GHC GitLab CI at 2020-09-20T20:30:57-04:00
testsuite: Mark TH_spliceE5_prof as broken on Windows

Due to #18721.

- - - - -
1a0f8243 by Ryan Scott at 2020-09-21T16:45:47-04:00
Remove unused ThBrackCtxt and ResSigCtxt

Fixes #18715.

- - - - -
2f222b12 by Ryan Scott at 2020-09-21T16:45:47-04:00
Disallow constraints in KindSigCtxt

This patch cleans up how `GHC.Tc.Validity` classifies `UserTypeCtxt`s
that can only refer to kind-level positions, which is important for
rejecting certain classes of programs. In particular, this patch:

* Introduces a new `TypeOrKindCtxt` data type and
  `typeOrKindCtxt :: UserTypeCtxt -> TypeOrKindCtxt` function, which
  determines whether a `UserTypeCtxt` can refer to type-level
  contexts, kind-level contexts, or both.
* Defines the existing `allConstraintsAllowed` and `vdqAllowed`
  functions in terms of `typeOrKindCtxt`, which avoids code
  duplication and ensures that they stay in sync in the future.

The net effect of this patch is that it fixes #18714, in which it was
discovered that `allConstraintsAllowed` incorrectly returned `True`
for `KindSigCtxt`. Because `typeOrKindCtxt` now correctly classifies
`KindSigCtxt` as a kind-level context, this bug no longer occurs.

- - - - -
aaa51dcf by Ben Gamari at 2020-09-21T16:46:22-04:00
hadrian: Add extra-deps: happy-1.20 to stack.yaml

GHC now requires happy-1.20, which isn't available in LTS-16.14.

Fixes #18726.
- - - - -
6de40f83 by Simon Peyton Jones at 2020-09-22T05:37:24-04:00
Better eta-expansion (again) and don't specilise DFuns

This patch fixes #18223, which made GHC generate an exponential
amount of code.  There are three quite separate changes in here

1.  Re-engineer eta-expansion (again).  The eta-expander was
    generating lots of intermediate stuff, which could be optimised
    away, but which choked the simplifier meanwhile.  Relatively
    easy to kill it off at source.

    See Note [The EtaInfo mechanism] in GHC.Core.Opt.Arity.
    The main new thing is the use of pushCoArg in getArg_maybe.

2.  Stop Specialise specalising DFuns.  This is the cause of a huge
    (and utterly unnecessary) blowup in program size in #18223.
    See Note [Do not specialise DFuns] in GHC.Core.Opt.Specialise.

    I also refactored the Specialise monad a bit... it was silly,
    because it passed on unchanging values as if they were mutable
    state.

3.  Do an extra Simplifer run, after SpecConstra and before
    late-Specialise.  I found (investigating perf/compiler/T16473)
    that failing to do this was crippling *both* SpecConstr *and*
    Specialise.  See Note [Simplify after SpecConstr] in
    GHC.Core.Opt.Pipeline.

    This change does mean an extra run of the Simplifier, but only
    with -O2, and I think that's acceptable.

    T16473 allocates *three* times less with this change.  (I changed
    it to check runtime rather than compile time.)

Some smaller consequences

* I moved pushCoercion, pushCoArg and friends from SimpleOpt
  to Arity, because it was needed by the new etaInfoApp.

  And pushCoValArg now returns a MCoercion rather than Coercion for
  the argument Coercion.

* A minor, incidental improvement to Core pretty-printing

This does fix #18223, (which was otherwise uncompilable. Hooray.  But
there is still a big intermediate because there are some very deeply
nested types in that program.

Modest reductions in compile-time allocation on a couple of benchmarks
    T12425     -2.0%
    T13253    -10.3%

Metric increase with -O2, due to extra simplifier run
    T9233     +5.8%
    T12227    +1.8%
    T15630    +5.0%

There is a spurious apparent increase on heap residency on T9630,
on some architectures at least.  I tried it with -G1 and the residency
is essentially unchanged.

Metric Increase
    T9233
    T12227
    T9630

Metric Decrease
    T12425
    T13253

- - - - -
416bd50e by Simon Peyton Jones at 2020-09-22T05:37:59-04:00
Fix the occurrence analyser

Ticket #18603 demonstrated that the occurrence analyser's
handling of

  local RULES for imported Ids

(which I now call IMP-RULES) was inadequate.  It led the simplifier
into an infnite loop by failing to label a binder as a loop breaker.

The main change in this commit is to treat IMP-RULES in a simple and
uniform way: as extra rules for the local binder.  See
  Note [IMP-RULES: local rules for imported functions]

This led to quite a bit of refactoring.  The result is still tricky,
but it's much better than before, and better documented I think.

Oh, and it fixes the bug.

- - - - -
6fe8a0c7 by Sebastian Graf at 2020-09-22T05:38:35-04:00
PmCheck - Comments only: Replace /~ by ≁

- - - - -
e9501547 by Sebastian Graf at 2020-09-22T05:38:35-04:00
PmCheck: Rewrite inhabitation test

We used to produce inhabitants of a pattern-match refinement type Nabla
in the checker in at least two different and mostly redundant ways:

  1. There was `provideEvidence` (now called
     `generateInhabitingPatterns`) which is used by
     `GHC.HsToCore.PmCheck` to produce non-exhaustive patterns, which
     produces inhabitants of a Nabla as a sub-refinement type where all
     match variables are instantiated.
  2. There also was `ensure{,All}Inhabited` (now called
     `inhabitationTest`) which worked slightly different, but was
     whenever new type constraints or negative term constraints were
     added. See below why `provideEvidence` and `ensureAllInhabited`
     can't be the same function, the main reason being performance.
  3. And last but not least there was the `nonVoid` test, which tested
     that a given type was inhabited. We did use this for strict fields
     and -XEmptyCase in the past.

The overlap of (3) with (2) was always a major pet peeve of mine. The
latter was quite efficient and proven to work for recursive data types,
etc, but could not handle negative constraints well (e.g. we often want
to know if a *refined* type is empty, such as `{ x:[a] | x /= [] }`).

Lower Your Guards suggested that we could get by with just one, by
replacing both functions with `inhabitationTest` in this patch.
That was only possible by implementing the structure of φ constraints
as in the paper, namely the semantics of φ constructor constraints.

This has a number of benefits:

  a. Proper handling of unlifted types and strict fields, fixing #18249,
     without any code duplication between
     `GHC.HsToCore.PmCheck.Oracle.instCon` (was `mkOneConFull`) and
     `GHC.HsToCore.PmCheck.checkGrd`.
  b. `instCon` can perform the `nonVoid` test (3) simply by emitting
     unliftedness constraints for strict fields.
  c. `nonVoid` (3) is thus simply expressed by a call to
     `inhabitationTest`.
  d. Similarly, `ensureAllInhabited` (2), which we called after adding
     type info, now can similarly be expressed as the fuel-based
     `inhabitationTest`.

See the new `Note [Why inhabitationTest doesn't call generateInhabitingPatterns]`
why we still have tests (1) and (2).

Fixes #18249 and brings nice metric decreases for `T17836` (-76%) and
`T17836b` (-46%), as well as `T18478` (-8%) at the cost of a few very
minor regressions (< +2%), potentially due to the fact that
`generateInhabitingPatterns` does more work to suggest the minimal
COMPLETE set.

Metric Decrease:
    T17836
    T17836b

- - - - -
086ef018 by Hécate at 2020-09-23T06:52:08-04:00
Remove the list of loaded modules from the ghci prompt

- - - - -
d7385f70 by Ben Gamari at 2020-09-23T06:52:44-04:00
Bump submodules

* Bump bytestring to 0.10.12.0
* Bump Cabal to 3.4.0.0-rc3
* Bump Win32 to 2.10.0.0

- - - - -
667d6355 by Sylvain Henry at 2020-09-23T20:43:48-04:00
Refactor CLabel pretty-printing

* Don't depend on the selected backend to know if we print Asm or C
  labels: we already have PprStyle to determine this. Moreover even when
  a native backend is used (NCG, LLVM) we may want to C headers
  containing pretty-printed labels, so it wasn't a good predicate
  anyway.

* Make pretty-printing code clearer and avoid partiality

- - - - -
a584366b by Sylvain Henry at 2020-09-23T20:43:48-04:00
Remove sdocWithDynFlags (fix #10143)

- - - - -
a997fa01 by Sylvain Henry at 2020-09-23T20:43:48-04:00
Preliminary work towards removing DynFlags -> Driver.Ppr dependency

- - - - -
31fea307 by Hécate at 2020-09-23T20:44:24-04:00
Remove redundant "do", "return" and language extensions from base

- - - - -
04d64331 by syd at cs-syd.eu at 2020-09-24T13:15:54-04:00
Update Lock.hs with more documentation to make sure that the Boolean return value is clear.

[skip ci]

- - - - -
97cff919 by Simon Peyton Jones at 2020-09-24T13:16:32-04:00
Implement Quick Look impredicativity

This patch implements Quick Look impredicativity (#18126), sticking
very closely to the design in
    A quick look at impredicativity, Serrano et al, ICFP 2020

The main change is that a big chunk of GHC.Tc.Gen.Expr has been
extracted to two new modules
    GHC.Tc.Gen.App
    GHC.Tc.Gen.Head
which deal with typechecking n-ary applications, and the head of
such applications, respectively.  Both contain a good deal of
documentation.

Three other loosely-related changes are in this patch:

* I implemented (partly by accident) points (2,3)) of the accepted GHC
  proposal "Clean up printing of foralls", namely
  https://github.com/ghc-proposals/ghc-proposals/blob/
        master/proposals/0179-printing-foralls.rst
  (see #16320).

  In particular, see Note [TcRnExprMode] in GHC.Tc.Module
  - :type instantiates /inferred/, but not /specified/, quantifiers
  - :type +d instantiates /all/ quantifiers
  - :type +v is killed off

  That completes the implementation of the proposal,
  since point (1) was done in
    commit df08468113ab46832b7ac0a7311b608d1b418c4d
    Author: Krzysztof Gogolewski <krzysztof.gogolewski at tweag.io>
    Date:   Mon Feb 3 21:17:11 2020 +0100
    Always display inferred variables using braces

* HsRecFld (which the renamer introduces for record field selectors),
  is now preserved by the typechecker, rather than being rewritten
  back to HsVar.  This is more uniform, and turned out to be more
  convenient in the new scheme of things.

* The GHCi debugger uses a non-standard unification that allows the
  unification variables to unify with polytypes.  We used to hack
  this by using ImpredicativeTypes, but that doesn't work anymore
  so I introduces RuntimeUnkTv.  See Note [RuntimeUnkTv] in
  GHC.Runtime.Heap.Inspect

Updates haddock submodule.

WARNING: this patch won't validate on its own.  It was too
hard to fully disentangle it from the following patch, on
type errors and kind generalisation.

Changes to tests

* Fixes #9730 (test added)

* Fixes #7026 (test added)

* Fixes most of #8808, except function `g2'` which uses a
  section (which doesn't play with QL yet -- see #18126)
  Test added

* Fixes #1330. NB Church1.hs subsumes Church2.hs, which is now deleted

* Fixes #17332 (test added)

* Fixes #4295

* This patch makes typecheck/should_run/T7861 fail.
  But that turns out to be a pre-existing bug: #18467.
  So I have just made T7861 into expect_broken(18467)

- - - - -
9fa26aa1 by Simon Peyton Jones at 2020-09-24T13:16:32-04:00
Improve kind generalisation, error messages

This patch does two things:

* It refactors GHC.Tc.Errors a bit.  In debugging Quick Look I was
  forced to look in detail at error messages, and ended up doing a bit
  of refactoring, esp in mkTyVarEqErr'.  It's still quite a mess, but
  a bit better, I think.

* It makes a significant improvement to the kind checking of type and
  class declarations. Specifically, we now ensure that if kind
  checking fails with an unsolved constraint, all the skolems are in
  scope.  That wasn't the case before, which led to some obscure error
  messages; and occasional failures with "no skolem info" (eg #16245).

Both of these, and the main Quick Look patch itself, affect a /lot/ of
error messages, as you can see from the number of files changed.  I've
checked them all; I think they are as good or better than before.

Smaller things

* I documented the various instances of VarBndr better.
  See Note [The VarBndr tyep and its uses] in GHC.Types.Var

* Renamed GHC.Tc.Solver.simpl_top to simplifyTopWanteds

* A bit of refactoring in bindExplicitTKTele, to avoid the
  footwork with Either.  Simpler now.

* Move promoteTyVar from GHC.Tc.Solver to GHC.Tc.Utils.TcMType

Fixes #16245 (comment 211369), memorialised as
  typecheck/polykinds/T16245a
Also fixes the three bugs in #18640

- - - - -
6d0ce0eb by Sebastian Graf at 2020-09-24T13:17:07-04:00
PmCheck: Desugar string literal patterns with -XRebindableSyntax correctly (#18708)

Fixes #18708.

- - - - -
007940d2 by Hécate at 2020-09-24T13:17:44-04:00
Namespace the Hadrian linting rule for base

- - - - -
5b727189 by Andreas Klebinger at 2020-09-25T21:10:20-04:00
Make sizeExpr strict in the size threshold to facilitate WW.

- - - - -
dd664031 by Ben Gamari at 2020-09-25T21:10:56-04:00
ci.sh: Factor out common utilities

- - - - -
5b78e865 by Ben Gamari at 2020-09-25T21:10:56-04:00
ci: Add ad-hoc performance testing rule

- - - - -
29885f07 by Zubin Duggal at 2020-09-25T21:11:32-04:00
Stop removing definitions of record fields in GHC.Iface.Ext.Ast

- - - - -
0d6519d9 by Ben Gamari at 2020-09-25T21:12:08-04:00
gitlab-ci: Drop Darwin cleanup job

We now have a proper periodic clean-up script installed on the runners.

- - - - -
277d20af by Sebastian Graf at 2020-09-25T21:12:44-04:00
Add regression tests for #18371

They have been fixed by !3959, I believe.
Fixes #18371.

- - - - -
8edf6056 by Sebastian Graf at 2020-09-25T21:12:44-04:00
Add a regression test for #18609

The egregious performance hits are gone since !4050.
So we fix #18609.

- - - - -
4a1b89a4 by Sebastian Graf at 2020-09-25T21:12:44-04:00
Accept new test output for #17218

The expected test output was plain wrong.
It has been fixed for a long time.
Thus we can close #17218.

- - - - -
51606236 by Sven Tennie at 2020-09-25T21:13:19-04:00
Print RET_BIG stack closures

A RET_BIG closure has a large bitmap that describes it's payload and can
be printed with printLargeBitmap().

Additionally, the output for payload closures of small and big bitmaps is
changed: printObj() is used to print a bit more information about what's
on the stack.

- - - - -
2707c4ea by Arnaud Spiwack at 2020-09-25T21:13:58-04:00
Pattern guards BindStmt always use multiplicity Many

Fixes #18439 .

The rhs of the pattern guard was consumed with multiplicity one, while
the pattern assumed it was Many. We use Many everywhere instead.

This is behaviour consistent with that of `case` expression. See #18738.

- - - - -
92daad24 by Sylvain Henry at 2020-09-25T21:14:36-04:00
Bignum: refactor backend modules

* move backends into GHC.Num.Backend.*
* split backend selection into GHC.Num.Backend and
  GHC.Num.Backend.Selected to avoid duplication with the Check backend

- - - - -
04bc50b3 by Sylvain Henry at 2020-09-25T21:14:36-04:00
Bignum: implement extended GCD (#18427)

- - - - -
6a7dae4b by Krzysztof Gogolewski at 2020-09-25T21:15:14-04:00
Fix typed holes causing linearity errors (#18491)

- - - - -
83407ffc by Krzysztof Gogolewski at 2020-09-25T21:15:53-04:00
Various documentation fixes

* Remove UnliftedFFITypes from conf. Some time ago, this extension
  was undocumented and we had to silence a warning.
  This is no longer needed.
* Use r'' in conf.py. This fixes a Sphinx warning:
  WARNING: Support for evaluating Python 2 syntax is deprecated and will be removed in Sphinx 4.0. Convert docs/users_guide/conf.py to Python 3 syntax.
* Mark GHCForeignImportPrim as documented
* Fix formatting in template_haskell.rst
* Remove 'recursive do' from the list of unsupported items in TH

- - - - -
af1e84e7 by Sebastian Graf at 2020-09-26T05:36:46-04:00
PmCheck: Big refactor of module structure

  * Move everything from `GHC.HsToCore.PmCheck.*` to
    `GHC.HsToCore.Pmc.*` in analogy to `GHC.Tc`, rename exported
    `covCheck*` functions to `pmc*`
  * Rename `Pmc.Oracle` to `Pmc.Solver`
  * Split off the LYG desugaring and checking steps into their own
    modules (`Pmc.Desugar` and `Pmc.Check` respectively)
  * Split off a `Pmc.Utils` module with stuff shared by
    `Pmc.{,Desugar,Check,Solver}`
  * Move `Pmc.Types` to `Pmc.Solver.Types`, add a new `Pmc.Types` module
    with all the LYG types, which form the interfaces between
    `Pmc.{Desugar,Check,Solver,}`.

- - - - -
f08f98e8 by Sebastian Graf at 2020-09-26T05:36:46-04:00
Extract SharedIdEnv into its own module

It's now named `GHC.Types.Unique.SDFM.UniqSDFM`.
The implementation is more clear about its stated goals and supported
operations.

- - - - -
1cde295c by Sylvain Henry at 2020-09-26T05:37:23-04:00
Bignum: add bigNatFromWordArray

Reimplementation of integer-gmp's byteArrayToBigNat#

- - - - -
bda55fa0 by Krzysztof Gogolewski at 2020-09-26T13:18:22-04:00
Make 'undefined x' linear in 'x' (#18731)

- - - - -
160fba4a by Krzysztof Gogolewski at 2020-09-26T13:19:00-04:00
Disallow linear types in FFI (#18472)

- - - - -
e124f2a7 by Krzysztof Gogolewski at 2020-09-26T13:19:36-04:00
Fix handling of function coercions (#18747)

This was broken when we added multiplicity to the function type.

- - - - -
7ff43382 by Vladislav Zavialov at 2020-09-27T03:01:31+03:00
Comments: change outdated reference to mergeOps

As of 686e06c59c3aa6b66895e8a501c7afb019b09e36,
GHC.Parser.PostProcess.mergeOps no longer exists.

[ci skip]

- - - - -
4edf5527 by Vladislav Zavialov at 2020-09-27T10:04:12-04:00
Don't rearrange (->) in the renamer

The parser produces an AST where the (->)
is already associated correctly:

  1. (->) has the least possible precedence
  2. (->) is right-associative

Thus we don't need to handle it in mkHsOpTyRn.

- - - - -
a9ce159b by Vladislav Zavialov at 2020-09-27T10:04:12-04:00
Remove outdated comment in rnHsTyKi

This comment dates back to 3df40b7b78044206bbcffe3e2c0a57d901baf5e8
and does not seem relevant anymore.

- - - - -
583a2070 by Richard Eisenberg at 2020-09-29T00:31:27-04:00
Optimize NthCo (FunCo ...) in coercion opt

We were missing this case previously.

Close #18528.

Metric Decrease:
    T18223
    T5321Fun

- - - - -
b31a3360 by Krzysztof Gogolewski at 2020-09-29T00:32:05-04:00
Linear types: fix kind inference when checking datacons

- - - - -
5830a12c by Vladislav Zavialov at 2020-09-29T00:32:05-04:00
New linear types syntax: a %p -> b (#18459)

Implements GHC Proposal #356

Updates the haddock submodule.

- - - - -
bca4d36d by Vladislav Zavialov at 2020-09-29T00:32:05-04:00
Improve error messages for (a %m) without LinearTypes

Detect when the user forgets to enable the LinearTypes
extension and produce a better error message.

Steals the (a %m) syntax from TypeOperators, the workaround
is to write (a % m) instead.

- - - - -
b9635d0a by Benjamin Maurer at 2020-09-29T00:32:43-04:00
Description of flag `-H` was in 'verbosity options', moved to 'misc'.
Fixes #18699

- - - - -
74c797f6 by Benjamin Maurer at 2020-09-29T00:33:20-04:00
Workaround for #18623: GHC crashes bc. under rlimit for vmem it will reserve
_all_ of it, leaving nothing for, e.g., thread stacks.
Fix will only allocate 2/3rds and check whether remainder is at least large
enough for minimum amount of thread stacks.

- - - - -
4365d77a by Ryan Scott at 2020-09-29T00:33:57-04:00
Add regression test #18501

ghc/ghc!3220 ended up fixing #18501. This patch adds a regression
test for #18501 to ensure that it stays fixed.

- - - - -
8e3f00dd by Sylvain Henry at 2020-09-29T17:24:03+02:00
Make the parser module less dependent on DynFlags

Bump haddock submodule

- - - - -
3ab0d8f7 by Sebastian Graf at 2020-09-30T02:48:27-04:00
PmCheck: Long-distance information for LocalBinds (#18626)

Now `desugarLocalBind` (formerly `desugarLet`) reasons about

  * `FunBind`s that
    * Have no pattern matches (so which aren't functions)
    * Have a singleton match group with a single GRHS
    * (which may have guards)
  * and looks through trivial post-typechecking `AbsBinds` in doing so
    to pick up the introduced renamings.

And desugars to `PmLet` LYG-style guards. Since GRHSs are no longer
denoted simply by `NonEmpty PmGRHS`, but also need to carry a `[PmGrd]`
for the `PmLet`s from `LocalBind`s, I added `PmGRHSs` to capture that.

Since we call out to the desugarer more often, I found that there were
superfluous warnings emitted when desugaring e.g. case expressions.
Thus, I made sure that we deactivate any warnings in the LYG desugaring
steps by the new wrapper function `noCheckDs`.

There's a regression test in `T18626`. Fixes #18626.

- - - - -
f8f60efc by Ben Gamari at 2020-09-30T02:49:03-04:00
testsuite: Mark T12971 as broken on Windows

Due to #17945.

- - - - -
6527fc57 by Ben Gamari at 2020-09-30T02:49:03-04:00
Bump Cabal, hsc2hs, directory, process submodules

Necessary for recent Win32 bump.

- - - - -
df3f5880 by Sylvain Henry at 2020-09-30T02:49:41-04:00
Remove unsafeGlobalDynFlags (#17957, #14597)

There are still global variables but only 3 booleans instead of a single
DynFlags.

- - - - -
9befd94d by Sylvain Henry at 2020-09-30T02:49:41-04:00
Remove unused global variables

Some removed globals variables were still declared in the RTS.

They were removed in the following commits:

* 4fc6524a2a4a0003495a96c8b84783286f65c198
* 0dc7985663efa1739aafb480759e2e2e7fca2a36
* bbd3c399939311ec3e308721ab87ca6b9443f358

- - - - -
7c98699f by Richard Eisenberg at 2020-09-30T02:50:17-04:00
Omit redundant kind equality check in solver

See updated Note [Use loose types in inert set] in
GHC.Tc.Solver.Monad.

Close #18753.

- - - - -
39549826 by Sebastian Graf at 2020-09-30T02:50:54-04:00
Pmc: Don't call exprType on type arguments (#18767)

Fixes #18767.

- - - - -
235e410f by Richard Eisenberg at 2020-09-30T02:51:29-04:00
Regression test for #10709.

Close #10709

- - - - -
5c32655f by Ben Gamari at 2020-09-30T22:31:55-04:00
hadrian/doc: Clarify documentation of key-value configuration
- - - - -
0bb02873 by Sylvain Henry at 2020-10-01T18:34:53-04:00
Add test for T18574

- - - - -
e393f213 by Sylvain Henry at 2020-10-01T18:34:53-04:00
Allow fusion with catMaybes (#18574)

Metric Decrease:
   T18574

- - - - -
d2cfad96 by Fendor at 2020-10-01T18:35:33-04:00
Add mainModuleNameIs and demote mainModIs

Add `mainModuleNameIs` to DynFlags and demote
`mainModIs` to function which uses the homeUnit from DynFlags
it is created from.

- - - - -
fc351ab8 by Fendor at 2020-10-01T18:35:33-04:00
Use HomeUnit for main module without module declaration

- - - - -
dca1cb22 by Fendor at 2020-10-01T18:35:33-04:00
Remove mAIN completely

- - - - -
a5aaceec by Sylvain Henry at 2020-10-01T18:36:11-04:00
Use ADTs for parser errors/warnings

Haskell and Cmm parsers/lexers now report errors and warnings using ADTs
defined in GHC.Parser.Errors. They can be printed using functions in
GHC.Parser.Errors.Ppr.

Some of the errors provide hints with a separate ADT (e.g. to suggest to
turn on some extension). For now, however, hints are not consistent
across all messages. For example some errors contain the hints in the
main message. I didn't want to change any message with this patch. I
expect these changes to be discussed and implemented later.

Surprisingly, this patch enhances performance. On CI
(x86_64/deb9/hadrian, ghc/alloc):

   parsing001         -11.5%
   T13719             -2.7%
   MultiLayerModules  -3.5%
   Naperian           -3.1%

Bump haddock submodule

Metric Decrease:
    MultiLayerModules
    Naperian
    T13719
    parsing001

- - - - -
a946c7ef by Sylvain Henry at 2020-10-01T18:36:11-04:00
Less DynFlags in Header parsing

- - - - -
dafe7943 by Sylvain Henry at 2020-10-01T18:36:11-04:00
Parser: remove some unused imports

These are not reported by GHC because Happy adds {-# OPTIONS_GHC -w #-}

- - - - -
93d5de16 by Sylvain Henry at 2020-10-01T18:36:11-04:00
Don't import GHC.Unit to reduce the number of dependencies

- - - - -
e3655f81 by Sebastian Graf at 2020-10-01T18:36:47-04:00
Don't attach CPR signatures to NOINLINE data structures (#18154)

Because the generated `KindRep`s don't have an unfolding, !3230 did not
actually stop to compute, attach and serialise unnecessary CPR
signatures for them. As already said in
`Note [CPR for data structures]`, that leads to bloated interface
files which is ultimately quadratic for Nested CPR.

So we don't attach any CPR signature to bindings that

  * Are not thunks (because thunks are not in WHNF)
  * Have arity 0 (which means the top-level constructor is not a lambda)

If the data structure has an unfolding, we continue to look through it.
If not (as is the case for `KindRep`s), we look at the unchanged CPR
signature and see `topCprType`, as expected.

- - - - -
ba5965eb by Richard Eisenberg at 2020-10-01T18:37:23-04:00
Add regression test for #18755.

Close #18755

- - - - -
a8018c17 by Vladislav Zavialov at 2020-10-01T18:37:58-04:00
Fix pretty-printing of the mult-polymorphic arrow

A follow-up to !4020 (5830a12c46e7227c276a8a71213057595ee4fc04)

- - - - -
e5523324 by Sylvain Henry at 2020-10-01T18:38:35-04:00
Bignum: add integerNegate RULE

- - - - -
1edd6d21 by Vladislav Zavialov at 2020-10-01T18:39:10-04:00
Refactor: remove rnHsDoc

It did not do any useful work.

- - - - -
a9ae83af by Krzysztof Gogolewski at 2020-10-02T08:00:25-04:00
Fix typos in comments

[skip ci]

- - - - -
b81350bb by Icelandjack at 2020-10-02T08:01:01-04:00
Replaced MkT1 with T1 in type signatures.
- - - - -
3c9beab7 by Vladislav Zavialov at 2020-10-02T13:51:58-04:00
Minor TTG clean-up: comments, unused families, bottom

1. Fix and update section headers in GHC/Hs/Extension.hs
2. Delete the unused 'XCoreAnn' and 'XTickPragma' families
3. Avoid calls to 'panic' in 'pprStmt'

- - - - -
12c06927 by Sylvain Henry at 2020-10-02T13:52:38-04:00
Bignum: implement integerRecipMod (#18427)

- - - - -
8dd4f405 by Sylvain Henry at 2020-10-02T13:52:38-04:00
Bignum: implement integerPowMod (#18427)

Incidentally fix powModInteger which was crashing in integer-gmp for
negative exponents when the modular multiplicative inverse for the base
didn't exist. Now we compute it explicitly with integerRecipMod so that
every backend returns the same result without crashing.

- - - - -
1033a720 by Krzysztof Gogolewski at 2020-10-02T13:53:23-04:00
Reject linearity in kinds in checkValidType (#18780)

Patch taken from https://gitlab.haskell.org/ghc/ghc/-/issues/18624#note_300673

- - - - -
b0ccba66 by Krzysztof Gogolewski at 2020-10-03T19:33:02-04:00
Small documentation fixes

- Fix formatting of code blocks and a few sphinx warnings
- Move the Void# change to 9.2, it was done right after the branch was cut
- Fix typo in linear types documentation
- Note that -Wincomplete-uni-patterns affects lazy patterns

[skip ci]

- - - - -
70dc2f09 by Karel Gardas at 2020-10-03T19:33:06-04:00
fix rts.cabal to use real arch names and not aliasses (fixes #18654)

- - - - -
bc5de347 by Sebastian Graf at 2020-10-05T13:59:24-04:00
Inline `integerDecodeDouble#` and constant-fold `decodeDouble_Int64#` instead

Currently, `integerDecodeDouble#` is known-key so that it can be
recognised in constant folding. But that is very brittle and doesn't
survive worker/wrapper, which we even do for
`NOINLINE` things since #13143.
Also it is a trade-off: The implementation of `integerDecodeDouble#`
allocates an `Integer` box that never cancels aways if we don't inline
it.

Hence we recognise the `decodeDouble_Int64#` primop instead in constant
folding, so that we can inline `integerDecodeDouble#`. As a result,
`integerDecodeDouble#` no longer needs to be known-key.

While doing so, I realised that we don't constant-fold
`decodeFloat_Int#` either, so I also added a RULE for it.

`integerDecodeDouble` is dead, so I deleted it.

Part of #18092. This improves the 32-bit `realToFrac`/`toRational`:

Metric Decrease:
    T10359

- - - - -
802b5e6f by Krzysztof Gogolewski at 2020-10-05T13:59:33-04:00
Fix linear types in TH splices (#18465)

- - - - -
18a3ddf7 by Ben Gamari at 2020-10-05T13:59:33-04:00
rts: Fix integer width in TICK_BUMP_BY

Previously `TICK_BUMP_BY` was defined as

```c
 #define TICK_BUMP_BY(ctr,n) CLong[ctr] = CLong[ctr] + n
```

Yet the tickers themselves were defined as `StgInt`s. This happened to
work out correctly on Linux, where `CLong` is 64-bits. However, it
failed on Windows, where `CLong` is 32-bits, resulting in #18782.

Fixes #18783.

- - - - -
5fc4243b by Rachel at 2020-10-07T14:59:45-04:00
Document profiling flags, warning flags, and no-pie

- - - - -
b41f7c38 by Andreas Klebinger at 2020-10-07T15:00:20-04:00
WinIO: Small changes related to atomic request swaps.

Move the atomix exchange over the Ptr type to an internal module.

Fix a bug caused by us passing ptr-to-ptr instead of ptr to
atomic exchange.

Renamed interlockedExchange to exchangePtr.

I've also added an cas primitive. It turned out we don't need it
for WinIO but I'm leaving it in as it's useful for other things.

- - - - -
948a14e1 by Ben Gamari at 2020-10-07T15:00:55-04:00
gitlab-ci: Fix name of Ubuntu 20.04 image
- - - - -
74d4017b by Sylvain Henry at 2020-10-07T15:01:35-04:00
Fix -flink-rts (#18651)

Before this patch -flink-rts could link with GHC's rts instead of the
selected one.

- - - - -
0e8b923d by Sylvain Henry at 2020-10-07T15:01:35-04:00
Apply suggestion to compiler/GHC/SysTools.hs
- - - - -
d6dff830 by Alan Zimmerman at 2020-10-07T15:02:10-04:00
Preserve as-parsed arrow type for HsUnrestrictedArrow

When linear types are disabled, HsUnrestrictedArrow is treated as
HslinearArrow.

Move this adjustment into the type checking phase, so that the parsed
source accurately represents the source as parsed.

Closes #18791

- - - - -
030c5ce0 by Karel Gardas at 2020-10-07T15:02:48-04:00
hadrian: use stage0 linker to merge objects when done during the stage0

Fixes #18800.

- - - - -
a94db588 by Ben Gamari at 2020-10-07T15:03:23-04:00
testsuite: Allow whitespace before "Metric (in|de)crease"

Several people have struggled with metric change annotations
in their commit messages not being recognized due to the fact that
GitLab's job log inserts a space at the beginning of each line. Teach
the regular expression to accept this whitespace.

- - - - -
e91ddddd by Krzysztof Gogolewski at 2020-10-07T15:04:07-04:00
Misc cleanup

* Include funTyCon in exposedPrimTyCons.
  Every single place using exposedPrimTyCons was adding funTyCon
  manually.
* Remove unused synTyConResKind and ieLWrappedName
* Add recordSelectorTyCon_maybe
* In exprType, panic instead of giving a trace message and dummy output.
  This prevents #18767 reoccurring.
* Fix compilation error in fragile concprog001 test (part of #18732)

- - - - -
386c2d7f by Sylvain Henry at 2020-10-09T08:40:33-04:00
Use UnitId in the backend instead of Unit

In Cmm we can only have real units identified with an UnitId.  Other
units (on-the-fly instantiated units and holes) are only used in
type-checking backpack sessions that don't produce Cmm.

- - - - -
a566c83d by Simon Jakobi at 2020-10-09T08:41:09-04:00
Update containers to v0.6.4.1

Updates containers submodule.

- - - - -
fd984d68 by Tamar Christina at 2020-10-09T08:41:50-04:00
rts: fix race condition in StgCRun

On windows the stack has to be allocated 4k at a time, otherwise we get
a segfault. This is done by using a helper ___chkstk_ms that is provided
by libgcc. The Haskell side already knows how to handle this but we need
to do the same from STG. Previously we would drop the stack in StgRun
but would only make it valid whenever the scheduler loop ran.

This approach was fundamentally broken in that it falls apart when you
take a signal from the OS. We see it less often because you initially
get allocated a 1MB stack block which you have to blow past first.

Concretely this means we must always keep the stack valid.

Fixes #18601.

- - - - -
accdb24a by Sylvain Henry at 2020-10-09T08:42:31-04:00
Expose RTS-only ways (#18651)

Some RTS ways are exposed via settings (ghcThreaded, ghcDebugged) but
not all. It's simpler if the RTS exposes them all itself.

- - - - -
d360f343 by MaxGabriel at 2020-10-09T08:43:11-04:00
Document -Wderiving-typeable

Tracking: #18641

- - - - -
e48cab2a by Krzysztof Gogolewski at 2020-10-09T08:43:49-04:00
Add a flag to indicate that gcc supports -no-pie

Fixes #17919.

- - - - -
f7e2fff9 by Hécate at 2020-10-09T08:44:26-04:00
Add linting of `base` to the CI

- - - - -
45a1d493 by Andreas Klebinger at 2020-10-09T08:45:05-04:00
Use proper RTS flags when collecting residency in perf tests.

Replace options like collect_stats(['peak_megabytes_allocated'],4) with
collect_runtime_residency(4) and so forth. Reason being that the later
also supplies some default RTS arguments which make sure residency does
not fluctuate too much.

The new flags mean we get new (hopefully more accurate) baselines so
accept the stat changes.

-------------------------
Metric Decrease:
     T4029
     T4334
     T7850
Metric Increase:
     T13218
     T7436
-------------------------

- - - - -
ef65b154 by Andreas Klebinger at 2020-10-09T08:45:42-04:00
testsuite/timeout: Fix windows specific errors.

We now seem to use -Werror there. Which caused some long standing
warnings to become errors.

I applied changes to remove the warnings allowing the testsuite to
run on windows as well.

- - - - -
e691a5a0 by Sylvain Henry at 2020-10-09T08:46:22-04:00
Hadrian: add quick-debug flavour

- - - - -
12191a99 by Sylvain Henry at 2020-10-09T08:47:00-04:00
Bignum: match on small Integer/Natural

Previously we only matched on *variables* whose unfoldings were a ConApp
of the form `IS lit#` or `NS lit##`. But we forgot to match on the
ConApp directly... As a consequence, constant folding only worked after
the FloatOut pass which creates bindings for most sub-expressions. With
this patch, matching on bignums works even with -O0 (see bignumMatch
test).

- - - - -
36787bba by Alan Zimmerman at 2020-10-09T08:47:36-04:00
ApiAnnotations : preserve parens in GADTs

A cleanup in 7f418acf61e accidentally discarded some parens in
ConDeclGADT.

Make sure these stay in the AST in a usable format.

Also ensure the AnnLolly does not get lost in a GADT.

- - - - -
32dc7698 by Krzysztof Gogolewski at 2020-10-09T08:48:15-04:00
Linear types: fix roles in GADTs (#18799)

- - - - -
9657f6f3 by Ben Gamari at 2020-10-09T08:48:52-04:00
sdist: Include hadrian sources in source distribution

Previously the make build system's source distribution rules neglected
to include Hadrian's sources.

Fixes #18794.

- - - - -
c832f7e2 by Tamar Christina at 2020-10-09T08:49:33-04:00
winio: fixed timeouts non-threaded.

- - - - -
6f0243ae by Tamar Christina at 2020-10-09T08:50:13-04:00
winio: fix array splat

- - - - -
0fd3d360 by Tamar Christina at 2020-10-09T08:50:51-04:00
winio: fixed bytestring reading interface.

- - - - -
dfaef1ca by Tamar Christina at 2020-10-09T08:51:30-04:00
winio: fixed more data error.

- - - - -
bfdccac6 by Simon Peyton Jones at 2020-10-09T08:52:07-04:00
Fix desugaring of record updates on data families

This fixes a long-standing bug in the desugaring of record
updates for data families, when the latter involves a GADT. It's
all explained in Note [Update for GADTs] in GHC.HsToCore.Expr.

Building the correct cast is surprisingly tricky, as that Note
explains.

Fixes #18809.  The test case (in indexed-types/should_compile/T18809)
contains several examples that exercise the dark corners.

- - - - -
e5c7c9c8 by Ben Gamari at 2020-10-09T08:52:43-04:00
Bump win32-tarballs version to 0.3

This should fix #18774.

- - - - -
ef950b19 by Andreas Klebinger at 2020-10-09T08:53:21-04:00
Add TyCon Set/Env and use them in a few places.

Firstly this improves code clarity.

But it also has performance benefits as we no longer
go through the name of the TyCon to get at it's unique.

In order to make this work the recursion check for TyCon
has been moved into it's own module in order to avoid import
cycles.

- - - - -
fd302e93 by Krzysztof Gogolewski at 2020-10-09T08:54:02-04:00
Add -pgmlm and -optlm flags

!3798 added documentation and semantics for the flags,
but not parsing.

- - - - -
db236ffc by Sylvain Henry at 2020-10-09T08:54:41-04:00
Testsuite: increase timeout for T18223 (#18795)

- - - - -
6a243e9d by Sylvain Henry at 2020-10-09T08:55:21-04:00
Cache HomeUnit in HscEnv (#17957)

Instead of recreating the HomeUnit from the DynFlags every time we need
it, we store it in the HscEnv.

- - - - -
5884fd32 by Fendor at 2020-10-09T19:46:28+02:00
Move File Target parser to library #18596

- - - - -
ea59fd4d by Hécate at 2020-10-10T14:49:59-04:00
Lint the compiler for extraneous LANGUAGE pragmas

- - - - -
22f218b7 by Krzysztof Gogolewski at 2020-10-10T14:50:42-04:00
Linear types: fix quantification in GADTs (#18790)

- - - - -
74ee1237 by Sylvain Henry at 2020-10-10T14:51:20-04:00
Bignum: fix bigNatCompareWord# bug (#18813)

- - - - -
274e21f0 by Hécate at 2020-10-11T10:55:56+02:00
Remove the dependency on the ghc-linters stage

- - - - -
990ea991 by Daniel Rogozin at 2020-10-11T22:20:04+03:00
Fall back to types when looking up data constructors (#18740)

Before this patch, referring to a data constructor in a term-level
context led to a scoping error:

    ghci> id Int
    <interactive>:1:4: error: Data constructor not in scope: Int

After this patch, the renamer falls back to the type namespace
and successfully finds the Int. It is then rejected in the type
checker with a more useful error message:

    <interactive>:1:4: error:
    • Illegal term-level use of the type constructor ‘Int’
        imported from ‘Prelude’ (and originally defined in ‘GHC.Types’)
    • In the first argument of ‘id’, namely ‘Int’
      In the expression: id Int

We also do this for type variables.

- - - - -
9bbc84d2 by Sylvain Henry at 2020-10-12T18:21:51-04:00
DynFlags: refactor DmdAnal

Make demand analysis usable without having to provide DynFlags.

- - - - -
7fdcce6d by Wander Hillen at 2020-10-13T00:12:47-04:00
Initial ShortText code and conversion of package db code

Metric Decrease:
    Naperian
    T10421
    T10421a
    T10547
    T12150
    T12234
    T12425
    T13035
    T18140
    T18304
    T5837
    T6048
    T13253-spj
    T18282
    T18223
    T3064
    T9961
Metric Increase
    T13701

HFSKJH

- - - - -
0a5f2918 by Sylvain Henry at 2020-10-13T00:13:28-04:00
Parser: don't require the HomeUnitId

The HomeUnitId is only used by the Cmm parser and this one has access to
the DynFlags, so it can grab the UnitId of the HomeUnit from them.

Bump haddock submodule

- - - - -
8f4f5794 by HaskellMouse at 2020-10-13T13:05:49+03:00
Unification of Nat and Naturals

This commit removes the separate kind 'Nat' and enables promotion
of type 'Natural' for using as type literal.
It partially solves #10776

Now the following code will be successfully typechecked:
    data C = MkC Natural
    type CC = MkC 1

Before this change we had to create the separate type for promotion
    data C = MkC Natural
    data CP = MkCP Nat
    type CC = MkCP 1

But CP is uninhabited in terms.

For backward compatibility type synonym `Nat` has been made:
    type Nat = Natural

The user's documentation and tests have been updated.
The haddock submodule also have been updated.

- - - - -
0fc1cb54 by Ben Gamari at 2020-10-14T03:42:50-04:00
gitlab-ci: Verify that Hadrian builds with Stack

As noted in #18726, this regularly breaks. Let's test it.

Note that we don't actually perform a build of GHC itself; we merely
test that the Hadrian executable builds and works (by invoking `hadrian
--version`).

- - - - -
89f4d8e9 by Ben Gamari at 2020-10-14T12:03:57-04:00
Bump LLVM version to 10.0

Fixes #18267.

- - - - -
716385c9 by Ryan Scott at 2020-10-14T12:04:34-04:00
Make DataKinds the sole arbiter of kind-level literals (and friends)

Previously, the use of kind-level literals, promoted tuples,
and promoted lists required enabling both `DataKinds` and
`PolyKinds`. This made sense back in a `TypeInType` world, but not so
much now that `TypeInType`'s role has been superseded. Nowadays,
`PolyKinds` only controls kind polymorphism, so let's make `DataKinds`
the thing that controls the other aspects of `TypeInType`, which include
literals, promoted tuples and promoted lists.

There are some other things that overzealously required `PolyKinds`,
which this patch fixes as well:

* Previously, using constraints in kinds (e.g., `data T :: () -> Type`)
  required `PolyKinds`, despite the fact that this is orthogonal to kind
  polymorphism. This now requires `DataKinds` instead.
* Previously, using kind annotations in kinds
  (e.g., `data T :: (Type :: Type) -> Type`) required both `KindSignatures`
  and `PolyKinds`. This doesn't make much sense, so it only requires
  `KindSignatures` now.

Fixes #18831.

- - - - -
ac300a0d by Vladislav Zavialov at 2020-10-14T12:05:11-04:00
Remove "Operator sections" from docs/users_guide/bugs.rst

The issue described in that section was fixed by
2b89ca5b850b4097447cc4908cbb0631011ce979

- - - - -
bf2411a3 by Vladislav Zavialov at 2020-10-14T12:05:11-04:00
Fix PostfixOperators (#18151)

This fixes a regression introduced in 2b89ca5b850b4097447cc4908cbb0631011ce979
See the new T18151x test case.

- - - - -
e60ae8a3 by Fumiaki Kinoshita at 2020-10-14T18:06:12-04:00
Add -Wnoncanonical-{monad,monoid}-instances to standardWarnings

-------------------------
Metric Decrease:
   T12425
Metric Increase:
   T17516
-------------------------

- - - - -
15d2340c by Simon Peyton Jones at 2020-10-14T18:06:48-04:00
Fix some missed opportunities for preInlineUnconditionally

There are two signficant changes here:

* Ticket #18815 showed that we were missing some opportunities for
  preInlineUnconditionally.  The one-line fix is in the code for
  GHC.Core.Opt.Simplify.Utils.preInlineUnconditionally, which now
  switches off only for INLINE pragmas.  I expanded
  Note [Stable unfoldings and preInlineUnconditionally] to explain.

* When doing this I discovered a way in which preInlineUnconditionally
  was occasionally /too/ eager.  It's all explained in
  Note [Occurrences in stable unfoldings] in GHC.Core.Opt.OccurAnal,
  and the one-line change adding markAllMany to occAnalUnfolding.

I also got confused about what NoUserInline meant, so I've renamed
it to NoUserInlinePrag, and changed its pretty-printing slightly.
That led to soem error messate wibbling, and touches quite a few
files, but there is no change in functionality.

I did a nofib run.  As expected, no significant changes.

        Program           Size    Allocs
----------------------------------------
         sphere          -0.0%     -0.4%
----------------------------------------
            Min          -0.0%     -0.4%
            Max          -0.0%     +0.0%
 Geometric Mean          -0.0%     -0.0%

I'm allowing a max-residency increase for T10370, which seems
very irreproducible. (See comments on !4241.)  There is always
sampling error for max-residency measurements; and in any case
the change shows up on some platforms but not others.

Metric Increase:
    T10370

- - - - -
0c4bfed8 by Ben Gamari at 2020-10-14T18:07:25-04:00
users-guide: Add missing :ghc-flag: directive
- - - - -
51c4b851 by Krzysztof Gogolewski at 2020-10-15T04:30:27-04:00
Remove Proxy# argument in Data.Typeable.Internal

No longer neccessary - TypeRep is now indexed, there is no ambiguity.

Also fix a comment in Evidence.hs, IsLabel no longer takes a Proxy#.

- - - - -
809f09e8 by Sylvain Henry at 2020-10-15T04:31:07-04:00
Fix parsing of PIE flags

-fPIE and -fno-PIE flags were (un)setting Opt_PIC instead of Opt_PIE.

Original commit: 3625728a0e3a9b56c2b85ae7ea8bcabdd83ece6a

- - - - -
3d7db148 by Ben Gamari at 2020-10-15T04:31:42-04:00
testsuite: Add missing #include on <stdlib.h>

This otherwise fails on newer Clangs, which warn
more aggressively on undeclared symbols.
- - - - -
998803dc by Andrzej Rybczak at 2020-10-15T11:40:32+02:00
Add flags for annotating Generic{,1} methods INLINE[1] (#11068)

Makes it possible for GHC to optimize away intermediate Generic representation
for more types.

Metric Increase:
    T12227

- - - - -
6b14c418 by GHC GitLab CI at 2020-10-15T21:57:50-04:00
Extend mAX_TUPLE_SIZE to 64

As well a ctuples and sums.

- - - - -
d495f36a by Ben Gamari at 2020-10-15T21:58:27-04:00
rts: Clean-up whitespace in Interpreter

- - - - -
cf10becd by Ben Gamari at 2020-10-15T21:58:27-04:00
compiler/ByteCode: Use strict Maps in bytecode assembler

- - - - -
ae146b53 by Ben Gamari at 2020-10-15T21:58:27-04:00
compiler/ByteCode: Make LocalLabel a newtype

- - - - -
cc536288 by Ben Gamari at 2020-10-15T21:58:27-04:00
compiler/ByteCode: Allow 2^32 local labels

This widens LocalLabel to 2^16, avoiding the crash observed in #14334.

Closes #14334.

- - - - -
1bb0512f by Ben Gamari at 2020-10-16T00:15:31-04:00
mingw: Extract zst toolchain archives

This should have been done when the toolchain was bumped.

- - - - -
bf7c5b6d by Ben Gamari at 2020-10-16T00:15:31-04:00
base: Reintroduce necessary LANGUAGE pragmas

These were incorrectly removed in a recent cleanup commit.

- - - - -
c6b4be4b by Ben Gamari at 2020-10-16T00:15:31-04:00
testsuite: Sort metrics by metric type

Closes #18838.

- - - - -
c7989c93 by Ben Gamari at 2020-10-16T00:15:31-04:00
testsuite: Account for -Wnoncanonical-monoid-instances changes on Windows

- - - - -
330a5433 by Ben Gamari at 2020-10-16T00:15:31-04:00
rts: Add __mingw_vfprintf to RtsSymbols.c

Following the model of the other printf symbols. See Note [Symbols for
MinGW's printf].

- - - - -
c4a69f37 by Ben Gamari at 2020-10-16T00:15:31-04:00
gitlab-ci: Remove allow_failure from Windows jobs

- - - - -
9a9679db by Ben Gamari at 2020-10-16T00:15:31-04:00
gitlab-ci: Fix Hadrian bindist names

- - - - -
07b0db86 by f-a at 2020-10-16T10:14:39-04:00
Clarify Eq documentation #18713
- - - - -
aca0e63b by Ben Gamari at 2020-10-17T10:20:31-04:00
gitlab-ci: Allow doc-tarball job to fail

Currently the Hadrian build appears not to package documentation correctly,
causing doc-tarball to fail due to the Windows build.
- - - - -
b02a9ea7 by Ben Gamari at 2020-10-17T13:26:24-04:00
gitlab-ci: s/allow_newer/allow_failure

Silly mistake on my part.
- - - - -
59d7c9f4 by John Ericson at 2020-10-17T22:01:38-04:00
Skip type family defaults with hs-boot and hsig files

Works around #17190, possible resolution for #17224. New design is is
according to accepted [GHC Propoal 320].

Instances in signatures currently unconditionally opt into associated
family defaults if no explicit instance is given. This is bad for two
reasons:

  1. It constrains possible instantiations to use the default, rather
  than possibly define the associated family differently.

  2. It breaks compilation as type families are unsupported in
  signatures.

This PR simply turns off the filling in of defaults in those cases.
Additionally, it squelches a missing definition warning for hs-boot too
that was only squelched for hsig before.

The downsides are:

  1. There is no way to opt into the default, other than copying its
  definition.

  2. If we fixed type classes in signatures, and wanted instances to
  have to explicitly *out of* rather than into the default, that would
  now be a breaking change.

The change that is most unambiguously goood is harmonizing the warning
squelching between hs-boot or hsig. Maybe they should have the warning
(opt out of default) maybe they shouldn't (opt in to default), but
surely it should be the same for both.

Add hs-boot version of a backpack test regarding class-specified
defaults in instances that appear in an hs-boot file.

The metrics increase is very slight and makes no sense --- at least no
one has figured anything out after this languishing for a while, so I'm
just going to accept it.

Metric Increase:
  T10421a

[GHC proposal 320]: https://github.com/ghc-proposals/ghc-proposals/pull/320

- - - - -
7eb46a09 by Sebastian Graf at 2020-10-17T22:02:13-04:00
Arity: Refactor fixed-point iteration in GHC.Core.Opt.Arity

Arity analysis used to propagate optimistic arity types during
fixed-point interation through the `ArityEnv`'s `ae_cheap_fun` field,
which is like `GHC.Core.Utils.exprIsCheap`, but also considers the
current iteration's optimistic arity, for the binder in question only.

In #18793, we have seen that this is a problematic design, because it
doesn't allow us to look through PAP bindings of that binder.

Hence this patch refactors to a more traditional form with an explicit
signature environment, in which we record the optimistic `ArityType` of
the binder in question (and at the moment is the *only* binder that is
recorded in the arity environment).

- - - - -
6b3eb06a by Sebastian Graf at 2020-10-17T22:02:13-04:00
Arity: Record arity types for non-recursive lets

In #18793, we saw a compelling example which requires us to look at
non-recursive let-bindings during arity analysis and unleash their arity
types at use sites.

After the refactoring in the previous patch, the needed change is quite
simple and very local to `arityType`'s defn for non-recurisve `Let`.

Apart from that, we had to get rid of the second item of
`Note [Dealing with bottoms]`, which was entirely a safety measure and
hindered optimistic fixed-point iteration.

Fixes #18793.

The following metric increases are all caused by this commit and a
result of the fact that we just do more work now:

Metric Increase:
    T3294
    T12545
    T12707

- - - - -
451455fd by Sebastian Graf at 2020-10-17T22:02:13-04:00
Testsuite: Add dead arity analysis tests

We didn't seem to test these old tests at all, judging from their
expected output.

- - - - -
50e9df49 by Dylan Yudaken at 2020-10-17T22:02:50-04:00
When using rts_setInCallCapability, lock incall threads

This diff makes sure that incall threads, when using `rts_setInCallCapability`, will be created as locked.
If the thread is not locked, the thread might end up being scheduled to a different capability.
While this is mentioned in the docs for `rts_setInCallCapability,`, it makes the method significantly less useful as there is no guarantees on the capability being used.

This commit also adds a test to make sure things stay on the correct capability.

- - - - -
0b995759 by DylanZA at 2020-10-17T22:02:50-04:00
Apply suggestion to testsuite/tests/ffi/should_run/all.T
- - - - -
a91dcb66 by Sylvain Henry at 2020-10-17T22:04:02-04:00
Don't get host RTS ways via settings (#18651)

To correctly perform a linking hack for Windows we need to link with the
RTS GHC is currently using. We used to query the RTS ways via the
"settings" file but it is fragile (#18651). The hack hasn't been fixed
to take into account all the ways (Tracing) and it makes linking of GHC
with another RTS more difficult (we need to link with another RTS and to
regenerate the settings file).

So this patch uses the ways reported by the RTS itself
(GHC.Platform.Ways.hostWays) instead of the "settings" file.

- - - - -
d858a3ae by Hécate at 2020-10-17T22:04:38-04:00
Linting corrections

* Bring back LANGUAGE pragmas in GHC.IO.Handle.Lock.Windows
* Exclude some modules that are wrongfully reported

- - - - -
b5b3e34e by Vladislav Zavialov at 2020-10-19T18:16:20-04:00
Implement -Woperator-whitespace (#18834)

This patch implements two related warnings:

  -Woperator-whitespace-ext-conflict
      warns on uses of infix operators that would be parsed
      differently were a particular GHC extension enabled

  -Woperator-whitespace
      warns on prefix, suffix, and tight infix uses of infix
      operators

Updates submodules: haddock, containers.

- - - - -
9648d680 by Sylvain Henry at 2020-10-19T18:16:58-04:00
Remove pdocPrec

pdocPrec was only used in GHC.Cmm.DebugBlock.pprUnwindExpr, so remove
it. OutputableP becomes a one-function class which might be better for
performance.

- - - - -
ee5dcdf9 by Ben Gamari at 2020-10-20T00:47:54-04:00
testsuite: Add test for #18346

This was fixed by 4291bddaea3148908c55f235ee8978e1d9aa6f20.

- - - - -
6c7a5c0c by Krzysztof Gogolewski at 2020-10-20T00:48:29-04:00
Minor comments, update linear types docs

- Update comments: placeHolderTypeTc no longer exists
  "another level check problem" was a temporary comment from linear types
- Use Mult type synonym (reported in #18676)
- Mention multiplicity-polymorphic fields in linear types docs

- - - - -
58a1ca38 by nineonine at 2020-10-20T00:49:07-04:00
Compile modules with `-fobject-code` enabled to byte-code when loaded with `*` prefix in ghci (#8042)

The documentation states that when using :add and :load, the `*` prefix forces a module
to be loaded as byte-code. However, this seems to be ignored when -fobject-code has been
enabled. In that case, the compiled code is always used, regardless of whether the *-form
is used.

The idea is to consult the Targets in HscEnv and check the 'targetAllowObjCode' flag. If
the flag for given module is set, then patch up DynFlags and select compilation backend
accordingly.

This would require a linear scan of course, but that shouldn't be too costly.

- - - - -
59b08a5d by Ben Gamari at 2020-10-20T00:49:41-04:00
gitlab-ci: Rename FLAVOUR -> BUILD_FLAVOUR

Previously the Hadrian jobs used the `FLAVOUR` environment variable to
communicate which flavour `ci.sh` should build whereas `make` used
`BUILD_FLAVOUR`. This caused unnecessary confusion. Consolidate these
two.

- - - - -
ea736839 by Alan Zimmerman at 2020-10-20T08:35:34+01:00
API Annotations: Keep track of unicode for linear arrow notation

The linear arrow can be parsed as `%1 ->` or a direct single token unicode
equivalent.

Make sure that this distinction is captured in the parsed AST by using
IsUnicodeSyntax where it appears, and introduce a new API Annotation,
AnnMult to represent its location when unicode is not used.

Updated haddock submodule

- - - - -
cf3c3bcd by Ben Gamari at 2020-10-20T22:56:31-04:00
testsuite: Mark T12971 as fragile on Windows

Due to #17945.

- - - - -
b9d4dd9c by Ben Gamari at 2020-10-24T20:44:17-04:00
SMP.h: Add C11-style atomic operations

- - - - -
ccf2d4b0 by Ben Gamari at 2020-10-24T20:59:39-04:00
rts: Infrastructure for testing with ThreadSanitizer

- - - - -
a61f66d6 by Ben Gamari at 2020-10-24T20:59:39-04:00
rts/CNF: Initialize all bdescrs in group

It seems wise and cheap to ensure that the whole bdescr of all blocks of
a compact group is valid, even if most cases only look at the flags
field.

- - - - -
65136c13 by Ben Gamari at 2020-10-24T20:59:39-04:00
rts/Capability: Intialize interrupt field

Previously this was left uninitialized.

Also clarify some comments.

- - - - -
b3ce6aca by Ben Gamari at 2020-10-24T20:59:39-04:00
rts/Task: Make comments proper Notes

- - - - -
d3890ac7 by Ben Gamari at 2020-10-24T20:59:39-04:00
rts/SpinLock: Move to proper atomics

This is fairly straightforward; we just needed to use relaxed operations
for the PROF_SPIN counters and a release store instead of a write
barrier.

- - - - -
ef88712f by Ben Gamari at 2020-10-24T20:59:39-04:00
rts/OSThreads: Fix data race

Previously we would race on the cached processor count. Avoiding this is
straightforward; just use relaxed operations.

- - - - -
33a719c3 by Ben Gamari at 2020-10-24T20:59:39-04:00
rts/ClosureMaros: Use relaxed atomics

- - - - -
f08951fd by Ben Gamari at 2020-10-24T20:59:39-04:00
configure: Bump minimum-supported gcc version to 4.7

Since the __atomic_* builtins are not supported until gcc 4.7. Given
that this version was released in 2012 I think this is acceptable.

- - - - -
d584923a by Ben Gamari at 2020-10-24T20:59:39-04:00
testsuite: Fix thread leak in hs_try_putmvar00[13]

- - - - -
bf1b0bc7 by Ben Gamari at 2020-10-24T20:59:39-04:00
rts: Introduce SET_HDR_RELEASE

Also ensure that we also store the info table pointer last to ensure
that the synchronization covers all stores.

- - - - -
1a2e9f5e by Ben Gamari at 2020-10-24T21:00:19-04:00
gitlab-ci: Add nightly-x86_64-linux-deb9-tsan job

- - - - -
58a5b0e5 by GHC GitLab CI at 2020-10-24T21:00:19-04:00
testsuite: Mark setnumcapabilities001 as broken with TSAN

Due to #18808.

- - - - -
d9bc7dea by GHC GitLab CI at 2020-10-24T21:00:19-04:00
testsuite: Skip divbyzero and derefnull under TSAN

ThreadSanitizer changes the output of these tests.

- - - - -
fcc42a10 by Ben Gamari at 2020-10-24T21:00:19-04:00
testsuite: Skip high memory usage tests with TSAN

ThreadSanitizer significantly increases the memory footprint of tests,
so much so that it can send machines into OOM.

- - - - -
cae4bb3e by Ben Gamari at 2020-10-24T21:00:19-04:00
testsuite: Mark hie002 as high_memory_usage

This test has a peak residency of 1GByte; this is large enough to
classify as "high" in my book.

- - - - -
dae1b86a by Ben Gamari at 2020-10-24T21:00:19-04:00
testsuite: Mark T9872[abc] as high_memory_usage

These all have a maximum residency of over 2 GB.

- - - - -
c5a0bb22 by Ben Gamari at 2020-10-24T21:00:19-04:00
gitlab-ci: Disable documentation in TSAN build

Haddock chews through enough memory to cause the CI builders to OOM and
there's frankly no reason to build documentation in this job anyways.

- - - - -
4cb1232e by Ben Gamari at 2020-10-24T21:00:19-04:00
TSANUtils: Ensure that C11 atomics are supported

- - - - -
7ed15f7f by Ben Gamari at 2020-10-24T21:00:19-04:00
testsuite: Mark T3807 as broken with TSAN

Due to #18883.

- - - - -
f7e6f012 by Ben Gamari at 2020-10-24T21:00:19-04:00
testsuite: Mark T13702 as broken with TSAN due to #18884

- - - - -
16b136b0 by Ben Gamari at 2020-10-24T21:00:36-04:00
rts: Factor out logic to identify a good capability for running a task

Not only does this make the control flow a bit clearer but it also
allows us to add a TSAN suppression on this logic, which requires
(harmless) data races.

- - - - -
2781d68c by Ben Gamari at 2020-10-24T21:00:36-04:00
rts: Annotate benign race in waitForCapability

- - - - -
f6b4b492 by Ben Gamari at 2020-10-24T21:00:36-04:00
rts: Clarify locking behavior of releaseCapability_

- - - - -
65219810 by Ben Gamari at 2020-10-24T21:00:36-04:00
rts: Add assertions for task ownership of capabilities

- - - - -
31fa87ec by Ben Gamari at 2020-10-24T21:00:36-04:00
rts: Use relaxed atomics on n_returning_tasks

This mitigates the warning of a benign race on n_returning_tasks in
shouldYieldCapability.

See #17261.

- - - - -
6517a2ea by Ben Gamari at 2020-10-24T21:00:36-04:00
rts: Mitigate races in capability interruption logic

- - - - -
2e9ba3f2 by Ben Gamari at 2020-10-24T21:00:36-04:00
rts/Capability: Use relaxed operations for last_free_capability

- - - - -
e10dde37 by Ben Gamari at 2020-10-24T21:00:37-04:00
rts: Use relaxed operations for cap->running_task (TODO)

This shouldn't be necessary since only the owning thread of the capability
should be touching this.

- - - - -
855325cd by Ben Gamari at 2020-10-24T21:00:37-04:00
rts/Schedule: Use relaxed operations for sched_state

- - - - -
811f915d by Ben Gamari at 2020-10-24T21:00:37-04:00
rts: Accept data race in work-stealing implementation

This race is okay since the task is owned by the capability pushing it.
By Note [Ownership of Task] this means that the capability is free to
write to `task->cap` without taking `task->lock`.

Fixes #17276.

- - - - -
8d2b3c3d by Ben Gamari at 2020-10-24T21:00:37-04:00
rts: Eliminate data races on pending_sync

- - - - -
f8871018 by Ben Gamari at 2020-10-24T21:00:37-04:00
rts/Schedule: Eliminate data races on recent_activity

We cannot safely use relaxed atomics here.

- - - - -
d079b943 by Ben Gamari at 2020-10-24T21:00:37-04:00
rts: Avoid data races in message handling

- - - - -
06f80497 by Ben Gamari at 2020-10-24T21:00:37-04:00
rts/Messages: Drop incredibly fishy write barrier

executeMessage previously had a write barrier at the beginning of its
loop apparently in an attempt to synchronize with another thread's
writes to the Message. I would guess that the author had intended to use
a load barrier here given that there are no globally-visible writes done
in executeMessage.

I've removed the redundant barrier since the necessary load barrier is
now provided by the ACQUIRE_LOAD.

- - - - -
d4a87779 by Ben Gamari at 2020-10-24T21:00:38-04:00
rts/ThreadPaused: Avoid data races

- - - - -
56778ab3 by Ben Gamari at 2020-10-24T21:00:38-04:00
rts/Schedule: Eliminate data races in run queue management

- - - - -
086521f7 by Ben Gamari at 2020-10-24T21:00:38-04:00
rts: Eliminate shutdown data race on task counters

- - - - -
abad9778 by Ben Gamari at 2020-10-24T21:00:38-04:00
rts/Threads: Avoid data races (TODO)

Replace barriers with appropriate ordering. Drop redundant barrier in
tryWakeupThread (the RELEASE barrier will be provided by sendMessage's
mutex release).

We use relaxed operations on why_blocked and the stack although it's not
clear to me why this is necessary.

- - - - -
2f56be8a by Ben Gamari at 2020-10-24T21:00:39-04:00
rts/Messages: Annotate benign race

- - - - -
7c0cdab1 by Ben Gamari at 2020-10-24T21:00:39-04:00
rts/RaiseAsync: Synchronize what_next read

- - - - -
6cc2a8a5 by Ben Gamari at 2020-10-24T21:00:39-04:00
rts/Task: Move debugTrace to avoid data race

Specifically, we need to hold all_tasks_mutex to read taskCount.

- - - - -
bbaec97d by Ben Gamari at 2020-10-24T21:00:39-04:00
Disable flawed assertion

- - - - -
dd175a92 by Ben Gamari at 2020-10-24T21:00:39-04:00
Document schedulePushWork race

- - - - -
3416244b by Ben Gamari at 2020-10-24T21:00:40-04:00
Capabiliity: Properly fix data race on n_returning_tasks

There is a real data race but can be made safe by using proper atomic
(but relaxed) accesses.

- - - - -
dffd9432 by Ben Gamari at 2020-10-24T21:00:40-04:00
rts: Make write of to_cap->inbox atomic

This is necessary since emptyInbox may read from to_cap->inbox without
taking cap->lock.

- - - - -
1f4cbc29 by Ben Gamari at 2020-10-24T21:00:57-04:00
rts/BlockAlloc: Use relaxed operations

- - - - -
d0d07cff by Ben Gamari at 2020-10-24T21:00:57-04:00
rts: Rework handling of mutlist scavenging statistics

- - - - -
9e5c7f6d by Ben Gamari at 2020-10-24T21:00:57-04:00
rts: Avoid data races in StablePtr implementation

This fixes two potentially problematic data races in the StablePtr
implementation:

 * We would fail to RELEASE the stable pointer table when enlarging it,
   causing other cores to potentially see uninitialized memory.

 * We would fail to ACQUIRE when dereferencing a stable pointer.

- - - - -
316add67 by Ben Gamari at 2020-10-24T21:00:57-04:00
rts/Storage: Use atomics

- - - - -
5c23bc4c by Ben Gamari at 2020-10-24T21:00:58-04:00
rts/Updates: Use proper atomic operations

- - - - -
3d0f033c by Ben Gamari at 2020-10-24T21:00:58-04:00
rts/Weak: Eliminate data races

By taking all_tasks_mutex in stat_exit. Also better-document the fact
that the task statistics are protected by all_tasks_mutex.

- - - - -
ce2ee5cb by Ben Gamari at 2020-10-24T21:00:58-04:00
rts/GC: Use atomics

- - - - -
e2901e49 by Ben Gamari at 2020-10-24T21:00:58-04:00
rts: Use RELEASE ordering in unlockClosure

- - - - -
463d71d0 by Ben Gamari at 2020-10-24T21:00:58-04:00
rts/Storage: Accept races on heap size counters

- - - - -
ab1c0702 by Ben Gamari at 2020-10-24T21:00:58-04:00
rts: Join to concurrent mark thread during shutdown

Previously we would take all capabilities but fail to join on the thread
itself, potentially resulting in a leaked thread.

- - - - -
98237242 by GHC GitLab CI at 2020-10-24T21:00:58-04:00
rts: Fix race in GC CPU time accounting

Ensure that the GC leader synchronizes with workers before calling
stat_endGC.

- - - - -
edb4b92b by Ben Gamari at 2020-10-24T21:01:18-04:00
rts/WSDeque: Rewrite with proper atomics

After a few attempts at shoring up the previous implementation, I ended
up turning to the literature and now use the proven implementation,

> N.M. Lê, A. Pop, A.Cohen, and F.Z. Nardelli. "Correct and Efficient
> Work-Stealing for Weak Memory Models". PPoPP'13, February 2013,
> ACM 978-1-4503-1922/13/02.

Note only is this approach formally proven correct under C11 semantics
but it is also proved to be a bit faster in practice.

- - - - -
d39bbd3d by Ben Gamari at 2020-10-24T21:01:33-04:00
rts: Use relaxed atomics for whitehole spin stats

- - - - -
8f802f38 by Ben Gamari at 2020-10-24T21:01:33-04:00
rts: Avoid lock order inversion during fork

Fixes #17275.

- - - - -
cef667b0 by GHC GitLab CI at 2020-10-24T21:01:34-04:00
rts: Use proper relaxe operations in getCurrentThreadCPUTime

Here we are doing lazy initialization; it's okay if we do the check more
than once, hence relaxed operation is fine.

- - - - -
8cf50eb1 by Ben Gamari at 2020-10-24T21:01:54-04:00
rts/STM: Use atomics

This fixes a potentially harmful race where we failed to synchronize
before looking at a TVar's current_value.

Also did a bit of refactoring to avoid abstract over management of
max_commits.

- - - - -
88a7ce38 by Ben Gamari at 2020-10-24T21:01:54-04:00
rts/stm: Strengthen orderings to SEQ_CST instead of volatile

Previously the `current_value`, `first_watch_queue_entry`, and
`num_updates` fields of `StgTVar` were marked as `volatile` in an
attempt to provide strong ordering. Of course, this isn't sufficient.

We now use proper atomic operations. In most of these cases I strengthen
the ordering all the way to SEQ_CST although it's possible that some
could be weakened with some thought.

- - - - -
f97c59ce by Ben Gamari at 2020-10-24T21:02:11-04:00
Mitigate data races in event manager startup/shutdown

- - - - -
c7c3f8aa by Ben Gamari at 2020-10-24T21:02:22-04:00
rts: Accept benign races in Proftimer

- - - - -
5a98dfca by Ben Gamari at 2020-10-24T21:02:22-04:00
rts: Pause timer while changing capability count

This avoids #17289.

- - - - -
01d95525 by Ben Gamari at 2020-10-24T21:02:22-04:00
Fix #17289

- - - - -
9a528985 by Ben Gamari at 2020-10-24T21:02:23-04:00
suppress #17289 (ticker) race

- - - - -
1726ec41 by Ben Gamari at 2020-10-24T21:02:23-04:00
rts: Fix timer initialization

Previously `initScheduler` would attempt to pause the ticker and in so
doing acquire the ticker mutex. However, initTicker, which is
responsible for initializing said mutex, hadn't been called
yet.

- - - - -
bfbe4366 by Ben Gamari at 2020-10-24T21:02:23-04:00
rts: Fix races in Pthread timer backend shudown

We can generally be pretty relaxed in the barriers here since the timer
thread is a loop.

- - - - -
297acc71 by Ben Gamari at 2020-10-24T21:02:44-04:00
rts/Stats: Hide a few unused unnecessarily global functions

- - - - -
0cdb34a0 by Ben Gamari at 2020-10-24T21:02:44-04:00
rts/Stats: Protect with mutex

While on face value this seems a bit heavy, I think it's far better than
enforcing ordering on every access.

- - - - -
bacdbe51 by Ben Gamari at 2020-10-24T21:04:43-04:00
rts: Tear down stats_mutex after exitHeapProfiling

Since the latter wants to call getRTSStats.

- - - - -
2b49fcb3 by Ben Gamari at 2020-10-24T21:10:30-04:00
Merge branches 'wip/tsan/sched', 'wip/tsan/ci', 'wip/tsan/storage', 'wip/tsan/wsdeque', 'wip/tsan/misc', 'wip/tsan/stm', 'wip/tsan/event-mgr', 'wip/tsan/timer' and 'wip/tsan/stats' into wip/tsan/all

- - - - -
642f2ed0 by Ben Gamari at 2020-10-24T21:11:14-04:00
testing

- - - - -


30 changed files:

- .gitlab-ci.yml
- .gitlab/ci.sh
- + .gitlab/common.sh
- aclocal.m4
- + compiler/.hlint.yaml
- compiler/GHC.hs
- compiler/GHC/Builtin/Names.hs
- compiler/GHC/Builtin/Names/TH.hs
- compiler/GHC/Builtin/PrimOps.hs
- compiler/GHC/Builtin/Types.hs
- compiler/GHC/Builtin/Types.hs-boot
- compiler/GHC/Builtin/Types/Literals.hs
- compiler/GHC/Builtin/Types/Prim.hs
- compiler/GHC/Builtin/Uniques.hs
- compiler/GHC/Builtin/Utils.hs
- compiler/GHC/Builtin/primops.txt.pp
- compiler/GHC/ByteCode/Asm.hs
- compiler/GHC/ByteCode/InfoTable.hs
- compiler/GHC/ByteCode/Instr.hs
- compiler/GHC/ByteCode/Linker.hs
- compiler/GHC/ByteCode/Types.hs
- compiler/GHC/Cmm.hs
- compiler/GHC/Cmm/CLabel.hs
- compiler/GHC/Cmm/CallConv.hs
- compiler/GHC/Cmm/Dataflow/Collections.hs
- compiler/GHC/Cmm/Dataflow/Label.hs
- compiler/GHC/Cmm/DebugBlock.hs
- compiler/GHC/Cmm/Info/Build.hs
- compiler/GHC/Cmm/LayoutStack.hs
- compiler/GHC/Cmm/Lexer.x


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/52901280e40cb05c3566c857e92caf1296d8d3ee...642f2ed0a68dc40abb9379e5c561c8c37d8ddfc4

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/52901280e40cb05c3566c857e92caf1296d8d3ee...642f2ed0a68dc40abb9379e5c561c8c37d8ddfc4
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/20201024/78391109/attachment-0001.html>


More information about the ghc-commits mailing list