[Git][ghc/ghc][wip/T17917] 51 commits: Make NoExtCon fields strict

Simon Peyton Jones gitlab at gitlab.haskell.org
Mon Apr 20 08:17:35 UTC 2020



Simon Peyton Jones pushed to branch wip/T17917 at Glasgow Haskell Compiler / GHC


Commits:
04b6cf94 by Ryan Scott at 2020-04-07T19:43:20-04:00
Make NoExtCon fields strict

This changes every unused TTG extension constructor to be strict in
its field so that the pattern-match coverage checker is smart enough
any such constructors are unreachable in pattern matches. This lets
us remove nearly every use of `noExtCon` in the GHC API. The only
ones we cannot remove are ones underneath uses of `ghcPass`, but that
is only because GHC 8.8's and 8.10's coverage checkers weren't smart
enough to perform this kind of reasoning. GHC HEAD's coverage
checker, on the other hand, _is_ smart enough, so we guard these uses
of `noExtCon` with CPP for now.

Bumps the `haddock` submodule.

Fixes #17992.

- - - - -
7802fa17 by Ryan Scott at 2020-04-08T16:43:44-04:00
Handle promoted data constructors in typeToLHsType correctly

Instead of using `nlHsTyVar`, which hardcodes `NotPromoted`, have
`typeToLHsType` pick between `Promoted` and `NotPromoted` by checking
if a type constructor is promoted using `isPromotedDataCon`.

Fixes #18020.

- - - - -
ce481361 by Ben Gamari at 2020-04-09T16:17:21-04:00
hadrian: Use --export-dynamic when linking iserv

As noticed in #17962, the make build system currently does this (see
3ce0e0ba) but the change was never ported to Hadrian.

- - - - -
fa66f143 by Ben Gamari at 2020-04-09T16:17:21-04:00
iserv: Don't pass --export-dynamic on FreeBSD

This is definitely a hack but it's probably the best we can do for now.
Hadrian does the right thing here by passing --export-dynamic only to
the linker.

- - - - -
39075176 by Ömer Sinan Ağacan at 2020-04-09T16:18:00-04:00
Fix CNF handling in compacting GC

Fixes #17937

Previously compacting GC simply ignored CNFs. This is mostly fine as
most (see "What about small compacts?" below) CNF objects don't have
outgoing pointers, and are "large" (allocated in large blocks) and large
objects are not moved or compacted.

However if we do GC *during* sharing-preserving compaction then the CNF
will have a hash table mapping objects that have been moved to the CNF
to their location in the CNF, to be able to preserve sharing.

This case is handled in the copying collector, in `scavenge_compact`,
where we evacuate hash table entries and then rehash the table.

Compacting GC ignored this case.

We now visit CNFs in all generations when threading pointers to the
compacted heap and thread hash table keys. A visited CNF is added to the
list `nfdata_chain`. After compaction is done, we re-visit the CNFs in
that list and rehash the tables.

The overhead is minimal: the list is static in `Compact.c`, and link
field is added to `StgCompactNFData` closure. Programs that don't use
CNFs should not be affected.

To test this CNF tests are now also run in a new way 'compacting_gc',
which just passes `-c` to the RTS, enabling compacting GC for the oldest
generation. Before this patch the result would be:

    Unexpected failures:
       compact_gc.run          compact_gc [bad exit code (139)] (compacting_gc)
       compact_huge_array.run  compact_huge_array [bad exit code (1)] (compacting_gc)

With this patch all tests pass. I can also pass `-c -DS` without any
failures.

What about small compacts? Small CNFs are still not handled by the
compacting GC. However so far I'm unable to write a test that triggers a
runtime panic ("update_fwd: unknown/strange object") by allocating a
small CNF in a compated heap. It's possible that I'm missing something
and it's not possible to have a small CNF.

NoFib Results:

--------------------------------------------------------------------------------
        Program           Size    Allocs    Instrs     Reads    Writes
--------------------------------------------------------------------------------
             CS          +0.1%      0.0%      0.0%     +0.0%     +0.0%
            CSD          +0.1%      0.0%      0.0%      0.0%      0.0%
             FS          +0.1%      0.0%      0.0%      0.0%      0.0%
              S          +0.1%      0.0%      0.0%      0.0%      0.0%
             VS          +0.1%      0.0%      0.0%      0.0%      0.0%
            VSD          +0.1%      0.0%     +0.0%     +0.0%     -0.0%
            VSM          +0.1%      0.0%     +0.0%     -0.0%      0.0%
           anna          +0.0%      0.0%     -0.0%     -0.0%     -0.0%
           ansi          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
           atom          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
         awards          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
         banner          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
     bernouilli          +0.1%      0.0%      0.0%     -0.0%     +0.0%
   binary-trees          +0.1%      0.0%     -0.0%     -0.0%      0.0%
          boyer          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
         boyer2          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
           bspt          +0.1%      0.0%     -0.0%     -0.0%     -0.0%
      cacheprof          +0.1%      0.0%     -0.0%     -0.0%     -0.0%
       calendar          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
       cichelli          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
        circsim          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
       clausify          +0.1%      0.0%     -0.0%     +0.0%     +0.0%
  comp_lab_zift          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
       compress          +0.1%      0.0%     +0.0%     +0.0%      0.0%
      compress2          +0.1%      0.0%     -0.0%      0.0%      0.0%
    constraints          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
   cryptarithm1          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
   cryptarithm2          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
            cse          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
   digits-of-e1          +0.1%      0.0%     +0.0%     -0.0%     -0.0%
   digits-of-e2          +0.1%      0.0%     -0.0%     -0.0%     -0.0%
         dom-lt          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
          eliza          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
          event          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
    exact-reals          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
         exp3_8          +0.1%      0.0%     +0.0%     -0.0%      0.0%
         expert          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
 fannkuch-redux          +0.1%      0.0%     -0.0%      0.0%      0.0%
          fasta          +0.1%      0.0%     -0.0%     +0.0%     +0.0%
            fem          +0.1%      0.0%     -0.0%     +0.0%      0.0%
            fft          +0.1%      0.0%     -0.0%     +0.0%     +0.0%
           fft2          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
       fibheaps          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
           fish          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
          fluid          +0.0%      0.0%     +0.0%     +0.0%     +0.0%
         fulsom          +0.1%      0.0%     -0.0%     +0.0%      0.0%
         gamteb          +0.1%      0.0%     +0.0%     +0.0%      0.0%
            gcd          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
    gen_regexps          +0.1%      0.0%     -0.0%     +0.0%      0.0%
         genfft          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
             gg          +0.1%      0.0%      0.0%     +0.0%     +0.0%
           grep          +0.1%      0.0%     -0.0%     +0.0%     +0.0%
         hidden          +0.1%      0.0%     +0.0%     -0.0%      0.0%
            hpg          +0.1%      0.0%     -0.0%     -0.0%     -0.0%
            ida          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
          infer          +0.1%      0.0%     +0.0%      0.0%     -0.0%
        integer          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
      integrate          +0.1%      0.0%     -0.0%     -0.0%     -0.0%
   k-nucleotide          +0.1%      0.0%     +0.0%     +0.0%      0.0%
          kahan          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
        knights          +0.1%      0.0%     -0.0%     -0.0%     -0.0%
         lambda          +0.1%      0.0%     +0.0%     +0.0%     -0.0%
     last-piece          +0.1%      0.0%     +0.0%      0.0%      0.0%
           lcss          +0.1%      0.0%     +0.0%     +0.0%      0.0%
           life          +0.1%      0.0%     -0.0%     +0.0%     +0.0%
           lift          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
         linear          +0.1%      0.0%     -0.0%     +0.0%      0.0%
      listcompr          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
       listcopy          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
       maillist          +0.1%      0.0%     +0.0%     -0.0%     -0.0%
         mandel          +0.1%      0.0%     +0.0%     +0.0%      0.0%
        mandel2          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
           mate          +0.1%      0.0%     +0.0%      0.0%     +0.0%
        minimax          +0.1%      0.0%     -0.0%      0.0%     -0.0%
        mkhprog          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
     multiplier          +0.1%      0.0%     +0.0%      0.0%      0.0%
         n-body          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
       nucleic2          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
           para          +0.1%      0.0%      0.0%     +0.0%     +0.0%
      paraffins          +0.1%      0.0%     +0.0%     -0.0%      0.0%
         parser          +0.1%      0.0%     -0.0%     -0.0%     -0.0%
        parstof          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
            pic          +0.1%      0.0%     -0.0%     -0.0%      0.0%
       pidigits          +0.1%      0.0%     +0.0%     -0.0%     -0.0%
          power          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
         pretty          +0.1%      0.0%     -0.0%     -0.0%     -0.1%
         primes          +0.1%      0.0%     -0.0%     -0.0%     -0.0%
      primetest          +0.1%      0.0%     -0.0%     -0.0%     -0.0%
         prolog          +0.1%      0.0%     -0.0%     -0.0%     -0.0%
         puzzle          +0.1%      0.0%     -0.0%     -0.0%     -0.0%
         queens          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
        reptile          +0.1%      0.0%     -0.0%     -0.0%     +0.0%
reverse-complem          +0.1%      0.0%     +0.0%      0.0%     -0.0%
        rewrite          +0.1%      0.0%     -0.0%     -0.0%     -0.0%
           rfib          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
            rsa          +0.1%      0.0%     -0.0%     +0.0%     -0.0%
            scc          +0.1%      0.0%     -0.0%     -0.0%     -0.1%
          sched          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
            scs          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
         simple          +0.1%      0.0%     -0.0%     -0.0%     -0.0%
          solid          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
        sorting          +0.1%      0.0%     -0.0%     -0.0%     -0.0%
  spectral-norm          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
         sphere          +0.1%      0.0%     -0.0%     -0.0%     -0.0%
         symalg          +0.1%      0.0%     -0.0%     -0.0%     -0.0%
            tak          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
      transform          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
       treejoin          +0.1%      0.0%     +0.0%     -0.0%     -0.0%
      typecheck          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
        veritas          +0.0%      0.0%     +0.0%     +0.0%     +0.0%
           wang          +0.1%      0.0%      0.0%     +0.0%     +0.0%
      wave4main          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
   wheel-sieve1          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
   wheel-sieve2          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
           x2n1          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
--------------------------------------------------------------------------------
            Min          +0.0%      0.0%     -0.0%     -0.0%     -0.1%
            Max          +0.1%      0.0%     +0.0%     +0.0%     +0.0%
 Geometric Mean          +0.1%     -0.0%     -0.0%     -0.0%     -0.0%

Bumping numbers of nonsensical perf tests:

Metric Increase:
    T12150
    T12234
    T12425
    T13035
    T5837
    T6048

It's simply not possible for this patch to increase allocations, and
I've wasted enough time on these test in the past (see #17686). I think
these tests should not be perf tests, but for now I'll bump the numbers.

- - - - -
dce50062 by Sylvain Henry at 2020-04-09T16:18:44-04:00
Rts: show errno on failure (#18033)

- - - - -
045139f4 by Hécate at 2020-04-09T23:10:44-04:00
Add an example to liftIO and explain its purpose

- - - - -
101fab6e by Sebastian Graf at 2020-04-09T23:11:21-04:00
Special case `isConstraintKindCon` on `AlgTyCon`

Previously, the `tyConUnique` record selector would unfold into a huge
case expression that would be inlined in all call sites, such as the
`INLINE`-annotated `coreView`, see #18026. `constraintKindTyConKey` only
occurs as the `Unique` of an `AlgTyCon` anyway, so we can make the code
a lot more compact, but have to move it to GHC.Core.TyCon.

Metric Decrease:
    T12150
    T12234

- - - - -
f5212dfc by Sebastian Graf at 2020-04-09T23:11:57-04:00
DmdAnal: No need to attach a StrictSig to DataCon workers

In GHC.Types.Id.Make we were giving a strictness signature to every data
constructor wrapper Id that we weren't looking at in demand analysis
anyway. We used to use its CPR info, but that has its own CPR signature
now.

`Note [Data-con worker strictness]` then felt very out of place, so I
moved it to GHC.Core.DataCon.

- - - - -
75a185dc by Sylvain Henry at 2020-04-09T23:12:37-04:00
Hadrian: fix --summary

- - - - -
723062ed by Ömer Sinan Ağacan at 2020-04-10T09:18:14+03:00
testsuite: Move no_lint to the top level, tweak hie002

- We don't want to benchmark linting so disable lints in hie002 perf
  test

- Move no_lint to the top-level to be able to use it in tests other than
  those in `testsuite/tests/perf/compiler`.

- Filter out -dstg-lint in no_lint.

- hie002 allocation numbers on 32-bit are unstable, so skip it on 32-bit

Metric Decrease:
    hie002
    ManyConstructors
    T12150
    T12234
    T13035
    T1969
    T4801
    T9233
    T9961

- - - - -
bcafaa82 by Peter Trommler at 2020-04-10T19:29:33-04:00
Testsuite: mark T11531 fragile

The test depends on a link editor allowing undefined symbols in an ELF
shared object. This is the standard but it seems some distributions
patch their link editor. See the report by @hsyl20 in #11531.

Fixes #11531

- - - - -
0889f5ee by Takenobu Tani at 2020-04-12T11:44:52+09:00
testsuite: Fix comment for a language extension

[skip ci]

- - - - -
cd4f92b5 by Simon Peyton Jones at 2020-04-12T11:20:58-04:00
Significant refactor of Lint

This refactoring of Lint was triggered by #17923, which is
fixed by this patch.

The main change is this.  Instead of
   lintType :: Type -> LintM LintedKind
we now have
   lintType :: Type -> LintM LintedType

Previously, all of typeKind was effectively duplicate in lintType.
Moreover, since we have an ambient substitution, we still had to
apply the substition here and there, sometimes more than once. It
was all very tricky, in the end, and made my head hurt.

Now, lintType returns a fully linted type, with all substitutions
performed on it.  This is much simpler.

The same thing is needed for Coercions.  Instead of
  lintCoercion :: OutCoercion
               -> LintM (LintedKind, LintedKind,
                         LintedType, LintedType, Role)
we now have
  lintCoercion :: Coercion -> LintM LintedCoercion

Much simpler!  The code is shorter and less bug-prone.

There are a lot of knock on effects.  But life is now better.

Metric Decrease:
    T1969

- - - - -
0efaf301 by Josh Meredith at 2020-04-12T11:21:34-04:00
Implement extensible interface files

- - - - -
54ca66a7 by Ryan Scott at 2020-04-12T11:22:10-04:00
Use conLikeUserTyVarBinders to quantify field selector types

This patch:

1. Writes up a specification for how the types of top-level field
   selectors should be determined in a new section of the GHC User's
   Guide, and
2. Makes GHC actually implement that specification by using
   `conLikeUserTyVarBinders` in `mkOneRecordSelector` to preserve the
   order and specificity of type variables written by the user.

Fixes #18023.

- - - - -
35799dda by Ben Gamari at 2020-04-12T11:22:50-04:00
hadrian: Don't --export-dynamic on Darwin

When fixing #17962 I neglected to consider that --export-dynamic is only
supported on ELF platforms.

- - - - -
e8029816 by Alexis King at 2020-04-12T11:23:27-04:00
Add an INLINE pragma to Control.Category.>>>

This fixes #18013 by adding INLINE pragmas to both Control.Category.>>>
and GHC.Desugar.>>>. The functional change in this patch is tiny (just
two lines of pragmas!), but an accompanying Note explains in gory
detail what’s going on.

- - - - -
0da186c1 by Krzysztof Gogolewski at 2020-04-14T07:55:20-04:00
Change zipWith to zipWithEqual in a few places

- - - - -
074c1ccd by Andreas Klebinger at 2020-04-14T07:55:55-04:00
Small change to the windows ticker.

We already have a function to go from time to ms so use it.
Also expand on the state of timer resolution.

- - - - -
b69cc884 by Alp Mestanogullari at 2020-04-14T07:56:38-04:00
hadrian: get rid of unnecessary levels of nesting in source-dist

- - - - -
d0c3b069 by Julien Debon at 2020-04-14T07:57:16-04:00
doc (Foldable): Add examples to Data.Foldable

See #17929

- - - - -
5b08e0c0 by Ben Gamari at 2020-04-14T23:28:20-04:00
StgCRun: Enable unwinding only on Linux

It's broken on macOS due and SmartOS due to assembler differences
(#15207) so let's be conservative in enabling it. Also, refactor things
to make the intent clearer.

- - - - -
27cc2e7b by Ben Gamari at 2020-04-14T23:28:57-04:00
rts: Don't mark evacuate_large as inline

This function has two callsites and is quite large. GCC consequently
decides not to inline and warns instead. Given the situation, I can't
blame it. Let's just remove the inline specifier.

- - - - -
9853fc5e by Ben Gamari at 2020-04-14T23:29:48-04:00
base: Enable large file support for OFD locking impl.

Not only is this a good idea in general but this should also avoid
issue #17950 by ensuring that off_t is 64-bits.

- - - - -
7b41f21b by Matthew Pickering at 2020-04-14T23:30:24-04:00
Hadrian: Make -i paths absolute

The primary reason for this change is that ghcide does not work with
relative paths. It also matches what cabal and stack do, they always
pass absolute paths.

- - - - -
41230e26 by Daniel Gröber at 2020-04-14T23:31:01-04:00
Zero out pinned block alignment slop when profiling

The heap profiler currently cannot traverse pinned blocks because of
alignment slop. This used to just be a minor annoyance as the whole block
is accounted into a special cost center rather than the respective object's
CCS, cf. #7275. However for the new root profiler we would like to be able
to visit _every_ closure on the heap. We need to do this so we can get rid
of the current 'flip' bit hack in the heap traversal code.

Since info pointers are always non-zero we can in principle skip all the
slop in the profiler if we can rely on it being zeroed. This assumption
caused problems in the past though, commit a586b33f8e ("rts: Correct
handling of LARGE ARR_WORDS in LDV profiler"), part of !1118, tried to use
the same trick for BF_LARGE objects but neglected to take into account that
shrink*Array# functions don't ensure that slop is zeroed when not
compiling with profiling.

Later, commit 0c114c6599 ("Handle large ARR_WORDS in heap census (fix
as we will only be assuming slop is zeroed when profiling is on.

This commit also reduces the ammount of slop we introduce in the first
place by calculating the needed alignment before doing the allocation for
small objects where we know the next available address. For large objects
we don't know how much alignment we'll have to do yet since those details
are hidden behind the allocateMightFail function so there we continue to
allocate the maximum additional words we'll need to do the alignment.

So we don't have to duplicate all this logic in the cmm code we pull it
into the RTS allocatePinned function instead.

Metric Decrease:
    T7257
    haddock.Cabal
    haddock.base

- - - - -
15fa9bd6 by Daniel Gröber at 2020-04-14T23:31:01-04:00
rts: Expand and add more notes regarding slop

- - - - -
caf3f444 by Daniel Gröber at 2020-04-14T23:31:01-04:00
rts: allocatePinned: Fix confusion about word/byte units

- - - - -
c3c0f662 by Daniel Gröber at 2020-04-14T23:31:01-04:00
rts: Underline some Notes as is conventional

- - - - -
e149dea9 by Daniel Gröber at 2020-04-14T23:31:38-04:00
rts: Fix nomenclature in OVERWRITING_CLOSURE macros

The additional commentary introduced by commit 8916e64e5437 ("Implement
shrinkSmallMutableArray# and resizeSmallMutableArray#.") unfortunately got
this wrong. We set 'prim' to true in overwritingClosureOfs because we
_don't_ want to call LDV_recordDead().

The reason is because of this "inherently used" distinction made in the LDV
profiler so I rename the variable to be more appropriate.

- - - - -
1dd3d18c by Daniel Gröber at 2020-04-14T23:31:38-04:00
Remove call to LDV_RECORD_CREATE for array resizing

- - - - -
19de2fb0 by Daniel Gröber at 2020-04-14T23:31:38-04:00
rts: Assert LDV_recordDead is not called for inherently used closures

The comments make it clear LDV_recordDead should not be called for
inhererently used closures, so add an assertion to codify this fact.

- - - - -
0b934e30 by Ryan Scott at 2020-04-14T23:32:14-04:00
Bump template-haskell version to 2.17.0.0

This requires bumping the `exceptions` and `text` submodules to bring
in commits that bump their respective upper version bounds on
`template-haskell`.

Fixes #17645. Fixes #17696.

Note that the new `text` commit includes a fair number of additions
to the Haddocks in that library. As a result, Haddock has to do more
work during the `haddock.Cabal` test case, increasing the number of
allocations it requires. Therefore,

-------------------------
Metric Increase:
    haddock.Cabal
-------------------------

- - - - -
22cc8e51 by Ryan Scott at 2020-04-15T17:48:47-04:00
Fix #18052 by using pprPrefixOcc in more places

This fixes several small oversights in the choice of pretty-printing
function to use. Fixes #18052.

- - - - -
ec77b2f1 by Daniel Gröber at 2020-04-15T17:49:24-04:00
rts: ProfHeap: Fix wrong time in last heap profile sample

We've had this longstanding issue in the heap profiler, where the time of
the last sample in the profile is sometimes way off causing the rendered
graph to be quite useless for long runs.

It seems to me the problem is that we use mut_user_time() for the last
sample as opposed to getRTSStats(), which we use when calling heapProfile()
in GC.c.

The former is equivalent to getProcessCPUTime() but the latter does
some additional stuff:

    getProcessCPUTime() - end_init_cpu - stats.gc_cpu_ns -
    stats.nonmoving_gc_cpu_ns

So to fix this just use getRTSStats() in both places.

- - - - -
85fc32f0 by Sylvain Henry at 2020-04-17T12:45:25-04:00
Hadrian: fix dyn_o/dyn_hi rule (#17534)

- - - - -
bfde3b76 by Ryan Scott at 2020-04-17T12:46:02-04:00
Fix #18065 by fixing an InstCo oversight in Core Lint

There was a small thinko in Core Lint's treatment of `InstCo`
coercions that ultimately led to #18065. The fix: add an apostrophe.
That's it!

Fixes #18065.

Co-authored-by: Simon Peyton Jones <simonpj at microsoft.com>

- - - - -
a05348eb by Cale Gibbard at 2020-04-17T13:08:47-04:00
Change the fail operator argument of BindStmt to be a Maybe

Don't use noSyntaxExpr for it. There is no good way to defensively case
on that, nor is it clear one ought to do so.

- - - - -
79e27144 by John Ericson at 2020-04-17T13:08:47-04:00
Use trees that grow for rebindable operators for `<-` binds

Also add more documentation.

- - - - -
18bc16ed by Cale Gibbard at 2020-04-17T13:08:47-04:00
Use FailOperator in more places, define a couple datatypes (XBindStmtRn and XBindStmtTc) to help clarify the meaning of XBindStmt in the renamer and typechecker

- - - - -
84cc8394 by Simon Peyton Jones at 2020-04-18T13:20:29-04:00
Add a missing zonk in tcHsPartialType

I omitted a vital zonk when refactoring tcHsPartialType in
   commit 48fb3482f8cbc8a4b37161021e846105f980eed4
   Author: Simon Peyton Jones <simonpj at microsoft.com>
   Date:   Wed Jun 5 08:55:17 2019 +0100

   Fix typechecking of partial type signatures

This patch fixes it and adds commentary to explain why.

Fixes #18008

- - - - -
2ee96ac1 by Ben Gamari at 2020-04-18T13:21:05-04:00
gitlab-ci: Bump FreeBSD bootstrap compiler to 8.10.1

- - - - -
434312e5 by Ben Gamari at 2020-04-18T13:21:05-04:00
gitlab-ci: Enable FreeBSD job for so-labelled MRs

- - - - -
ddffb227 by Ben Gamari at 2020-04-18T13:21:05-04:00
gitlab-ci: Use rules syntax for conditional jobs

- - - - -
e2586828 by Ben Gamari at 2020-04-18T13:21:05-04:00
Bump hsc2hs submodule

- - - - -
15ab6cd5 by Ömer Sinan Ağacan at 2020-04-18T13:21:44-04:00
Improve prepForeignCall error reporting

Show parameters and description of the error code when ffi_prep_cif
fails.

This may be helpful for debugging #17018.

- - - - -
3ca52151 by Sylvain Henry at 2020-04-18T20:04:14+02:00
GHC.Core.Opt renaming

* GHC.Core.Op                  => GHC.Core.Opt
* GHC.Core.Opt.Simplify.Driver => GHC.Core.Opt.Driver
* GHC.Core.Opt.Tidy            => GHC.Core.Tidy
* GHC.Core.Opt.WorkWrap.Lib    => GHC.Core.Opt.WorkWrap.Utils

As discussed in:
 * https://mail.haskell.org/pipermail/ghc-devs/2020-April/018758.html
 * https://gitlab.haskell.org/ghc/ghc/issues/13009#note_264650

- - - - -
15312bbb by Sylvain Henry at 2020-04-18T20:04:46+02:00
Modules (#13009)

* SysTools
* Parser
* GHC.Builtin
* GHC.Iface.Recomp
* Settings

Update Haddock submodule

Metric Decrease:
    Naperian
    parsing001

- - - - -
eaed0a32 by Alexis King at 2020-04-19T03:16:44-04:00
Add missing addInScope call for letrec binders in OccurAnal

This fixes #18044, where a shadowed variable was incorrectly substituted
by the binder swap on the RHS of a floated-in letrec. This can only
happen when the uniques line up *just* right, so writing a regression
test would be very difficult, but at least the fix is small and
straightforward.

- - - - -
a6431f92 by Simon Peyton Jones at 2020-04-20T09:17:23+01:00
Avoid useless w/w split

This patch is just a tidy-up for the post-strictness-analysis
worker wrapper split.  Consider

   f x = x

Strictnesss analysis does not lead to a w/w split, so the
obvious thing is to leave it 100% alone.  But actually, because
the RHS is small, we ended up adding a StableUnfolding for it.

There is some reason to do this if we choose /not/ do to w/w
on the grounds that the function is small.  See
Note [Don't w/w inline small non-loop-breaker things]

But there is no reason if we would not have done w/w anyway.

This patch just moves the conditional to later.  Easy.
This does move soem -ddump-simpl printouts around a bit.

I also discovered that the previous code was overwritten an
InlineCompulsory with InlineStable, which is utterly wrong.  That in
turn meant that some default methods (marked InlineCompulsory)
were getting their InlineCompulsory squashed. This patch fixes
that bug --- but of course that does mean a bit more inlining!

- - - - -


30 changed files:

- .gitlab-ci.yml
- .gitlab/ci.sh
- compiler/GHC.hs
- compiler/prelude/PrelNames.hs → compiler/GHC/Builtin/Names.hs
- compiler/prelude/PrelNames.hs-boot → compiler/GHC/Builtin/Names.hs-boot
- compiler/prelude/THNames.hs → compiler/GHC/Builtin/Names/TH.hs
- compiler/prelude/PrimOp.hs → compiler/GHC/Builtin/PrimOps.hs
- compiler/prelude/PrimOp.hs-boot → compiler/GHC/Builtin/PrimOps.hs-boot
- compiler/prelude/TysWiredIn.hs → compiler/GHC/Builtin/Types.hs
- compiler/prelude/TysWiredIn.hs-boot → compiler/GHC/Builtin/Types.hs-boot
- compiler/typecheck/TcTypeNats.hs → compiler/GHC/Builtin/Types/Literals.hs
- compiler/prelude/TysPrim.hs → compiler/GHC/Builtin/Types/Prim.hs
- compiler/prelude/KnownUniques.hs → compiler/GHC/Builtin/Uniques.hs
- compiler/prelude/KnownUniques.hs-boot → compiler/GHC/Builtin/Uniques.hs-boot
- compiler/prelude/PrelInfo.hs → compiler/GHC/Builtin/Utils.hs
- compiler/prelude/primops.txt.pp → compiler/GHC/Builtin/primops.txt.pp
- compiler/GHC/ByteCode/Instr.hs
- compiler/GHC/ByteCode/Linker.hs
- compiler/GHC/ByteCode/Types.hs
- compiler/GHC/Cmm/CLabel.hs
- compiler/GHC/Cmm/Lexer.x
- compiler/GHC/Cmm/Monad.hs
- compiler/GHC/Cmm/Parser.y
- compiler/GHC/CmmToLlvm.hs
- compiler/GHC/Core.hs
- compiler/GHC/Core/Class.hs
- compiler/GHC/Core/Coercion.hs
- compiler/GHC/Core/Coercion/Axiom.hs
- compiler/GHC/Core/Coercion/Opt.hs
- compiler/GHC/Core/ConLike.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6d9fd7cd87afa68586da31973fd49036aa566d39...a6431f92a2a5fbaf58a647d4b332c5c7222309f6

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6d9fd7cd87afa68586da31973fd49036aa566d39...a6431f92a2a5fbaf58a647d4b332c5c7222309f6
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/20200420/e368914d/attachment-0001.html>


More information about the ghc-commits mailing list