[Git][ghc/ghc][wip/ticky-eventlog] 166 commits: core-spec: Modify file paths according to new module hierarchy

Ben Gamari gitlab at gitlab.haskell.org
Wed Jun 24 02:05:12 UTC 2020



Ben Gamari pushed to branch wip/ticky-eventlog at Glasgow Haskell Compiler / GHC


Commits:
ede24126 by Takenobu Tani at 2020-05-27T00:13:55-04:00
core-spec: Modify file paths according to new module hierarchy

This patch updates file paths according to new module hierarchy [1]:

  * GHC/Core.hs                <= coreSyn/CoreSyn.hs
  * GHC/Core/Coercion.hs       <= types/Coercion.hs
  * GHC/Core/Coercion/Axiom.hs <= types/CoAxiom.hs
  * GHC/Core/Coercion/Opt.hs   <= types/OptCoercion.hs
  * GHC/Core/DataCon.hs        <= basicTypes/DataCon.hs
  * GHC/Core/FamInstEnv.hs     <= types/FamInstEnv.hs
  * GHC/Core/Lint.hs           <= coreSyn/CoreLint.hs
  * GHC/Core/Subst.hs          <= coreSyn/CoreSubst.hs
  * GHC/Core/TyCo/Rep.hs       <= types/TyCoRep.hs
  * GHC/Core/TyCon.hs          <= types/TyCon.hs
  * GHC/Core/Type.hs           <= types/Type.hs
  * GHC/Core/Unify.hs          <= types/Unify.hs
  * GHC/Types/Literal.hs       <= basicTypes/Literal.hs
  * GHC/Types/Var.hs           <= basicTypes/Var.hs

[1]: https://gitlab.haskell.org/ghc/ghc/-/wikis/Make-GHC-codebase-more-modular

[skip ci]

- - - - -
04750304 by Ben Gamari at 2020-05-27T00:14:33-04:00
eventlog: Fix racy flushing

Previously no attempt was made to avoid multiple threads writing their
capability-local eventlog buffers to the eventlog writer simultaneously.
This could result in multiple eventlog streams being interleaved. Fix
this by documenting that the EventLogWriter's write() and flush()
functions may be called reentrantly and fix the default writer to
protect its FILE* by a mutex.

Fixes #18210.

- - - - -
d6203f24 by Joshua Price at 2020-05-27T00:15:17-04:00
Make `identifier` parse unparenthesized `->` (#18060)

- - - - -
28deee28 by Ben Gamari at 2020-05-28T16:23:21-04:00
GHC.Core.Unfold: Refactor traceInline

This reduces duplication as well as fixes a bug wherein -dinlining-check
would override -ddump-inlinings. Moreover, the new variant

- - - - -
1f393e1e by Ben Gamari at 2020-05-28T16:23:21-04:00
Avoid unnecessary allocations due to tracing utilities

While ticky-profiling the typechecker I noticed that hundreds of
millions of SDocs are being allocated just in case -ddump-*-trace is
enabled. This is awful.

We avoid this by ensuring that the dump flag check is inlined into the
call site, ensuring that the tracing document needn't be allocated
unless it's actually needed.

See Note [INLINE conditional tracing utilities] for details.

Fixes #18168.

Metric Decrease:
  T9961
  haddock.Cabal
  haddock.base
  haddock.compiler

- - - - -
5f621a78 by Vladislav Zavialov at 2020-05-28T16:23:58-04:00
Add Semigroup/Monoid for Q (#18123)

- - - - -
dc5f004c by Xavier Denis at 2020-05-28T16:24:37-04:00
Fix #18071

Run the core linter on candidate instances to ensure they are
well-kinded.

Better handle quantified constraints by using a CtWanted to avoid
having unsolved constraints thrown away at the end by the solver.

- - - - -
10e6982c by Sebastian Graf at 2020-05-28T16:25:14-04:00
FloatOut: Only eta-expand dead-end RHS if arity will increase (#18231)

Otherwise we risk turning trivial RHS into non-trivial RHS, introducing
unnecessary bindings in the next Simplifier run, resulting in more
churn.

Fixes #18231.

- - - - -
08dab5f7 by Sebastian Graf at 2020-05-28T16:25:14-04:00
DmdAnal: Recognise precise exceptions from case alternatives (#18086)

Consider

```hs
m :: IO ()
m = do
  putStrLn "foo"
  error "bar"
```

`m` (from #18086) always throws a (precise or imprecise) exception or
diverges. Yet demand analysis infers `<L,A>` as demand signature instead
of `<L,A>x` for it.

That's because the demand analyser sees `putStrLn` occuring in a case
scrutinee and decides that it has to `deferAfterPreciseException`,
because `putStrLn` throws a precise exception on some control flow
paths. This will mask the `botDiv` `Divergence`of the single case alt
containing `error` to `topDiv`. Since `putStrLn` has `topDiv` itself,
the final `Divergence` is `topDiv`.

This is easily fixed: `deferAfterPreciseException` works by `lub`ing
with the demand type of a virtual case branch denoting the precise
exceptional control flow. We used `nopDmdType` before, but we can be
more precise and use `exnDmdType`, which is `nopDmdType` with `exnDiv`.

Now the `Divergence` from the case alt will degrade `botDiv` to `exnDiv`
instead of `topDiv`, which combines with the result from the scrutinee
to `exnDiv`, and all is well.

Fixes #18086.

- - - - -
aef95f11 by Ben Gamari at 2020-05-28T16:25:53-04:00
Ticky-ticky: Record DataCon name in ticker name

This makes it significantly easier to spot the nature of
allocations regressions and comes at a reasonably low cost.

- - - - -
8f021b8c by Ben Gamari at 2020-05-28T16:26:34-04:00
hadrian: Don't track GHC's verbosity argument

Teach hadrian to ignore GHC's -v argument in its recompilation check,
thus fixing #18131.

- - - - -
13d9380b by Ben Gamari at 2020-05-28T16:27:20-04:00
Rip out CmmStackInfo(updfr_space)

As noted in #18232, this field is currently completely unused and
moreover doesn't have a clear meaning.

- - - - -
f10d11fa by Andreas Klebinger at 2020-05-29T01:38:42-04:00
Fix "build/elem" RULE.

An redundant constraint prevented the rule from matching.

Fixing this allows a call to elem on a known list to be translated
into a series of equality checks, and eventually a simple case
expression.

Surprisingly this seems to regress elem for strings. To avoid
this we now also allow foldrCString to inline and add an UTF8
variant. This results in elem being compiled to a tight
non-allocating loop over the primitive string literal which
performs a linear search.

In the process this commit adds UTF8 variants for some of the
functions in GHC.CString. This is required to make this work for
both ASCII and UTF8 strings.

There are also small tweaks to the CString related rules.
We now allow ourselfes the luxury to compare the folding function
via eqExpr, which helps to ensure the rule fires before we inline
foldrCString*. Together with a few changes to allow matching on both
the UTF8 and ASCII variants of the CString functions.

- - - - -
bbeb2389 by Ben Gamari at 2020-05-29T01:39:19-04:00
CoreToStg: Add Outputable ArgInfo instance

- - - - -
0e3361ca by Simon Peyton Jones at 2020-05-29T01:39:19-04:00
Make Lint check return type of a join point

Consider
   join x = rhs in body
It's important that the type of 'rhs' is the same as the type of
'body', but Lint wasn't checking that invariant.

Now it does!  This was exposed by investigation into !3113.

- - - - -
c49f7df0 by Simon Peyton Jones at 2020-05-29T01:39:19-04:00
Do not float join points in exprIsConApp_maybe

We hvae been making exprIsConApp_maybe cleverer in recent times:

    commit b78cc64e923716ac0512c299f42d4d0012306c05
    Date:   Thu Nov 15 17:14:31 2018 +0100
    Make constructor wrappers inline only during the final phase

    commit 7833cf407d1f608bebb1d38bb99d3035d8d735e6
    Date:   Thu Jan 24 17:58:50 2019 +0100
    Look through newtype wrappers (Trac #16254)

    commit c25b135ff5b9c69a90df0ccf51b04952c2dc6ee1
    Date:   Thu Feb 21 12:03:22 2019 +0000
    Fix exprIsConApp_maybe

But alas there was still a bug, now immortalised in
  Note [Don't float join points]
in SimpleOpt.

It's quite hard to trigger because it requires a dead
join point, but it came up when compiling Cabal
Cabal.Distribution.Fields.Lexer.hs, when working on
!3113.

Happily, the fix is extremly easy.  Finding the
bug was not so easy.

- - - - -
46720997 by Ben Gamari at 2020-05-29T01:39:19-04:00
Allow simplification through runRW#

Because runRW# inlines so late, we were previously able to do very
little simplification across it. For instance, given even a simple
program like

    case runRW# (\s -> let n = I# 42# in n) of
      I# n# -> f n#

we previously had no way to avoid the allocation of the I#.

This patch allows the simplifier to push strict contexts into the
continuation of a runRW# application, as explained in
in Note [Simplification of runRW#] in GHC.CoreToStg.Prep.

Fixes #15127.

Metric Increase:
    T9961
Metric Decrease:
    ManyConstructors

Co-Authored-By: Simon Peyton-Jone <simonpj at microsoft.com>

- - - - -
277c2f26 by Ben Gamari at 2020-05-29T01:39:55-04:00
Eta expand un-saturated primops

Now since we no longer try to predict CAFfyness we have no need for the
solution to #16846. Eta expanding unsaturated primop applications is
conceptually simpler, especially in the presence of levity polymorphism.

This essentially reverts cac8dc9f51e31e4c0a6cd9bc302f7e1bc7c03beb,
as suggested in #18079.

Closes #18079.

- - - - -
f44d7ae0 by Simon Jakobi at 2020-05-29T01:40:34-04:00
base: Scrap deprecation plan for Data.Monoid.{First,Last}

See the discussion on the libraries mailing list for context:

https://mail.haskell.org/pipermail/libraries/2020-April/030357.html

- - - - -
8b494895 by Jeremy Schlatter at 2020-05-29T01:41:12-04:00
Fix typo in documentation

- - - - -
998450f4 by Gleb Popov at 2020-05-29T01:41:53-04:00
Always define USE_PTHREAD_FOR_ITIMER for FreeBSD.

- - - - -
f9a513e0 by Alp Mestanogullari at 2020-05-29T01:42:36-04:00
hadrian: introduce 'install' target

Its logic is very simple. It `need`s the `binary-dist-dir` target
and runs suitable `configure` and `make install` commands for the
user. A new `--prefix` command line argument is introduced to
specify where GHC should be installed.

- - - - -
67738db1 by Travis Whitaker at 2020-05-29T13:34:48-04:00
Build a threaded stage 1 if the bootstrapping GHC supports it.

- - - - -
aac19e6c by Peter Trommler at 2020-05-29T13:35:24-04:00
PPC NCG: No per-symbol .section ".toc" directives

All position independent symbols are collected during code generation
and emitted in one go. Prepending each symbol with a .section ".toc"
directive is redundant. This patch drops the per-symbol directives
leading to smaller assembler files.

Fixes #18250

- - - - -
4413828b by Ben Gamari at 2020-05-30T06:07:31-04:00
rts: Teach getNumProcessors to return available processors

Previously we would report the number of physical processors, which
can be quite wrong in a containerized setting. Now we rather return how
many processors are in our affinity mask when possible.

I also refactored the code to prefer platform-specific since this will
report logical CPUs instead of physical (using
`machdep.cpu.thread_count` on Darwin and `cpuset_getaffinity` on FreeBSD).

Fixes #14781.

- - - - -
1449435c by Ben Gamari at 2020-05-30T06:07:31-04:00
users-guide: Note change in getNumProcessors in users guide

- - - - -
3d960169 by Ben Gamari at 2020-05-30T06:07:31-04:00
rts: Drop compatibility shims for Windows Vista

We can now assume that the thread and processor group interfaces are
available.

- - - - -
7f8f948c by Peter Trommler at 2020-05-30T06:08:07-04:00
PPC NCG: Fix .size directive on powerpc64 ELF v1

Thanks to Sergei Trofimovich for pointing out the issue.

Fixes #18237

- - - - -
7c555b05 by Andreas Klebinger at 2020-05-30T06:08:43-04:00
Optimize GHC.Utils.Monad.

Many functions in this module are recursive and as such are marked
loop breakers. Which means they are unlikely to get an unfolding.

This is *bad*. We always want to specialize them to specific Monads.
Which requires a visible unfolding at the use site.

I rewrote the recursive ones from:

    foo f x = ... foo x' ...

to

    foo f x = go x
      where
        go x = ...

As well as giving some pragmas to make all of them available
for specialization.

The end result is a reduction of allocations of about -1.4% for
nofib/spectral/simple/Main.hs when compiled with `-O`.

-------------------------
Metric Decrease:
    T12425
    T14683
    T5631
    T9233
    T9675
    T9961
    WWRec
-------------------------

- - - - -
8b1cb5df by Ben Gamari at 2020-05-30T06:09:20-04:00
Windows: Bump Windows toolchain to 0.2

- - - - -
6947231a by Zubin Duggal at 2020-05-30T06:10:02-04:00
Simplify contexts in GHC.Iface.Ext.Ast

- - - - -
2ee4f36c by Daniel Gröber at 2020-06-01T06:32:56-04:00
Cleanup OVERWRITING_CLOSURE logic

The code is just more confusing than it needs to be. We don't need to mix
the threaded check with the ldv profiling check since ldv's init already
checks for this. Hence they can be two separate checks. Taking the sanity
checking into account is also cleaner via DebugFlags.sanity. No need for
checking the DEBUG define.

The ZERO_SLOP_FOR_LDV_PROF and ZERO_SLOP_FOR_SANITY_CHECK definitions the
old code had also make things a lot more opaque IMO so I removed those.

- - - - -
6159559b by Daniel Gröber at 2020-06-01T06:32:56-04:00
Fix OVERWRITING_CLOSURE assuming closures are not inherently used

The new ASSERT in LDV_recordDead() was being tripped up by MVars when
removeFromMVarBlockedQueue() calls OVERWRITING_CLOSURE() via
OVERWRITE_INFO().

- - - - -
38992085 by Daniel Gröber at 2020-06-01T06:32:56-04:00
Always zero shrunk mutable array slop when profiling

When shrinking arrays in the profiling way we currently don't always zero
the leftover slop. This means we can't traverse such closures in the heap
profiler. The old Note [zeroing slop] and #8402 have some rationale for why
this is so but I belive the reasoning doesn't apply to mutable
closures. There users already have to ensure multiple threads don't step on
each other's toes so zeroing should be safe.

- - - - -
b0c1f2a6 by Ben Gamari at 2020-06-01T06:33:37-04:00
testsuite: Add test for #18151

- - - - -
9a99a178 by Ben Gamari at 2020-06-01T06:33:37-04:00
testsuite: Add test for desugaring of PostfixOperators

- - - - -
2b89ca5b by Ben Gamari at 2020-06-01T06:33:37-04:00
HsToCore: Eta expand left sections

Strangely, the comment next to this code already alluded to the fact
that even simply eta-expanding will sacrifice laziness. It's quite
unclear how we regressed so far.

See #18151.

- - - - -
d412d7a3 by Kirill Elagin at 2020-06-01T06:34:21-04:00
Winferred-safe-imports: Do not exit with error

Currently, when -Winferred-safe-imports is enabled, even when it is not
turned into an error, the compiler will still exit with exit code 1 if
this warning was emitted.

Make sure it is really treated as a warning.

- - - - -
f945eea5 by Ben Gamari at 2020-06-01T06:34:58-04:00
nonmoving: Optimise log2_ceil

- - - - -
aab606e4 by Bodigrim at 2020-06-01T06:35:36-04:00
Clarify description of fromListN
- - - - -
7e5220e2 by Bodigrim at 2020-06-01T06:35:36-04:00
Apply suggestion to libraries/base/GHC/Exts.hs
- - - - -
f3fb1ce9 by fendor at 2020-06-01T06:36:18-04:00
Add `isInScope` check to `lintCoercion`

Mirrors the behaviour of `lintType`.

- - - - -
5ac4d946 by fendor at 2020-06-01T06:36:18-04:00
Lint rhs of IfaceRule

- - - - -
1cef6126 by Jeremy Schlatter at 2020-06-01T06:37:00-04:00
Fix wording in documentation

The duplicate "orphan instance" phrase here doesn't make sense, and was
probably an accident.

- - - - -
5aaf08f2 by Takenobu Tani at 2020-06-01T06:37:43-04:00
configure: Modify aclocal.m4 according to new module hierarchy

This patch updates file paths according to new module hierarchy [1]:

* Rename:
  * compiler/GHC/Parser.hs       <= compiler/parser/Parser.hs
  * compiler/GHC/Parser/Lexer.hs <= compiler/Parser/Lexer.hs

* Add:
  * compiler/GHC/Cmm/Lexer.hs

[1]: https://gitlab.haskell.org/ghc/ghc/-/wikis/Make-GHC-codebase-more-modular

- - - - -
15857ad8 by Ben Gamari at 2020-06-01T06:38:26-04:00
testsuite: Don't fail if we can't unlink __symlink_test

Afterall, it's possible we were unable to create it due to lack of
symlink permission.

- - - - -
4a7229ef by Ben Gamari at 2020-06-01T06:38:26-04:00
testsuite: Refactor ghostscript detection

Tamar reported that he saw crashes due to unhandled exceptions.

- - - - -
2ab37eaf by Ben Gamari at 2020-06-01T06:38:26-04:00
testsuite/perf_notes: Fix ill-typed assignments

- - - - -
e45d5b66 by Ben Gamari at 2020-06-01T06:38:26-04:00
testsuite/testutil: Fix bytes/str mismatch

- - - - -
7002d0cb by Ben Gamari at 2020-06-01T06:38:26-04:00
testsuite: Work around spurious mypy failure

- - - - -
11390e3a by Takenobu Tani at 2020-06-01T06:39:05-04:00
Clean up file paths for new module hierarchy

This updates comments only.
This patch replaces file references according to new module hierarchy.

See also:
* https://gitlab.haskell.org/ghc/ghc/-/wikis/Make-GHC-codebase-more-modular
* https://gitlab.haskell.org/ghc/ghc/issues/13009

- - - - -
8f2e5732 by Takenobu Tani at 2020-06-01T06:39:05-04:00
Modify file paths to module paths for new module hierarchy

This updates comments only.

This patch replaces module references according to new module
hierarchy [1][2].

For files under the `compiler/` directory, I replace them as
module paths instead of file paths. For instance,
`GHC.Unit.State` instead of `compiler/GHC/Unit/State.hs` [3].

For current and future haddock's markup, this patch encloses
the module name with "" [4].

[1]: https://gitlab.haskell.org/ghc/ghc/-/wikis/Make-GHC-codebase-more-modular
[2]: https://gitlab.haskell.org/ghc/ghc/issues/13009
[3]: https://gitlab.haskell.org/ghc/ghc/-/merge_requests/3375#note_276613
[4]: https://haskell-haddock.readthedocs.io/en/latest/markup.html#linking-to-modules

- - - - -
68b71c4a by Tom Ellis at 2020-06-01T06:39:55-04:00
Rename the singleton tuple GHC.Tuple.Unit to GHC.Tuple.Solo

- - - - -
95da76c2 by Sylvain Henry at 2020-06-01T06:40:41-04:00
Hadrian: fix binary-dist target for cross-compilation

- - - - -
730fcd54 by Vladislav Zavialov at 2020-06-01T06:41:18-04:00
Improve parser error messages for the @-operator

Since GHC diverges from the Haskell Report by allowing the user
to define (@) as an infix operator, we better give a good
error message when the user does so unintentionally.

In general, this is rather hard to do, as some failures will be
discovered only in the renamer or the type checker:

	x :: (Integer, Integer)
	x @ (a, b) = (1, 2)

This patch does *not* address this general case.

However, it gives much better error messages when the binding
is not syntactically valid:

	pairs xs @ (_:xs') = zip xs xs'

Before this patch, the error message was rather puzzling:

	<interactive>:1:1: error: Parse error in pattern: pairs

After this patch, the error message includes a hint:

	<interactive>:1:1: error:
	    Parse error in pattern: pairs
	    In a function binding for the ‘@’ operator.
	    Perhaps you meant an as-pattern, which must not be surrounded by whitespace

- - - - -
0fde5377 by Vladislav Zavialov at 2020-06-01T06:41:18-04:00
Improve parser error messages for TypeApplications

With this patch, we always parse  f @t  as a type application,
thereby producing better error messages.

This steals two syntactic forms:

* Prefix form of the @-operator in expressions. Since the @-operator is
  a divergence from the Haskell Report anyway, this is not a major loss.

* Prefix form of @-patterns. Since we are stealing loose infix form
  anyway, might as well sacrifice the prefix form for the sake of much
  better error messages.

- - - - -
c68e7e1e by Vladislav Zavialov at 2020-06-01T06:41:18-04:00
Improve parser error messages for TemplateHaskellQuotes

While [e| |], [t| |], [d| |], and so on, steal syntax from list
comprehensions, [| |] and [|| ||] do not steal any syntax.

Thus we can improve error messages by always accepting them in the
lexer. Turns out the renamer already performs necessary validation.

- - - - -
120aedbd by Ben Gamari at 2020-06-01T16:07:02-04:00
gitlab-ci: Disable use of ld.lld on ARMv7

It turns out that lld non-deterministically fails on ARMv7. I suspect
this may be due to the a kernel regression as this only started
happening when we upgraded to 5.4. Nevertheless, easily avoided by
simply sticking with gold.

Works around #18280.

- - - - -
d6279ff0 by Ben Gamari at 2020-06-02T13:03:30-04:00
gitlab-ci: Ensure that workaround for #18280 applies to bindisttest

We need to ensure that the `configure` flags working around #18280 are
propagated to the bindisttest `configure` as well.

- - - - -
cb5c31b5 by Ben Gamari at 2020-06-03T17:55:04-04:00
gitlab-ci: Allow ARMv7 job to fail

Due to #18298.

- - - - -
32a4ae90 by John Ericson at 2020-06-04T04:34:42-04:00
Clean up boot vs non-boot disambiguating types

We often have (ModuleName, Bool) or (Module, Bool) pairs for "extended"
module names (without or with a unit id) disambiguating boot and normal
modules. We think this is important enough across the compiler that it
deserves a new nominal product type. We do this with synnoyms and a
functor named with a `Gen` prefix, matching other newly created
definitions.

It was also requested that we keep custom `IsBoot` / `NotBoot` sum type.
So we have it too. This means changing many the many bools to use that
instead.

Updates `haddock` submodule.

- - - - -
c05756cd by Niklas Hambüchen at 2020-06-04T04:35:24-04:00
docs: Add more details on InterruptibleFFI.

Details from https://gitlab.haskell.org/ghc/ghc/issues/8684
and https://github.com/takano-akio/filelock/pull/7#discussion_r280332430

- - - - -
1b975aed by Andrew Martin at 2020-06-04T04:36:03-04:00
Allow finalizeForeignPtr to be called on FinalPtr/PlainPtr.

MR 2165 (commit 49301ad6226d9a83d110bee8c419615dd94f5ded) regressed
finalizeForeignPtr by throwing exceptions when PlainPtr was encounterd.
This regression did not make it into a release of GHC. Here, the
original behavior is restored, and FinalPtr is given the same treatment
as PlainPtr.

- - - - -
2bd3929a by Luke Lau at 2020-06-04T04:36:41-04:00
Fix documentation on type families not being extracted

It looks like the location of the Names used for CoAxioms on type
families are now located at their type constructors. Previously, Docs.hs
thought the Names were located in the RHS, so the RealSrcSpan in the
instanceMap and getInstLoc didn't match up. Fixes #18241

- - - - -
6735b9d9 by Ben Gamari at 2020-06-04T04:37:21-04:00
GHC.Hs.Instances: Compile with -O0

This module contains exclusively Data instances, which are going to be
slow no matter what we do. Furthermore, they are incredibly slow to
compile with optimisation (see #9557). Consequently we compile this with
-O0.  See #18254.

- - - - -
c330331a by nineonine at 2020-06-04T04:37:59-04:00
Add test for #17669

- - - - -
cab684f0 by Ben Gamari at 2020-06-04T04:38:36-04:00
rts: Add Windows-specific implementation of rtsSleep

Previously we would use the POSIX path, which uses `nanosleep`. However,
it turns out that `nanosleep` is provided by `libpthread` on Windows. In
general we don't want to incur such a dependency. Avoid this by simply
using `Sleep` on Windows.

Fixes #18272.

- - - - -
ad44b504 by Ben Gamari at 2020-06-04T04:38:36-04:00
compiler: Disable use of process jobs with process < 1.6.9

Due to #17926.

- - - - -
6a4098a4 by Moritz Angermann at 2020-06-04T04:55:51-04:00
[linker] Adds void printLoadedObjects(void);

This allows us to dump in-memory object code locations for debugging.

Fixup printLoadedObjects prototype

- - - - -
af5e3a88 by Artem Pelenitsyn at 2020-06-05T03:18:49-04:00
base: fix sign confusion in log1mexp implementation (fix #17125)

author: claude (https://gitlab.haskell.org/trac-claude)

The correct threshold for log1mexp is -(log 2) with the current specification
of log1mexp. This change improves accuracy for large negative inputs.

To avoid code duplication, a small helper function is added;
it isn't the default implementation in Floating because it needs Ord.

This patch does nothing to address that the Haskell specification is
different from that in common use in other languages.

- - - - -
2b792fac by Simon Peyton Jones at 2020-06-05T09:27:50-04:00
Simple subsumption

This patch simplifies GHC to use simple subsumption.
  Ticket #17775

Implements GHC proposal #287
   https://github.com/ghc-proposals/ghc-proposals/blob/master/
   proposals/0287-simplify-subsumption.rst

All the motivation is described there; I will not repeat it here.
The implementation payload:
 * tcSubType and friends become noticably simpler, because it no
   longer uses eta-expansion when checking subsumption.
 * No deeplyInstantiate or deeplySkolemise

That in turn means that some tests fail, by design; they can all
be fixed by eta expansion.  There is a list of such changes below.

Implementing the patch led me into a variety of sticky corners, so
the patch includes several othe changes, some quite significant:

* I made String wired-in, so that
    "foo" :: String   rather than
    "foo" :: [Char]
  This improves error messages, and fixes #15679

* The pattern match checker relies on knowing about in-scope equality
  constraints, andd adds them to the desugarer's environment using
  addTyCsDs.  But the co_fn in a FunBind was missed, and for some reason
  simple-subsumption ends up with dictionaries there. So I added a
  call to addTyCsDs.  This is really part of #18049.

* I moved the ic_telescope field out of Implication and into
  ForAllSkol instead.  This is a nice win; just expresses the code
  much better.

* There was a bug in GHC.Tc.TyCl.Instance.tcDataFamInstHeader.
  We called checkDataKindSig inside tc_kind_sig, /before/
  solveEqualities and zonking.  Obviously wrong, easily fixed.

* solveLocalEqualitiesX: there was a whole mess in here, around
  failing fast enough.  I discovered a bad latent bug where we
  could successfully kind-check a type signature, and use it,
  but have unsolved constraints that could fill in coercion
  holes in that signature --  aargh.

  It's all explained in Note [Failure in local type signatures]
  in GHC.Tc.Solver. Much better now.

* I fixed a serious bug in anonymous type holes. IN
    f :: Int -> (forall a. a -> _) -> Int
  that "_" should be a unification variable at the /outer/
  level; it cannot be instantiated to 'a'.  This was plain
  wrong.  New fields mode_lvl and mode_holes in TcTyMode,
  and auxiliary data type GHC.Tc.Gen.HsType.HoleMode.

  This fixes #16292, but makes no progress towards the more
  ambitious #16082

* I got sucked into an enormous refactoring of the reporting of
  equality errors in GHC.Tc.Errors, especially in
      mkEqErr1
      mkTyVarEqErr
      misMatchMsg
      misMatchMsgOrCND
  In particular, the very tricky mkExpectedActualMsg function
  is gone.

  It took me a full day.  But the result is far easier to understand.
  (Still not easy!)  This led to various minor improvements in error
  output, and an enormous number of test-case error wibbles.

  One particular point: for occurs-check errors I now just say
     Can't match 'a' against '[a]'
  rather than using the intimidating language of "occurs check".

* Pretty-printing AbsBinds

Tests review

* Eta expansions
   T11305: one eta expansion
   T12082: one eta expansion (undefined)
   T13585a: one eta expansion
   T3102:  one eta expansion
   T3692:  two eta expansions (tricky)
   T2239:  two eta expansions
   T16473: one eta
   determ004: two eta expansions (undefined)
   annfail06: two eta (undefined)
   T17923: four eta expansions (a strange program indeed!)
   tcrun035: one eta expansion

* Ambiguity check at higher rank.  Now that we have simple
  subsumption, a type like
     f :: (forall a. Eq a => Int) -> Int
  is no longer ambiguous, because we could write
     g :: (forall a. Eq a => Int) -> Int
     g = f
  and it'd typecheck just fine.  But f's type is a bit
  suspicious, and we might want to consider making the
  ambiguity check do a check on each sub-term.  Meanwhile,
  these tests are accepted, whereas they were previously
  rejected as ambiguous:
     T7220a
     T15438
     T10503
     T9222

* Some more interesting error message wibbles
   T13381: Fine: one error (Int ~ Exp Int)
           rather than two (Int ~ Exp Int, Exp Int ~ Int)
   T9834:  Small change in error (improvement)
   T10619: Improved
   T2414:  Small change, due to order of unification, fine
   T2534:  A very simple case in which a change of unification order
           means we get tow unsolved constraints instead of one
   tc211: bizarre impredicative tests; just accept this for now

Updates Cabal and haddock submodules.

Metric Increase:
  T12150
  T12234
  T5837
  haddock.base
Metric Decrease:
  haddock.compiler
  haddock.Cabal
  haddock.base

Merge note: This appears to break the
`UnliftedNewtypesDifficultUnification` test. It has been marked as
broken in the interest of merging.

(cherry picked from commit 66b7b195cb3dce93ed5078b80bf568efae904cc5)

- - - - -
2dff8141 by Ryan Scott at 2020-06-05T14:21:24-04:00
Simplify bindLHsTyVarBndrs and bindHsQTyVars

Both `bindLHsTyVarBndrs` and `bindHsQTyVars` take two separate
`Maybe` arguments, which I find terribly confusing. Thankfully, it's
possible to remove one `Maybe` argument from each of these functions,
which this patch accomplishes:

* `bindHsQTyVars` takes a `Maybe SDoc` argument, which is `Just` if
  GHC should warn about any of the quantified type variables going
  unused. However, every call site uses `Nothing` in practice. This
  makes sense, since it doesn't really make sense to warn about
  unused type variables bound by an `LHsQTyVars`. For instance, you
  wouldn't warn about the `a` in `data Proxy a = Proxy` going unused.

  As a result, I simply remove this `Maybe SDoc` argument altogether.
* `bindLHsTyVarBndrs` also takes a `Maybe SDoc` argument for the same
  reasons that `bindHsQTyVars` took one. To make things more
  confusing, however, `bindLHsTyVarBndrs` also takes a separate
  `HsDocContext` argument, which is pretty-printed (to an `SDoc`) in
  warnings and error messages.

  In practice, the `Maybe SDoc` and the `HsDocContext` often contain
  the same text. See the call sites for `bindLHsTyVarBndrs` in
  `rnFamInstEqn` and `rnConDecl`, for instance. There are only a
  handful of call sites where the text differs between the
  `Maybe SDoc` and `HsDocContext` arguments:

  * In `rnHsRuleDecl`, where the `Maybe SDoc` says "`In the rule`"
    and the `HsDocContext` says "`In the transformation rule`".
  * In `rnHsTyKi`/`rn_ty`, where the `Maybe SDoc` says
    "`In the type`" but the `HsDocContext` is inhereted from the
    surrounding context (e.g., if `rnHsTyKi` were called on a
    top-level type signature, the `HsDocContext` would be
    "`In the type signature`" instead)

  In both cases, warnings/error messages arguably _improve_ by
  unifying making the `Maybe SDoc`'s text match that of the
  `HsDocContext`. As a result, I decided to remove the `Maybe SDoc`
  argument to `bindLHsTyVarBndrs` entirely and simply reuse the text
  from the `HsDocContext`. (I decided to change the phrase
  "transformation rule" to "rewrite rule" while I was in the area.)

  The `Maybe SDoc` argument has one other purpose: signaling when to
  emit "`Unused quantified type variable`" warnings. To recover this
  functionality, I replaced the `Maybe SDoc` argument with a
  boolean-like `WarnUnusedForalls` argument. The only
  `bindLHsTyVarBndrs` call site that chooses _not_ to emit these
  warnings in `bindHsQTyVars`.

- - - - -
e372331b by Ben Gamari at 2020-06-07T08:46:41-04:00
hadrian: Add missing deriveConstants dependency on ghcplatform.h

deriveConstants wants to compile C sources which #include PosixSource.h,
which itself #includes ghcplatform.h. Make sure that Hadrian knows
about this dependency.

Fixes #18290.

- - - - -
b022051a by Moritz Angermann at 2020-06-07T08:46:42-04:00
ghc-prim needs to depend on libc and libm

libm is just an empty shell on musl, and all the math functions are contained in
libc.

- - - - -
6dae6548 by Moritz Angermann at 2020-06-07T08:46:42-04:00
Disable DLL loading if without system linker

Some platforms (musl, aarch64) do not have a working dynamic linker
implemented in the libc, even though we might see dlopen.  It will
ultimately just return that this is not supported.  Hence we'll add
a flag to the compiler to flat our disable loading dlls.  This is
needed as we will otherwise try to load the shared library even
if this will subsequently fail.  At that point we have given up
looking for static options though.

- - - - -
4a158ffc by Moritz Angermann at 2020-06-07T08:46:43-04:00
Range is actually +/-2^32, not +/-2^31

See also: https://static.docs.arm.com/ihi0056/g/aaelf64.pdf

- - - - -
f1bfb806 by Ben Gamari at 2020-06-07T10:49:30-04:00
OccurAnal: Avoid exponential behavior due to where clauses

Previously the `Var` case of `occAnalApp` could in some cases (namely
in the case of `runRW#` applications) call `occAnalRhs` two. In the case
of nested `runRW#`s this results in exponential complexity. In some
cases the compilation time that resulted would be very long indeed
(see #18296).

Fixes #18296.

Metric Decrease:
    T9961
    T12150
    T12234

- - - - -
9b607671 by Takenobu Tani at 2020-06-09T08:05:46-04:00
Add link to GHC's wiki in the GHC API header

This adds a URL to point to GHC's wiki in the GHC API header.
Newcomers could easily find more information from the GHC API's
web like [1].

[1]: Current version, https://ghc.gitlab.haskell.org/ghc/doc/libraries/ghc-8.11.0.20200604/index.html

[skip ci]

- - - - -
72c7fe9a by Ryan Scott at 2020-06-09T08:06:24-04:00
Make GADT constructors adhere to the forall-or-nothing rule properly

Issue #18191 revealed that the types of GADT constructors don't quite
adhere to the `forall`-or-nothing rule. This patch serves to clean up
this sad state of affairs somewhat. The main change is not in the
code itself, but in the documentation, as this patch introduces two
sections to the GHC User's Guide:

* A "Formal syntax for GADTs" section that presents a BNF-style
  grammar for what is and isn't allowed in GADT constructor types.
  This mostly exists to codify GHC's existing behavior, but it also
  imposes a new restriction that addresses #18191: the outermost
  `forall` and/or context in a GADT constructor is not allowed to be
  surrounded by parentheses. Doing so would make these
  `forall`s/contexts nested, and GADTs do not support nested
  `forall`s/contexts at present.

* A "`forall`-or-nothing rule" section that describes exactly what
  the `forall`-or-nothing rule is all about. Surprisingly, there was
  no mention of this anywhere in the User's Guide up until now!

To adhere the new specification in the "Formal syntax for GADTs"
section of the User's Guide, the following code changes were made:

* A new function, `GHC.Hs.Type.splitLHsGADTPrefixTy`, was introduced.
  This is very much like `splitLHsSigmaTy`, except that it avoids
  splitting apart any parentheses, which can be syntactically
  significant for GADT types. See
  `Note [No nested foralls or contexts in GADT constructors]` in
  `GHC.Hs.Type`.

* `ConDeclGADTPrefixPs`, an extension constructor for `XConDecl`, was
  introduced so that `GHC.Parser.PostProcess.mkGadtDecl` can return
  it when given a prefix GADT constructor. Unlike `ConDeclGADT`,
  `ConDeclGADTPrefixPs` does not split the GADT type into its argument
  and result types, as this cannot be done until after the type is
  renamed (see `Note [GADT abstract syntax]` in `GHC.Hs.Decls` for why
  this is the case).

* `GHC.Renamer.Module.rnConDecl` now has an additional case for
  `ConDeclGADTPrefixPs` that (1) splits apart the full `LHsType` into
  its `forall`s, context, argument types, and result type, and
  (2) checks for nested `forall`s/contexts. Step (2) used to be
  performed the typechecker (in `GHC.Tc.TyCl.badDataConTyCon`) rather
  than the renamer, but now the relevant code from the typechecker
  can simply be deleted.

  One nice side effect of this change is that we are able to give a
  more accurate error message for GADT constructors that use visible
  dependent quantification (e.g., `MkFoo :: forall a -> a -> Foo a`),
  which improves the stderr in the `T16326_Fail6` test case.

Fixes #18191. Bumps the Haddock submodule.

- - - - -
a47e6442 by Ryan Scott at 2020-06-10T03:39:12-04:00
Always use rnImplicitBndrs to bring implicit tyvars into scope

This implements a first step towards #16762 by changing the renamer
to always use `rnImplicitBndrs` to bring implicitly bound type
variables into scope. The main change is in `rnFamInstEqn` and
`bindHsQTyVars`, which previously used _ad hoc_ methods of binding
their implicit tyvars.

There are a number of knock-on consequences:

* One of the reasons that `rnFamInstEqn` used an _ad hoc_ binding
  mechanism was to give more precise source locations in
  `-Wunused-type-patterns` warnings. (See
  https://gitlab.haskell.org/ghc/ghc/issues/16762#note_273343 for an
  example of this.) However, these warnings are actually a little
  _too_ precise, since implicitly bound type variables don't have
  exact binding sites like explicitly bound type variables do.
  A similar problem existed for
  "`Different names for the same type variable`" errors involving
  implicit tyvars bound by `bindHsQTyVars`.
  Therefore, we simply accept the less precise (but more accurate)
  source locations from `rnImplicitBndrs` in `rnFamInstEqn` and
  `bindHsQTyVars`. See
  `Note [Source locations for implicitly bound type variables]` in
  `GHC.Rename.HsType` for the full story.
* In order for `rnImplicitBndrs` to work in `rnFamInstEqn`, it needs
  to be able to look up names from the parent class (in the event
  that we are renaming an associated type family instance). As a
  result, `rnImplicitBndrs` now takes an argument of type
  `Maybe assoc`, which is `Just` in the event that a type family
  instance is associated with a class.
* Previously, GHC kept track of three type synonyms for free type
  variables in the renamer: `FreeKiTyVars`, `FreeKiTyVarsDups`
  (which are allowed to contain duplicates), and
  `FreeKiTyVarsNoDups` (which contain no duplicates). However, making
  is a distinction between `-Dups` and `-NoDups` is now pointless, as
  all code that returns `FreeKiTyVars{,Dups,NoDups}` will eventually
  end up being passed to `rnImplicitBndrs`, which removes duplicates.
  As a result, I decided to just get rid of `FreeKiTyVarsDups` and
  `FreeKiTyVarsNoDups`, leaving only `FreeKiTyVars`.
* The `bindLRdrNames` and `deleteBys` functions are now dead code, so
  I took the liberty of removing them.

- - - - -
24879129 by Takenobu Tani at 2020-06-10T03:39:59-04:00
Clarify leaf module names for new module hierarchy

This updates comments only.

This patch replaces leaf module names according to new module
hierarchy [1][2] as followings:

* Expand leaf names to easily find the module path:
  for instance, `Id.hs` to `GHC.Types.Id`.

* Modify leaf names according to new module hierarchy:
  for instance, `Convert.hs` to `GHC.ThToHs`.

* Fix typo:
  for instance, `GHC.Core.TyCo.Rep.hs` to `GHC.Core.TyCo.Rep`

See also !3375

[1]: https://gitlab.haskell.org/ghc/ghc/-/wikis/Make-GHC-codebase-more-modular
[2]: https://gitlab.haskell.org/ghc/ghc/issues/13009

- - - - -
92de9e25 by Ömer Sinan Ağacan at 2020-06-10T03:41:07-04:00
rts: Remove unused GET_ENTRY closure macro

This macro is not used and got broken in the meantime, as ENTRY_CODE was
deleted.

- - - - -
87102928 by Ömer Sinan Ağacan at 2020-06-10T03:41:50-04:00
Fix -fkeep-cafs flag name in users guide

- - - - -
ccd6843d by Shayne Fletcher at 2020-06-10T04:14:57-04:00
Expose impliedGFlags, impledOffGFlags, impliedXFlags

- - - - -
7a737e89 by Ömer Sinan Ağacan at 2020-06-10T04:14:58-04:00
Cross-module LambdaFormInfo passing

- Store LambdaFormInfos of exported Ids in interface files
- Use them in importing modules

This is for optimization purposes: if we know LambdaFormInfo of imported
Ids we can generate more efficient calling code, see `getCallMethod`.

Exporting (putting them in interface files or in ModDetails) and
importing (reading them from interface files) are both optional. We
don't assume known LambdaFormInfos anywhere and do not change how we
call Ids with unknown LambdaFormInfos.

Runtime, allocation, and residency numbers when building
Cabal-the-library (commit 0d4ee7ba3):

(Log and .hp files are in the MR: !2842)

|     | GHC HEAD | This patch | Diff           |
|-----|----------|------------|----------------|
| -O0 |  0:35.89 |    0:34.10 | -1.78s, -4.98% |
| -O1 |  2:24.01 |    2:23.62 | -0.39s, -0.27% |
| -O2 |  2:52.23 |    2:51.35 | -0.88s, -0.51% |

|     | GHC HEAD        | This patch      | Diff                       |
|-----|-----------------|-----------------|----------------------------|
| -O0 |  54,843,608,416 |  54,878,769,544 |  +35,161,128 bytes, +0.06% |
| -O1 | 227,136,076,400 | 227,569,045,168 | +432,968,768 bytes, +0.19% |
| -O2 | 266,147,063,296 | 266,749,643,440 | +602,580,144 bytes, +0.22% |

NOTE: Residency is measured with extra runtime args: `-i0 -h` which effectively
turn all GCs into major GCs, and do GC more often.

|     | GHC HEAD                   | This patch                   | Diff                       |
|-----|----------------------------|------------------------------|----------------------------|
| -O0 | 410,284,000 (910 samples)  | 411,745,008 (906 samples)    | +1,461,008 bytes, +0.35%   |
| -O1 | 928,580,856 (2109 samples) | 943,506,552 (2103 samples)   | +14,925,696 bytes, +1.60%  |
| -O2 | 993,951,352 (2549 samples) | 1,010,156,328 (2545 samples) | +16,204,9760 bytes, +1.63% |

NoFib results:

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

Metric increases micro benchmarks tracked in #17686:

Metric Increase:
    T12150
    T12234
    T12425
    T13035
    T5837
    T6048
    T9233

Co-authored-by: Andreas Klebinger <klebinger.andreas at gmx.at>

- - - - -
3b22b14a by Shayne Fletcher at 2020-06-10T04:15:01-04:00
Give Language a Bounded instance

- - - - -
9454511b by Simon Peyton Jones at 2020-06-10T04:17:06-04:00
Optimisation in Unique.Supply

This patch switches on -fno-state-hack in GHC.Types.Unique.Supply.

It turned out that my fixes for #18078 (coercion floating) changed the
optimisation pathway for mkSplitUniqSupply in such a way that we had
an extra allocation inside the inner loop.  Adding -fno-state-hack
fixed that -- and indeed the loop in mkSplitUniqSupply is a classic
example of the way in which -fno-state-hack can be bad; see #18238.

Moreover, the new code is better than the old.  They allocate
the same, but the old code ends up with a partial application.
The net effect is that the test
    perf/should_run/UniqLoop
runs 20% faster!   From 2.5s down to 2.0s.  The allocation numbers
are the same -- but elapsed time falls. Good!

The bad thing about this is that it's terribly delicate.  But
at least it's a good example of such delicacy in action.

There is a long Note [Optimising the unique supply] which now
explains all this.

- - - - -
6d49d5be by Simon Peyton Jones at 2020-06-10T04:17:06-04:00
Implement cast worker/wrapper properly

The cast worker/wrapper transformation transforms
   x = e |> co
into
   y = e
   x = y |> co

This is done by the simplifier, but we were being
careless about transferring IdInfo from x to y,
and about what to do if x is a NOINLNE function.
This resulted in a series of bugs:
     #17673, #18093, #18078.

This patch fixes all that:

* Main change is in GHC.Core.Opt.Simplify, and
  the new prepareBinding function, which does this
  cast worker/wrapper transform.
  See Note [Cast worker/wrappers].

* There is quite a bit of refactoring around
  prepareRhs, makeTrivial etc.  It's nicer now.

* Some wrappers from strictness and cast w/w, notably those for
  a function with a NOINLINE, should inline very late. There
  wasn't really a mechanism for that, which was an existing bug
  really; so I invented a new finalPhase = Phase (-1).  It's used
  for all simplifier runs after the user-visible phase 2,1,0 have
  run.  (No new runs of the simplifier are introduced thereby.)

  See new Note [Compiler phases] in GHC.Types.Basic;
  the main changes are in GHC.Core.Opt.Driver

* Doing this made me trip over two places where the AnonArgFlag on a
  FunTy was being lost so we could end up with (Num a -> ty)
  rather than (Num a => ty)
    - In coercionLKind/coercionRKind
    - In contHoleType in the Simplifier

  I fixed the former by defining mkFunctionType and using it in
  coercionLKind/RKind.

  I could have done the same for the latter, but the information
  is almost to hand.  So I fixed the latter by
    - adding sc_hole_ty to ApplyToVal (like ApplyToTy),
    - adding as_hole_ty to ValArg (like TyArg)
    - adding sc_fun_ty to StrictArg
  Turned out I could then remove ai_type from ArgInfo.  This is
  just moving the deck chairs around, but it worked out nicely.

  See the new Note [AnonArgFlag] in GHC.Types.Var

* When looking at the 'arity decrease' thing (#18093) I discovered
  that stable unfoldings had a much lower arity than the actual
  optimised function.  That's what led to the arity-decrease
  message.  Simple solution: eta-expand.

  It's described in Note [Eta-expand stable unfoldings]
  in GHC.Core.Opt.Simplify

* I also discovered that unsafeCoerce wasn't being inlined if
  the context was boring.  So (\x. f (unsafeCoerce x)) would
  create a thunk -- yikes!  I fixed that by making inlineBoringOK
  a bit cleverer: see Note [Inline unsafeCoerce] in GHC.Core.Unfold.

  I also found that unsafeCoerceName was unused, so I removed it.

I made a test case for #18078, and a very similar one for #17673.

The net effect of all this on nofib is very modest, but positive:

--------------------------------------------------------------------------------
        Program           Size    Allocs   Runtime   Elapsed  TotalMem
--------------------------------------------------------------------------------
           anna          -0.4%     -0.1%     -3.1%     -3.1%      0.0%
 fannkuch-redux          -0.4%     -0.3%     -0.1%     -0.1%      0.0%
       maillist          -0.4%     -0.1%     -7.8%     -1.0%    -14.3%
      primetest          -0.4%    -15.6%     -7.1%     -6.6%      0.0%
--------------------------------------------------------------------------------
            Min          -0.9%    -15.6%    -13.3%    -14.2%    -14.3%
            Max          -0.3%      0.0%    +12.1%    +12.4%      0.0%
 Geometric Mean          -0.4%     -0.2%     -2.3%     -2.2%     -0.1%

All following metric decreases are compile-time allocation decreases
between -1% and -3%:

Metric Decrease:
  T5631
  T13701
  T14697
  T15164

- - - - -
32fd37f5 by Luke Lau at 2020-06-10T04:17:22-04:00
Fix lookupGlobalOccRn_maybe sometimes reporting an error

In some cases it was possible for lookupGlobalOccRn_maybe to return an
error, when it should be returning a Nothing. If it called
lookupExactOcc_either when there were no matching GlobalRdrElts in the
otherwise case, it would return an error message. This could be caused
when lookupThName_maybe in Template Haskell was looking in different
namespaces (thRdrNameGuesses), guessing different namespaces that the
name wasn't guaranteed to be found in.

However, by addressing this some more accurate errors were being lost in
the conversion to Maybes. So some of the lookup* functions have been
shuffled about so that errors should always be ignored in
lookup*_maybes, and propagated otherwise.

This fixes #18263

- - - - -
9b283e1b by Roland Senn at 2020-06-10T04:17:34-04:00
Initialize the allocation counter in GHCi to 0 (Fixes #16012)

According to the documentation for the function `getAllocationCounter` in
[System.Mem](http://hackage.haskell.org/package/base-4.14.0.0/docs/System-Mem.html)
initialize the allocationCounter also in GHCi to 0.

- - - - -
8d07c48c by Sylvain Henry at 2020-06-10T04:17:36-04:00
test: fix conc038

We had spurious failures of conc038 test on CI with stdout:

```
 newThread started
-mainThread
-Haskell: 2
 newThread back again
+mainThread
 1 sec later

 shutting down
+Haskell: 2
```

- - - - -
4c7e9689 by Sebastian Graf at 2020-06-11T10:37:38+02:00
Release Notes: Add news from the pattern-match checker [skip ci]

- - - - -
3445b965 by Sylvain Henry at 2020-06-13T02:13:01-04:00
Only test T16190 with the NCG

T16190 is meant to test a NCG feature. It has already caused spurious
failures in other MRs (e.g. !2165) when LLVM is used.

- - - - -
2517a51c by Sylvain Henry at 2020-06-13T02:13:01-04:00
DynFlags refactoring VIII (#17957)

* Remove several uses of `sdocWithDynFlags`, especially in GHC.Llvm.*

* Add LlvmOpts datatype to store Llvm backend options

* Remove Outputable instances (for LlvmVar, LlvmLit, LlvmStatic and
  Llvm.MetaExpr) which require LlvmOpts.

* Rename ppMetaExpr into ppMetaAnnotExpr (pprMetaExpr is now used in place of `ppr :: MetaExpr -> SDoc`)

- - - - -
7a02599a by Sylvain Henry at 2020-06-13T02:13:02-04:00
Remove unused code

- - - - -
72d08610 by Sylvain Henry at 2020-06-13T02:13:02-04:00
Refactor homeUnit

* rename thisPackage into homeUnit
* document and refactor several Backpack things

- - - - -
8dc71f55 by Sylvain Henry at 2020-06-13T02:13:02-04:00
Rename unsafeGetUnitInfo into unsafeLookupUnit

- - - - -
f6be6e43 by Sylvain Henry at 2020-06-13T02:13:02-04:00
Add allowVirtualUnits field in PackageState

Instead of always querying DynFlags to know whether we are allowed to
use virtual units (i.e. instantiated on-the-fly, cf Note [About units]
in GHC.Unit), we store it once for all in
`PackageState.allowVirtualUnits`.

This avoids using DynFlags too much (cf #17957) and is preliminary work
for #14335.

- - - - -
e7272d53 by Sylvain Henry at 2020-06-13T02:13:02-04:00
Enhance UnitId use

* use UnitId instead of String to identify wired-in units
* use UnitId instead of Unit in the backend (Unit are only use by
  Backpack to produce type-checked interfaces, not real code)
* rename lookup functions for consistency
* documentation

- - - - -
9c5572cd by Sylvain Henry at 2020-06-13T02:13:02-04:00
Remove LinkerUnitId type alias

- - - - -
d345edfe by Sylvain Henry at 2020-06-13T02:13:02-04:00
Refactor WiredMap

* Remove WiredInUnitId and WiredUnitId type aliases

- - - - -
3d171cd6 by Sylvain Henry at 2020-06-13T02:13:03-04:00
Document and refactor `mkUnit` and `mkUnitInfoMap`

- - - - -
d2109b4f by Sylvain Henry at 2020-06-13T02:13:03-04:00
Remove PreloadUnitId type alias

- - - - -
f50c19b8 by Sylvain Henry at 2020-06-13T02:13:03-04:00
Rename listUnitInfoMap into listUnitInfo

There is no Map involved

- - - - -
ed533ec2 by Sylvain Henry at 2020-06-13T02:13:03-04:00
Rename Package into Unit

The terminology changed over time and now package databases contain
"units" (there can be several units compiled from a single Cabal
package: one per-component, one for each option set, one per
instantiation, etc.). We should try to be consistent internally and use
"units": that's what this renaming does. Maybe one day we'll fix the UI
too (e.g. replace -package-id with -unit-id, we already have
-this-unit-id and ghc-pkg has -unit-id...) but it's not done in this
patch.

* rename getPkgFrameworkOpts into getUnitFrameworkOpts
* rename UnitInfoMap into ClosureUnitInfoMap
* rename InstalledPackageIndex into UnitInfoMap
* rename UnusablePackages into UnusableUnits
* rename PackagePrecedenceIndex into UnitPrecedenceMap
* rename PackageDatabase into UnitDatabase
* rename pkgDatabase into unitDatabases
* rename pkgState into unitState
* rename initPackages into initUnits
* rename renamePackage into renameUnitInfo
* rename UnusablePackageReason into UnusableUnitReason
* rename getPackage* into getUnit*
* etc.

- - - - -
202728e5 by Sylvain Henry at 2020-06-13T02:13:03-04:00
Make ClosureUnitInfoMap uses UnitInfoMap

- - - - -
55b4263e by Sylvain Henry at 2020-06-13T02:13:03-04:00
Remove ClosureUnitInfoMap

- - - - -
653d17bd by Sylvain Henry at 2020-06-13T02:13:03-04:00
Rename Package into Unit (2)

* rename PackageState into UnitState
* rename findWiredInPackages into findWiredInUnits
* rename lookupModuleInAll[Packages,Units]
* etc.

- - - - -
ae900605 by Sylvain Henry at 2020-06-13T02:13:03-04:00
Move dump_mod_map into initUnits

- - - - -
598cc1dd by Sylvain Henry at 2020-06-13T02:13:03-04:00
Move wiring of homeUnitInstantiations outside of mkUnitState

- - - - -
437265eb by Sylvain Henry at 2020-06-13T02:13:03-04:00
Avoid timing module map dump in initUnits

- - - - -
9400aa93 by Sylvain Henry at 2020-06-13T02:13:03-04:00
Remove preload parameter of mkUnitState

* Remove preload parameter (unused)
* Don't explicitly return preloaded units: redundant because already
  returned as "preloadUnits" field of UnitState

- - - - -
266bc3d9 by Sylvain Henry at 2020-06-13T02:13:03-04:00
DynFlags: refactor unwireUnit

- - - - -
9e715c1b by Sylvain Henry at 2020-06-13T02:13:03-04:00
Document getPreloadUnitsAnd

- - - - -
bd5810dc by Sylvain Henry at 2020-06-13T02:13:03-04:00
DynFlags: remove useless add_package parameter

- - - - -
36e1daf0 by Sylvain Henry at 2020-06-13T02:13:03-04:00
DynFlags: make listVisibleModuleNames take a UnitState

- - - - -
5226da37 by Sylvain Henry at 2020-06-13T02:13:03-04:00
Refactor and document add_package

- - - - -
4b53aac1 by Sylvain Henry at 2020-06-13T02:13:03-04:00
Refactor and document closeUnitDeps

- - - - -
42c054f6 by Sylvain Henry at 2020-06-13T02:13:03-04:00
DynFlags: findWiredInUnits

- - - - -
a444d01b by Sylvain Henry at 2020-06-13T02:13:03-04:00
DynFlags: reportCycles, reportUnusable

- - - - -
8408d521 by Sylvain Henry at 2020-06-13T02:13:03-04:00
DynFlags: merge_databases

- - - - -
fca2d25f by Sylvain Henry at 2020-06-13T02:13:03-04:00
DynFlags: add UnitConfig datatype

Avoid directly querying flags from DynFlags to build the UnitState.
Instead go via UnitConfig so that we could reuse this to make another
UnitState for plugins.

- - - - -
4274688a by Sylvain Henry at 2020-06-13T02:13:03-04:00
Move distrustAll into mkUnitState

- - - - -
28d804e1 by Sylvain Henry at 2020-06-13T02:13:03-04:00
Create helper upd_wired_in_home_instantiations

- - - - -
ac964c83 by Sylvain Henry at 2020-06-13T02:13:03-04:00
Put database cache in UnitConfig

- - - - -
bfd0a78c by Sylvain Henry at 2020-06-13T02:13:03-04:00
Don't return preload units when we set DyNFlags

Preload units can be retrieved in UnitState when needed (i.e. in GHCi)

- - - - -
1fbb4bf5 by Sylvain Henry at 2020-06-13T02:13:03-04:00
NCGConfig: remove useless ncgUnitId field

- - - - -
c10ff7e7 by Sylvain Henry at 2020-06-13T02:13:03-04:00
Doc: fix some comments

- - - - -
456e17f0 by Sylvain Henry at 2020-06-13T02:13:03-04:00
Bump haddock submodule and allow metric decrease

Metric Decrease:
    T12150
    T12234
    T5837

Metric Increase:
    T16190

- - - - -
42953902 by Simon Peyton Jones at 2020-06-13T02:13:03-04:00
Trim the demand for recursive product types

Ticket #18304 showed that we need to be very careful
when exploring the demand (esp usage demand) on recursive
product types.

This patch solves the problem by trimming the demand on such types --
in effect, a form of "widening".

See the Note [Trimming a demand to a type] in DmdAnal, which explains
how I did this by piggy-backing on an existing mechansim for trimming
demands becuase of GADTs.  The significant payload of this patch is
very small indeed:

* Make GHC.Core.Opt.WorkWrap.Utils.typeShape use RecTcChecker to
  avoid looking through recursive types.

But on the way

* I found that ae_rec_tc was entirely inoperative and did nothing.
  So I removed it altogether from DmdAnal.

* I moved some code around in DmdAnal and Demand.
  (There are no actual changes in dmdFix.)

* I changed the API of DmsAnal.dmdAnalRhsLetDown to return
  a StrictSig rather than a decorated Id

* I removed the dead function peelTsFuns from Demand

Performance effects:

Nofib: 0.0% changes.  Not surprising, because they don't
       use recursive products

Perf tests

T12227:
  1% increase in compiler allocation, becuase $cto gets w/w'd.
  It did not w/w before because it takes a deeply nested
  argument, so the worker gets too many args, so we abandon w/w
  altogether (see GHC.Core.Opt.WorkWrap.Utils.isWorkerSmallEnough)

  With this patch we trim the demands.  That is not strictly
  necessary (since these Generic type constructors are like
  tuples -- they can't cause a loop) but the net result is that
  we now w/w $cto which is fine.

UniqLoop:
  16% decrease in /runtime/ allocation. The UniqSupply is a
  recursive product, so currently we abandon all strictness on
  'churn'.  With this patch 'churn' gets useful strictness, and
  we w/w it.  Hooray

Metric Decrease:
    UniqLoop

Metric Increase:
    T12227

- - - - -
87d504f4 by Viktor Dukhovni at 2020-06-13T02:13:05-04:00
Add introductory prose for Data.Traversable

- - - - -
9f09b608 by Oleg Grenrus at 2020-06-13T02:13:07-04:00
Fix #12073: Add MonadFix Q instance

- - - - -
220c2d34 by Ben Gamari at 2020-06-13T02:13:07-04:00
testsuite: Increase size of T12150

As noted in #18319, this test was previously very fragile. Increase its
size to make it more likely that its fails with its newly-increased
acceptance threshold.

Metric Increase:
    T12150

- - - - -
8bba1c26 by Ben Gamari at 2020-06-13T04:59:06-04:00
gitlab-ci: Always push perf notes

Previously we ci.sh would run with `set -e` implying that we wouldn't
push perf notes if the testsuite were to fail, even if it *only* failed
due to perf notes. This rendered the whole performance testing story
quite fragile as a single regressing commit would cause every successive
commit to fail since a new baseline would not be uploaded.

Fix this by ensuring that we always push performance notes.

- - - - -
7a773f16 by Ben Gamari at 2020-06-13T15:10:55-04:00
gitlab-ci: Eliminate redundant push of CI metrics

- - - - -
a31218f7 by Ryan Scott at 2020-06-13T15:58:37-04:00
Use HsForAllTelescope to avoid inferred, visible foralls

Currently, `HsForAllTy` permits the combination of `ForallVis` and
`Inferred`, but you can't actually typecheck code that uses it
(e.g., `forall {a} ->`). This patch refactors `HsForAllTy` to use a
new `HsForAllTelescope` data type that makes a type-level distinction
between visible and invisible `forall`s such that visible `forall`s
do not track `Specificity`. That part of the patch is actually quite
small; the rest is simply changing consumers of `HsType` to
accommodate this new type.

Fixes #18235. Bumps the `haddock` submodule.

- - - - -
c0e6dee9 by Tamar Christina at 2020-06-14T09:07:44-04:00
winio: Add Atomic Exchange PrimOp and implement Atomic Ptr exchanges.

The initial version was rewritten by Tamar Christina.
It was rewritten in large parts by Andreas Klebinger.

Co-authored-by: Andreas Klebinger <klebinger.andreas at gmx.at>

- - - - -
9a7462fb by Ben Gamari at 2020-06-14T15:35:23-04:00
codeGen: Don't discard live case binders in unsafeEqualityProof logic

Previously CoreToStg would unconditionally discard cases of the form:

    case unsafeEqualityProof of wild { _ -> rhs }

and rather replace the whole thing with `rhs`. However, in some cases
(see #18227) the case binder is still live, resulting in unbound
occurrences in `rhs`. Fix this by only discarding the case if the case
binder is dead.

Fixes #18227.

- - - - -
e4137c48 by Ben Gamari at 2020-06-14T15:35:23-04:00
testsuite: Add tests for #18227

T18227A is the original issue which gave rise to the ticket and depends
upon bytestring. T18227B is a minimized reproducer.

- - - - -
8bab9ff1 by Ben Gamari at 2020-06-14T15:35:59-04:00
hadrian: Fix rts include and library paths

Fixes two bugs:

 * (?) and (<>) associated in a surprising way
 * We neglected to include libdw paths in the rts configure flags

- - - - -
bd761185 by Ben Gamari at 2020-06-14T15:35:59-04:00
hadrian: Drop redundant GHC arguments

Cabal should already be passing this arguments to GHC.

- - - - -
01f7052c by Peter Trommler at 2020-06-14T15:36:38-04:00
FFI: Fix pass small ints in foreign call wrappers

The Haskell calling convention requires integer parameters smaller
than wordsize to be promoted to wordsize (where the upper bits are
don't care). To access such small integer parameter read a word from
the parameter array and then cast that word to the small integer
target type.

Fixes #15933

- - - - -
502647f7 by Krzysztof Gogolewski at 2020-06-14T15:37:14-04:00
Fix "ndecreasingIndentation" in manual (#18116)

- - - - -
9a9cc089 by Simon Jakobi at 2020-06-15T13:10:00-04:00
Use foldl' in unionManyUniqDSets

- - - - -
761dcb84 by Moritz Angermann at 2020-06-15T13:10:36-04:00
Load .lo as well.

Some archives contain so called linker objects, with the affectionate
.lo suffic.  For example the musl libc.a will come in that form.  We
still want to load those objects, hence we should not discard them and
look for .lo as well.  Ultimately we might want to fix this proerly by
looking at the file magic.

- - - - -
cf01477f by Vladislav Zavialov at 2020-06-15T13:11:20-04:00
User's Guide: KnownNat evidence is Natural

This bit of documentation got outdated after commit
1fcede43d2b30f33b7505e25eb6b1f321be0407f

- - - - -
d0dcbfe6 by Jan Hrček at 2020-06-16T20:36:38+02:00
Fix typos and formatting in user guide

- - - - -
56a9e95f by Jan Hrček at 2020-06-16T20:36:38+02:00
Resolve TODO

- - - - -
3e884d14 by Jan Hrček at 2020-06-16T20:36:38+02:00
Rename TcHoleErrors to GHC.Tc.Errors.Hole

- - - - -
d23fc678 by Stefan Schulze Frielinghaus at 2020-06-17T15:31:09-04:00
hadrian: Build with threaded runtime if available

See #16873.

- - - - -
0639dc10 by Sylvain Henry at 2020-06-17T15:31:53-04:00
T16190: only measure bytes_allocated

Just adding `{-# LANGUAGE BangPatterns #-}` makes the two other metrics
fluctuate by 13%.

- - - - -
4cab6897 by Adam Sandberg Ericsson at 2020-06-17T15:32:44-04:00
docs: fix formatting in users guide

- - - - -
eb8115a8 by Sylvain Henry at 2020-06-17T15:33:23-04:00
Move CLabel assertions into smart constructors (#17957)

It avoids using DynFlags in the Outputable instance of Clabel to check
assertions at pretty-printing time.

- - - - -
7faa4509 by Ben Gamari at 2020-06-17T15:43:31-04:00
base: Bump to 4.15.0.0

- - - - -
20616959 by Ben Gamari at 2020-06-17T15:43:31-04:00
configure: Use grep -q instead of --quiet

The latter is apparently not supported by busybox.

- - - - -
40fa237e by Krzysztof Gogolewski at 2020-06-17T16:21:58-04:00
Linear types (#15981)

This is the first step towards implementation of the linear types proposal
(https://github.com/ghc-proposals/ghc-proposals/pull/111).

It features

* A language extension -XLinearTypes
* Syntax for linear functions in the surface language
* Linearity checking in Core Lint, enabled with -dlinear-core-lint
* Core-to-core passes are mostly compatible with linearity
* Fields in a data type can be linear or unrestricted; linear fields
  have multiplicity-polymorphic constructors.
  If -XLinearTypes is disabled, the GADT syntax defaults to linear fields

The following items are not yet supported:

* a # m -> b syntax (only prefix FUN is supported for now)
* Full multiplicity inference (multiplicities are really only checked)
* Decent linearity error messages
* Linear let, where, and case expressions in the surface language
  (each of these currently introduce the unrestricted variant)
* Multiplicity-parametric fields
* Syntax for annotating lambda-bound or let-bound with a multiplicity
* Syntax for non-linear/multiple-field-multiplicity records
* Linear projections for records with a single linear field
* Linear pattern synonyms
* Multiplicity coercions (test LinearPolyType)

A high-level description can be found at
https://ghc.haskell.org/trac/ghc/wiki/LinearTypes/Implementation
Following the link above you will find a description of the changes made to Core.
This commit has been authored by

* Richard Eisenberg
* Krzysztof Gogolewski
* Matthew Pickering
* Arnaud Spiwack

With contributions from:

* Mark Barbone
* Alexander Vershilov

Updates haddock submodule.

- - - - -
6cb84c46 by Krzysztof Gogolewski at 2020-06-17T16:22:03-04:00
Various performance improvements

This implements several general performance improvements to GHC,
to offset the effect of the linear types change.

General optimisations:
- Add a `coreFullView` function which iterates `coreView` on the
  head. This avoids making function recursive solely because the
  iterate `coreView` themselves. As a consequence, this functions can
  be inlined, and trigger case-of-known constructor (_e.g._
  `kindRep_maybe`, `isLiftedRuntimeRep`, `isMultiplicityTy`,
  `getTyVar_maybe`, `splitAppTy_maybe`, `splitFunType_maybe`,
  `tyConAppTyCon_maybe`). The common pattern about all these functions
  is that they are almost always used as views, and immediately
  consumed by a case expression. This commit also mark them asx `INLINE`.
- In `subst_ty` add a special case for nullary `TyConApp`, which avoid
  allocations altogether.
- Use `mkTyConApp` in `subst_ty` for the general `TyConApp`. This
  required quite a bit of module shuffling.
  case. `myTyConApp` enforces crucial sharing, which was lost during
  substitution. See also !2952 .
- Make `subst_ty` stricter.
- In `eqType` (specifically, in `nonDetCmpType`), add a special case,
  tested first, for the very common case of nullary `TyConApp`.
  `nonDetCmpType` has been made `INLINE` otherwise it is actually a
  regression. This is similar to the optimisations in !2952.

Linear-type specific optimisations:
- Use `tyConAppTyCon_maybe` instead of the more complex `eqType` in
  the definition of the pattern synonyms `One` and `Many`.
- Break the `hs-boot` cycles between `Multiplicity.hs` and `Type.hs`:
  `Multiplicity` now import `Type` normally, rather than from the
  `hs-boot`. This way `tyConAppTyCon_maybe` can inline properly in the
  `One` and `Many` pattern synonyms.
- Make `updateIdTypeAndMult` strict in its type and multiplicity
- The `scaleIdBy` gets a specialised definition rather than being an
  alias to `scaleVarBy`
- `splitFunTy_maybe` is given the type `Type -> Maybe (Mult, Type,
  Type)` instead of `Type -> Maybe (Scaled Type, Type)`
- Remove the `MultMul` pattern synonym in favour of a view `isMultMul`
  because pattern synonyms appear not to inline well.
- in `eqType`, in a `FunTy`, compare multiplicities last: they are
  almost always both `Many`, so it helps failing faster.
- Cache `manyDataConTy` in `mkTyConApp`, to make sure that all the
  instances of `TyConApp ManyDataConTy []` are physically the same.

This commit has been authored by
* Richard Eisenberg
* Krzysztof Gogolewski
* Arnaud Spiwack

Metric Decrease:
    haddock.base
    T12227
    T12545
    T12990
    T1969
    T3064
    T5030
    T9872b

Metric Increase:
    haddock.base
    haddock.Cabal
    haddock.compiler
    T12150
    T12234
    T12425
    T12707
    T13035
    T13056
    T15164
    T16190
    T18304
    T1969
    T3064
    T3294
    T5631
    T5642
    T5837
    T6048
    T9020
    T9233
    T9675
    T9872a
    T9961
    WWRec

- - - - -
57db91d8 by Sylvain Henry at 2020-06-17T16:22:03-04:00
Remove integer-simple

integer-simple uses lists of words (`[Word]`) to represent big numbers
instead of ByteArray#:

   * it is less efficient than the newer ghc-bignum native backend

   * it isn't compatible with the big number representation that is now
     shared by all the ghc-bignum backends (based on the one that was
     used only in integer-gmp before).

As a consequence, we simply drop integer-simple

- - - - -
9f96bc12 by Sylvain Henry at 2020-06-17T16:22:03-04:00
ghc-bignum library

ghc-bignum is a newer package that aims to replace the legacy
integer-simple and integer-gmp packages.

* it supports several backends. In particular GMP is still supported and
  most of the code from integer-gmp has been merged in the "gmp"
  backend.

* the pure Haskell "native" backend is new and is much faster than the
  previous pure Haskell implementation provided by integer-simple

* new backends are easier to write because they only have to provide a
  few well defined functions. All the other code is common to all
  backends. In particular they all share the efficient small/big number
  distinction previously used only in integer-gmp.

* backends can all be tested against the "native" backend with a simple
  Cabal flag. Backends are only allowed to differ in performance, their
  results should be the same.

* Add `integer-gmp` compat package: provide some pattern synonyms and
  function aliases for those in `ghc-bignum`. It is intended to avoid
  breaking packages that depend on `integer-gmp` internals.

Update submodules: text, bytestring

Metric Decrease:
    Conversions
    ManyAlternatives
    ManyConstructors
    Naperian
    T10359
    T10547
    T10678
    T12150
    T12227
    T12234
    T12425
    T13035
    T13719
    T14936
    T1969
    T4801
    T4830
    T5237
    T5549
    T5837
    T8766
    T9020
    parsing001
    space_leak_001
    T16190
    haddock.base

On ARM and i386, T17499 regresses (+6% > 5%).
On x86_64 unregistered, T13701 sometimes regresses (+2.2% > 2%).

Metric Increase:
    T17499
    T13701

- - - - -
96aa5787 by Sylvain Henry at 2020-06-17T16:22:03-04:00
Update compiler

Thanks to ghc-bignum, the compiler can be simplified:

* Types and constructors of Integer and Natural can be wired-in. It
  means that we don't have to query them from interfaces. It also means
  that numeric literals don't have to carry their type with them.

* The same code is used whatever ghc-bignum backend is enabled. In
  particular, conversion of bignum literals into final Core expressions
  is now much more straightforward. Bignum closure inspection too.

* GHC itself doesn't depend on any integer-* package anymore

* The `integerLibrary` setting is gone.

- - - - -
0f67e344 by Sylvain Henry at 2020-06-17T16:22:03-04:00
Update `base` package

* GHC.Natural isn't implemented in `base` anymore. It is provided by
  ghc-bignum in GHC.Num.Natural. It means that we can safely use Natural
  primitives in `base` without fearing issues with built-in rewrite
  rules (cf #15286)

* `base` doesn't conditionally depend on an integer-* package anymore,
  it depends on ghc-bignum

* Some duplicated code in integer-* can now be factored in GHC.Float

* ghc-bignum tries to use a uniform naming convention so most of the
  other changes are renaming

- - - - -
aa9e7b71 by Sylvain Henry at 2020-06-17T16:22:03-04:00
Update `make` based build system

* replace integer-* package selection with ghc-bignum backend selection

- - - - -
f817d816 by Sylvain Henry at 2020-06-17T16:22:04-04:00
Update testsuite

* support detection of slow ghc-bignum backend (to replace the detection
  of integer-simple use). There are still some test cases that the
  native backend doesn't handle efficiently enough.

* remove tests for GMP only functions that have been removed from
  ghc-bignum

* fix test results showing dependent packages (e.g. integer-gmp) or
  showing suggested instances

* fix test using Integer/Natural API or showing internal names

- - - - -
dceecb09 by Sylvain Henry at 2020-06-17T16:22:04-04:00
Update Hadrian

* support ghc-bignum backend selection in flavours and command-line

* support ghc-bignum "--check" flag (compare results of selected backend
  against results of the native one) in flavours and command-line (e.g.
  pass --bignum=check-gmp" to check the "gmp" backend)

* remove the hack to workaround #15286

* build GMP only when the gmp backend is used

* remove hacks to workaround `text` package flags about integer-*. We
  fix `text` to use ghc-bignum unconditionally in another patch

- - - - -
fa4281d6 by Sylvain Henry at 2020-06-17T16:22:04-04:00
Bump bytestring and text submodules

- - - - -
5526ecc0 by Ben Gamari at 2020-06-24T02:04:59+00:00
rts: Post ticky entry counts to the eventlog

We currently only post the entry counters, not the other global
counters as in my experience the former are more useful. We use the heap
profiler's census period to decide when to dump.

- - - - -


30 changed files:

- .gitlab-ci.yml
- .gitlab/ci.sh
- .gitmodules
- aclocal.m4
- 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/Prim.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/Linker.hs
- compiler/GHC/Cmm.hs
- compiler/GHC/Cmm/CLabel.hs
- compiler/GHC/Cmm/DebugBlock.hs
- compiler/GHC/Cmm/LayoutStack.hs
- compiler/GHC/Cmm/MachOp.hs
- compiler/GHC/Cmm/Node.hs
- compiler/GHC/Cmm/Parser.y
- compiler/GHC/Cmm/Ppr.hs
- compiler/GHC/Cmm/Ppr/Expr.hs
- compiler/GHC/Cmm/ProcPoint.hs
- compiler/GHC/Cmm/Utils.hs
- compiler/GHC/CmmToAsm.hs
- compiler/GHC/CmmToAsm/CFG.hs
- compiler/GHC/CmmToAsm/CPrim.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/a6ec2bb3f31837896cd0ef17efb9c0c7845033e6...5526ecc0f6a0922e483f8a2fc3af77b102ac4e17

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/a6ec2bb3f31837896cd0ef17efb9c0c7845033e6...5526ecc0f6a0922e483f8a2fc3af77b102ac4e17
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/20200623/cfd00dc1/attachment-0001.html>


More information about the ghc-commits mailing list