[Git][ghc/ghc][wip/explicit-perf-baseline] 238 commits: ghc-prim: Turn some comments into haddocks

Ben Gamari gitlab at gitlab.haskell.org
Mon Jul 27 20:20:46 UTC 2020



Ben Gamari pushed to branch wip/explicit-perf-baseline at Glasgow Haskell Compiler / GHC


Commits:
e61d5395 by Chaitanya Koparkar at 2020-07-07T13:55:59-04:00
ghc-prim: Turn some comments into haddocks

[ci skip]

- - - - -
37743f91 by John Ericson at 2020-07-07T13:56:00-04:00
Support `timesInt2#` in LLVM backend

- - - - -
46397e53 by John Ericson at 2020-07-07T13:56:00-04:00
`genericIntMul2Op`: Call `genericWordMul2Op` directly

This unblocks a refactor, and removes partiality. It might be a PowerPC
regression but that should be fixable.

- - - - -
8a1c0584 by John Ericson at 2020-07-07T13:56:00-04:00
Simplify `PrimopCmmEmit`

Follow @simonpj's suggestion of pushing the "into regs" logic into
`emitPrimOp`. With the previous commit getting rid of the recursion in
`genericIntMul2Op`, this is now an easy refactor.

- - - - -
6607f203 by John Ericson at 2020-07-07T13:56:00-04:00
`opAllDone` -> `opIntoRegs`

The old name was and terrible and became worse after the previous
commit's refactor moved non-trivial funcationlity into its body.

- - - - -
fdcc53ba by Sylvain Henry at 2020-07-07T13:56:00-04:00
Optimise genericIntMul2Op

We shouldn't directly call 'genericWordMul2Op' in genericIntMul2Op
because a target may provide a faster primop for 'WordMul2Op': we'd
better use it!

- - - - -
686e7225 by Moritz Angermann at 2020-07-07T13:56:01-04:00
[linker/rtsSymbols] More linker symbols

Mostly symbols needed for aarch64/armv7l
and in combination with musl, where we have
to rely on loading *all* objects/archives

- __stack_chk_* only when not DYNAMIC

- - - - -
3f60b94d by Moritz Angermann at 2020-07-07T13:56:01-04:00
better if guards.

- - - - -
7abffced by Moritz Angermann at 2020-07-07T13:56:01-04:00
Fix (1)

- - - - -
cdfeb3f2 by Moritz Angermann at 2020-07-07T13:56:01-04:00
AArch32 symbols only on aarch32.

- - - - -
f496c955 by Adam Sandberg Ericsson at 2020-07-07T13:56:02-04:00
add -flink-rts flag to link the rts when linking a shared or static library #18072

By default we don't link the RTS when linking shared libraries because in the
most usual mode a shared library is an intermediary product, for example a
Haskell library, that will be linked into some executable in the end. So we
wish to defer the RTS flavour to link to the final link.

However sometimes the final product is the shared library, for example when
writing a plugin for some other system, so we do wish the shared library to
link the RTS.

For consistency we also make -staticlib honor this flag and its inversion.
-staticlib currently implies -flink-shared.

- - - - -
c59faf67 by Stefan Schulze Frielinghaus at 2020-07-07T13:56:04-04:00
hadrian: link check-ppr against debugging RTS if ghcDebugged

- - - - -
0effc57d by Adam Sandberg Ericsson at 2020-07-07T13:56:05-04:00
rts linker: teach the linker about GLIBC's special handling of *stat, mknod and atexit functions #7072

- - - - -
96153433 by Adam Sandberg Ericsson at 2020-07-07T13:56:06-04:00
hadrian: make hadrian/ghci use the bootstrap compiler from configure #18190

- - - - -
4d24f886 by Adam Sandberg Ericsson at 2020-07-07T13:56:07-04:00
hadrian: ignore cabal configure verbosity related flags #18131

- - - - -
7332bbff by Ben Gamari at 2020-07-07T13:56:08-04:00
testsuite: Widen T12234 acceptance window to 2%

Previously it wasn't uncommon to see +/-1% fluctuations in compiler
allocations on this test.

- - - - -
180b6313 by Gabor Greif at 2020-07-07T13:56:08-04:00
When running libtool, report it as such
- - - - -
d3bd6897 by Sylvain Henry at 2020-07-07T13:56:11-04:00
BigNum: rename BigNat types

Before this patch BigNat names were confusing because we had:

* GHC.Num.BigNat.BigNat: unlifted type used everywhere else
* GHC.Num.BigNat.BigNatW: lifted type only used to share static constants
* GHC.Natural.BigNat: lifted type only used for backward compatibility

After this patch we have:

* GHC.Num.BigNat.BigNat#: unlifted type
* GHC.Num.BigNat.BigNat: lifted type (reexported from GHC.Natural)

Thanks to @RyanGlScott for spotting this.

- - - - -
929d26db by Sylvain Henry at 2020-07-07T13:56:12-04:00
Bignum: don't build ghc-bignum with stage0

Noticed by @Ericson2314

- - - - -
d25b6851 by Sylvain Henry at 2020-07-07T13:56:12-04:00
Hadrian: ghc-gmp.h shouldn't be a compiler dependency

- - - - -
0ddae2ba by Sylvain Henry at 2020-07-07T13:56:14-04:00
DynFlags: factor out pprUnitId from "Outputable UnitId" instance

- - - - -
204f3f5d by Krzysztof Gogolewski at 2020-07-07T13:56:18-04:00
Remove unused function pprHsForAllExtra (#18423)

The function `pprHsForAllExtra` was called only on `Nothing`
since 2015 (1e041b7382b6aa).

- - - - -
3033e0e4 by Adam Sandberg Ericsson at 2020-07-08T20:36:49-04:00
hadrian: add flag to skip rebuilding dependency information #17636

- - - - -
b7de4b96 by Stefan Schulze Frielinghaus at 2020-07-09T09:49:22-04:00
Fix GHCi :print on big-endian platforms

On big-endian platforms executing

  import GHC.Exts
  data Foo = Foo Float# deriving Show
  foo = Foo 42.0#
  foo
  :print foo

results in an arithmetic overflow exception which is caused by function
index where moveBytes equals
  word_size - (r + item_size_b) * 8
Here we have a mixture of units. Both, word_size and item_size_b have
unit bytes whereas r has unit bits.  On 64-bit platforms moveBytes
equals then
  8 - (0 + 4) * 8
which results in a negative and therefore invalid second parameter for a
shiftL operation.

In order to make things more clear the expression
  (word .&. (mask `shiftL` moveBytes)) `shiftR` moveBytes
is equivalent to
  (word `shiftR` moveBytes) .&. mask
On big-endian platforms the shift must be a left shift instead of a
right shift. For symmetry reasons not a mask is used but two shifts in
order to zero out bits. Thus the fixed version equals
  case endian of
    BigEndian    -> (word `shiftL` moveBits) `shiftR` zeroOutBits `shiftL` zeroOutBits
    LittleEndian -> (word `shiftR` moveBits) `shiftL` zeroOutBits `shiftR` zeroOutBits

Fixes #16548 and #14455

- - - - -
3656dff8 by Sylvain Henry at 2020-07-09T09:50:01-04:00
LLVM: fix MO_S_Mul2 support (#18434)

The value indicating if the carry is useful wasn't taken into account.

- - - - -
d9f09506 by Simon Peyton Jones at 2020-07-10T10:33:44-04:00
Define multiShotIO and use it in mkSplitUniqueSupply

This patch is part of the ongoing eta-expansion saga;
see #18238.

It implements a neat trick (suggested by Sebastian Graf)
that allows the programmer to disable the default one-shot behaviour
of IO (the "state hack").  The trick is to use a new multiShotIO
function; see Note [multiShotIO].  For now, multiShotIO is defined
here in Unique.Supply; but it should ultimately be moved to the IO
library.

The change is necessary to get good code for GHC's unique supply;
see Note [Optimising the unique supply].

However it makes no difference to GHC as-is.  Rather, it makes
a difference when a subsequent commit

   Improve eta-expansion using ArityType

lands.

- - - - -
bce695cc by Simon Peyton Jones at 2020-07-10T10:33:44-04:00
Make arityType deal with join points

As Note [Eta-expansion and join points] describes,
this patch makes arityType deal correctly with join points.
What was there before was not wrong, but yielded lower
arities than it could.

Fixes #18328

In base GHC this makes no difference to nofib.

        Program           Size    Allocs   Runtime   Elapsed  TotalMem
--------------------------------------------------------------------------------
         n-body          -0.1%     -0.1%     -1.2%     -1.1%      0.0%
--------------------------------------------------------------------------------
            Min          -0.1%     -0.1%    -55.0%    -56.5%      0.0%
            Max          -0.0%      0.0%    +16.1%    +13.4%      0.0%
 Geometric Mean          -0.0%     -0.0%    -30.1%    -31.0%     -0.0%

But it starts to make real difference when we land the change to the
way mkDupableAlts handles StrictArg, in fixing #13253 and friends.
I think this is because we then get more non-inlined join points.

- - - - -
2b7c71cb by Simon Peyton Jones at 2020-07-11T12:17:02-04:00
Improve eta-expansion using ArityType

As #18355 shows, we were failing to preserve one-shot info when
eta-expanding.  It's rather easy to fix, by using ArityType more,
rather than just Arity.

This patch is important to suport the one-shot monad trick;
see #18202.  But the extra tracking of one-shot-ness requires
the patch

   Define multiShotIO and use it in mkSplitUniqueSupply

If that patch is missing, ths patch makes things worse in
GHC.Types.Uniq.Supply.  With it, however, we see these improvements

    T3064     compiler bytes allocated -2.2%
    T3294     compiler bytes allocated -1.3%
    T12707    compiler bytes allocated -1.3%
    T13056    compiler bytes allocated -2.2%

Metric Decrease:
    T3064
    T3294
    T12707
    T13056

- - - - -
de139cc4 by Artem Pelenitsyn at 2020-07-12T02:53:20-04:00
add reproducer for #15630

- - - - -
c4de6a7a by Andreas Klebinger at 2020-07-12T02:53:55-04:00
Give Uniq[D]FM a phantom type for its key.

This fixes #17667 and should help to avoid such issues going forward.

The changes are mostly mechanical in nature. With two notable
exceptions.

* The register allocator.

  The register allocator references registers by distinct uniques.
  However they come from the types of VirtualReg, Reg or Unique in
  various places. As a result we sometimes cast the key type of the
  map and use functions which operate on the now typed map but take
  a raw Unique as actual key. The logic itself has not changed it
  just becomes obvious where we do so now.

* <Type>Env Modules.

As an example a ClassEnv is currently queried using the types `Class`,
`Name`, and `TyCon`. This is safe since for a distinct class value all
these expressions give the same unique.

    getUnique cls
    getUnique (classTyCon cls)
    getUnique (className cls)
    getUnique (tcName $ classTyCon cls)

This is for the most part contained within the modules defining the
interface. However it requires us to play dirty when we are given a
`Name` to lookup in a `UniqFM Class a` map. But again the logic did
not change and it's for the most part hidden behind the Env Module.

Some of these cases could be avoided by refactoring but this is left
for future work.

We also bump the haddock submodule as it uses UniqFM.

- - - - -
c2cfdfde by Aaron Allen at 2020-07-13T09:00:33-04:00
Warn about empty Char enumerations (#18402)

Currently the "Enumeration is empty" warning (-Wempty-enumerations)
only fires for numeric literals. This patch adds support for `Char`
literals so that enumerating an empty list of `Char`s will also
trigger the warning.

- - - - -
c3ac87ec by Stefan Schulze Frielinghaus at 2020-07-13T09:01:10-04:00
hadrian: build check-ppr dynamic if GHC is build dynamic

Fixes #18361

- - - - -
9ad072b4 by Simon Peyton Jones at 2020-07-13T14:52:49-04:00
Use dumpStyle when printing inlinings

This just makes debug-printing consistent,
and more informative.

- - - - -
e78c4efb by Simon Peyton Jones at 2020-07-13T14:52:49-04:00
Comments only

- - - - -
7ccb760b by Simon Peyton Jones at 2020-07-13T14:52:49-04:00
Reduce result discount in conSize

Ticket #18282 showed that the result discount given by conSize
was massively too large.  This patch reduces that discount to
a constant 10, which just balances the cost of the constructor
application itself.

Note [Constructor size and result discount] elaborates, as
does the ticket #18282.

Reducing result discount reduces inlining, which affects perf.  I
found that I could increase the unfoldingUseThrehold from 80 to 90 in
compensation; in combination with the result discount change I get
these overall nofib numbers:

        Program           Size    Allocs   Runtime   Elapsed  TotalMem
--------------------------------------------------------------------------------
          boyer          -0.2%     +5.4%     -3.2%     -3.4%      0.0%
       cichelli          -0.1%     +5.9%    -11.2%    -11.7%      0.0%
      compress2          -0.2%     +9.6%     -6.0%     -6.8%      0.0%
   cryptarithm2          -0.1%     -3.9%     -6.0%     -5.7%      0.0%
         gamteb          -0.2%     +2.6%    -13.8%    -14.4%      0.0%
         genfft          -0.1%     -1.6%    -29.5%    -29.9%      0.0%
             gg          -0.0%     -2.2%    -17.2%    -17.8%    -20.0%
           life          -0.1%     -2.2%    -62.3%    -63.4%      0.0%
           mate          +0.0%     +1.4%     -5.1%     -5.1%    -14.3%
         parser          -0.2%     -2.1%     +7.4%     +6.7%      0.0%
      primetest          -0.2%    -12.8%    -14.3%    -14.2%      0.0%
         puzzle          -0.2%     +2.1%    -10.0%    -10.4%      0.0%
            rsa          -0.2%    -11.7%     -3.7%     -3.8%      0.0%
         simple          -0.2%     +2.8%    -36.7%    -38.3%     -2.2%
   wheel-sieve2          -0.1%    -19.2%    -48.8%    -49.2%    -42.9%
--------------------------------------------------------------------------------
            Min          -0.4%    -19.2%    -62.3%    -63.4%    -42.9%
            Max          +0.3%     +9.6%     +7.4%    +11.0%    +16.7%
 Geometric Mean          -0.1%     -0.3%    -17.6%    -18.0%     -0.7%

I'm ok with these numbers, remembering that this change removes
an *exponential* increase in code size in some in-the-wild cases.

I investigated compress2.  The difference is entirely caused by this
function no longer inlining

WriteRoutines.$woutputCodes
  = \ (w :: [CodeEvent]) ->
      let result_s1Sr
            = case WriteRoutines.outputCodes_$s$woutput w 0# 0# 8# 9# of
                (# ww1, ww2 #) -> (ww1, ww2)
      in (# case result_s1Sr of (x, _) ->
              map @Int @Char WriteRoutines.outputCodes1 x
         , case result_s1Sr of { (_, y) -> y } #)

It was right on the cusp before, driven by the excessive result
discount.  Too bad!

Happily, the compiler/perf tests show a number of improvements:
    T12227     compiler bytes-alloc  -6.6%
    T12545     compiler bytes-alloc  -4.7%
    T13056     compiler bytes-alloc  -3.3%
    T15263     runtime  bytes-alloc -13.1%
    T17499     runtime  bytes-alloc -14.3%
    T3294      compiler bytes-alloc  -1.1%
    T5030      compiler bytes-alloc -11.7%
    T9872a     compiler bytes-alloc  -2.0%
    T9872b     compiler bytes-alloc  -1.2%
    T9872c     compiler bytes-alloc  -1.5%

Metric Decrease:
    T12227
    T12545
    T13056
    T15263
    T17499
    T3294
    T5030
    T9872a
    T9872b
    T9872c

- - - - -
7f0b671e by Ben Gamari at 2020-07-13T14:52:49-04:00
testsuite: Widen acceptance threshold on T5837

This test is positively tiny and consequently the bytes allocated
measurement will be relatively noisy. Consequently I have seen this
fail spuriously quite often.

- - - - -
118e1c3d by Alp Mestanogullari at 2020-07-14T21:30:52-04:00
compiler: re-engineer the treatment of rebindable if

Executing on the plan described in #17582, this patch changes the way if expressions
are handled in the compiler in the presence of rebindable syntax. We get rid of the
SyntaxExpr field of HsIf and instead, when rebindable syntax is on, we rewrite the HsIf
node to the appropriate sequence of applications of the local `ifThenElse` function.

In order to be able to report good error messages, with expressions as they were
written by the user (and not as desugared by the renamer), we make use of TTG
extensions to extend GhcRn expression ASTs with an `HsExpansion` construct, which
keeps track of a source (GhcPs) expression and the desugared (GhcRn) expression that
it gives rise to. This way, we can typecheck the latter while reporting the former in
error messages.

In order to discard the error context lines that arise from typechecking the desugared
expressions (because they talk about expressions that the user has not written), we
carefully give a special treatment to the nodes fabricated by this new renaming-time
transformation when typechecking them. See Note [Rebindable syntax and HsExpansion]
for more details. The note also includes a recipe to apply the same treatment to
other rebindable constructs.

Tests 'rebindable11' and 'rebindable12' have been added to make sure we report
identical error messages as before this patch under various circumstances.

We also now disable rebindable syntax when processing untyped TH quotes, as per
the discussion in #18102 and document the interaction of rebindable syntax and
Template Haskell, both in Note [Template Haskell quotes and Rebindable Syntax]
and in the user guide, adding a test to make sure that we do not regress in
that regard.

- - - - -
64c774b0 by Andreas Klebinger at 2020-07-14T21:31:27-04:00
Explain why keeping DynFlags in AnalEnv saves allocation.

- - - - -
254245d0 by Ben Gamari at 2020-07-14T21:32:03-04:00
docs/users-guide: Update default -funfolding-use-threshold value

This was changed in 3d2991f8 but I neglected to update the
documentation. Fixes #18419.

- - - - -
4c259f86 by Andreas Klebinger at 2020-07-14T21:32:41-04:00
Escape backslashes in json profiling reports properly.

I also took the liberty to do away the fixed buffer size for escaping.
Using a fixed size here can only lead to issues down the line.

Fixes #18438.

- - - - -
23797224 by Sergei Trofimovich at 2020-07-14T21:33:19-04:00
.gitlab: re-enable integer-simple substitute (BIGNUM_BACKEND)

Recently build system migrated from INTEGER_LIBRARY to BIGNUM_BACKEND.
But gitlab CI was never updated. Let's enable BIGNUM_BACKEND=native.

Bug: https://gitlab.haskell.org/ghc/ghc/-/issues/18437
Signed-off-by: Sergei Trofimovich <slyfox at gentoo.org>

- - - - -
e0db878a by Sergei Trofimovich at 2020-07-14T21:33:19-04:00
ghc-bignum: bring in sync .hs-boot files with module declarations

Before this change `BIGNUM_BACKEND=native` build was failing as:

```
libraries/ghc-bignum/src/GHC/Num/BigNat/Native.hs:708:16: error:
    * Variable not in scope: naturalFromBigNat# :: WordArray# -> t
    * Perhaps you meant one of these:
        `naturalFromBigNat' (imported from GHC.Num.Natural),
        `naturalToBigNat' (imported from GHC.Num.Natural)
    |
708 |           m' = naturalFromBigNat# m
    |
```

This happens because `.hs-boot` files are slightly out of date.
This change brings in data and function types in sync.

Bug: https://gitlab.haskell.org/ghc/ghc/-/issues/18437
Signed-off-by: Sergei Trofimovich <slyfox at gentoo.org>

- - - - -
c9f65c36 by Stefan Schulze Frielinghaus at 2020-07-14T21:33:57-04:00
rts/Disassembler.c: Use FMT_HexWord for printing values in hex format

- - - - -
58ae62eb by Matthias Andreas Benkard at 2020-07-14T21:34:35-04:00
macOS: Load frameworks without stating them first.

macOS Big Sur makes the following change to how frameworks are shipped
with the OS:

> New in macOS Big Sur 11 beta, the system ships with a built-in
> dynamic linker cache of all system-provided libraries. As part of
> this change, copies of dynamic libraries are no longer present on
> the filesystem. Code that attempts to check for dynamic library
> presence by looking for a file at a path or enumerating a directory
> will fail. Instead, check for library presence by attempting to
> dlopen() the path, which will correctly check for the library in the
> cache. (62986286)

https://developer.apple.com/documentation/macos-release-notes/macos-big-sur-11-beta-release-notes/

Therefore, the previous method of checking whether a library exists
before attempting to load it makes GHC.Runtime.Linker.loadFramework
fail to find frameworks installed at /System/Library/Frameworks.

GHC.Runtime.Linker.loadFramework now opportunistically loads the
framework libraries without checking for their existence first,
failing only if all attempts to load a given framework from any of the
various possible locations fail.

- - - - -
cdc4a6b0 by Matthias Andreas Benkard at 2020-07-14T21:34:35-04:00
loadFramework: Output the errors collected in all loading attempts.

With the recent change away from first finding and then loading a
framework, loadFramework had no way of communicating the real reason
why loadDLL failed if it was any reason other than the framework
missing from the file system.  It now collects all loading attempt
errors into a list and concatenates them into a string to return to
the caller.

- - - - -
51dbfa52 by Ben Gamari at 2020-07-15T04:05:34-04:00
StgToCmm: Use CmmRegOff smart constructor

Previously we would generate expressions of the form
`CmmRegOff BaseReg 0`. This should do no harm (and really should be
handled by the NCG anyways) but it's better to just generate a plain
`CmmReg`.

- - - - -
ae11bdfd by Ben Gamari at 2020-07-15T04:06:08-04:00
testsuite: Add regression test for #17744

Test due to @monoidal.

- - - - -
0e3c277a by Ben Gamari at 2020-07-15T16:41:01-04:00
Bump Cabal submodule

Updates a variety of tests as Cabal is now more strict about Cabal file
form.

- - - - -
ceed994a by Tamar Christina at 2020-07-15T16:41:01-04:00
winio: Drop Windows Vista support, require Windows 7

- - - - -
00a23bfd by Tamar Christina at 2020-07-15T16:41:01-04:00
winio: Update Windows FileSystem wrapper utilities.

- - - - -
459e1c5f by Tamar Christina at 2020-07-15T16:41:01-04:00
winio: Use SlimReaderLocks and ConditonalVariables provided by the OS instead of emulated ones

- - - - -
763088fc by Tamar Christina at 2020-07-15T16:41:01-04:00
winio: Small linker comment and ifdef cleanups

- - - - -
1a228ff9 by Tamar Christina at 2020-07-15T16:41:01-04:00
winio: Flush event logs eagerly.

- - - - -
e9e04dda by Tamar Christina at 2020-07-15T16:41:01-04:00
winio: Refactor Buffer structures to be able to track async operations

- - - - -
356dc3fe by Tamar Christina at 2020-07-15T16:41:01-04:00
winio: Implement new Console API

- - - - -
90e69f77 by Tamar Christina at 2020-07-15T16:41:01-04:00
winio: Add IOPort synchronization primitive

- - - - -
71245fcc by Tamar Christina at 2020-07-15T16:41:01-04:00
winio: Add new io-manager cmdline options

- - - - -
d548a3b3 by Tamar Christina at 2020-07-15T16:41:01-04:00
winio: Init Windows console Codepage to UTF-8.

- - - - -
58ef6366 by Tamar Christina at 2020-07-15T16:41:01-04:00
winio: Add unsafeSplat to GHC.Event.Array

- - - - -
d660725e by Tamar Christina at 2020-07-15T16:41:01-04:00
winio: Add size and iterate to GHC.Event.IntTable.

- - - - -
050da6dd by Tamar Christina at 2020-07-15T16:41:01-04:00
winio: Switch Testsuite to test winio by default

- - - - -
4bf542bf by Tamar Christina at 2020-07-15T16:41:01-04:00
winio: Multiple refactorings and support changes.

- - - - -
4489af6b by Tamar Christina at 2020-07-15T16:41:02-04:00
winio: core threaded I/O manager

- - - - -
64d8f2fe by Tamar Christina at 2020-07-15T16:41:02-04:00
winio: core non-threaded I/O manager

- - - - -
8da15a09 by Tamar Christina at 2020-07-15T16:41:02-04:00
winio: Fix a scheduler bug with the threaded-runtime.

- - - - -
84ea3d14 by Tamar Christina at 2020-07-15T16:41:02-04:00
winio: Relaxing some constraints in io-manager.

- - - - -
ccf0d107 by Tamar Christina at 2020-07-15T16:41:02-04:00
winio: Fix issues with non-threaded I/O manager after split.

- - - - -
b492fe6e by Tamar Christina at 2020-07-15T16:41:02-04:00
winio: Remove some barf statements that are a bit strict.

- - - - -
01423fd2 by Andreas Klebinger at 2020-07-15T16:41:02-04:00
winio: Expand comments describing non-threaded loop

- - - - -
4b69004f by Tamar Christina at 2020-07-15T16:41:02-04:00
winio: fix FileSize unstat-able handles

- - - - -
9b384270 by Tamar Christina at 2020-07-15T16:41:02-04:00
winio: Implement new tempfile routines for winio

- - - - -
f1e0be82 by Andreas Klebinger at 2020-07-15T16:41:02-04:00
winio: Fix input truncation when reading from handle.

This was caused by not upholding the read buffer invariant
that bufR == bufL == 0 for empty read buffers.

- - - - -
e176b625 by Andreas Klebinger at 2020-07-15T16:41:02-04:00
winio: Fix output truncation for writes larger than buffer size

- - - - -
a831ce0e by Andreas Klebinger at 2020-07-15T16:41:02-04:00
winio: Rewrite bufWrite.

I think it's far easier to follow the code now.
It's also correct now as I had still missed a spot
where we didn't update the offset.

- - - - -
6aefdf62 by Andreas Klebinger at 2020-07-15T16:41:02-04:00
winio: Fix offset set by bufReadEmpty.

bufReadEmpty returns the bytes read *including* content that
was already buffered,
But for calculating the offset we only care about the number
of bytes read into the new buffer.

- - - - -
750ebaee by Andreas Klebinger at 2020-07-15T16:41:02-04:00
winio: Clean up code surrounding IOPort primitives.

According to phyx these should only be read and written once per
object. Not neccesarily in that order.

To strengthen that guarantee the primitives will now throw an
exception if we violate this invariant.

As a consequence we can eliminate some code from their primops.
In particular code dealing with multiple queued readers/writers
now simply checks the invariant and throws an exception if it
was violated. That is in contrast to mvars which will do things
like wake up all readers, queue multi writers etc.

- - - - -
ffd31db9 by Andreas Klebinger at 2020-07-15T16:41:02-04:00
winio: Fix multi threaded threadDelay and a few other small changes.

Multithreaded threadDelay suffered from a race condition
based on the ioManagerStatus. Since the status isn't needed
for WIO I removed it completely.

This resulted in a light refactoring, as consequence we will always
wake up the IO manager using interruptSystemManager, which uses
`postQueuedCompletionStatus` internally.

I also added a few comments which hopefully makes the code easier to
dive into for the next person diving in.

- - - - -
6ec26df2 by Andreas Klebinger at 2020-07-15T16:41:02-04:00
wionio: Make IO subsystem check a no-op on non-windows platforms.

- - - - -
29bcd936 by Andreas Klebinger at 2020-07-15T16:41:02-04:00
winio: Set handle offset when opening files in Append mode.

Otherwise we would truncate the file.

- - - - -
55c29700 by Andreas Klebinger at 2020-07-15T16:41:02-04:00
winio: Remove debug event log trace

- - - - -
9acb9f40 by Andreas Klebinger at 2020-07-15T16:41:02-04:00
winio: Fix sqrt and openFile009 test cases

- - - - -
57017cb7 by Andreas Klebinger at 2020-07-15T16:41:02-04:00
winio: Allow hp2ps to build with -DDEBUG

- - - - -
b8cd9995 by Andreas Klebinger at 2020-07-15T16:41:02-04:00
winio: Update output of T9681 since we now actually run it.

- - - - -
10af5b14 by Andreas Klebinger at 2020-07-15T16:41:02-04:00
winio: A few more improvements to the IOPort primitives.

- - - - -
39afc4a7 by Andreas Klebinger at 2020-07-15T16:41:02-04:00
winio: Fix expected tempfiles output.

Tempfiles now works properly on windows, as such we can
delete the win32 specific output.

- - - - -
99db46e0 by Andreas Klebinger at 2020-07-15T16:41:02-04:00
winio: Assign thread labels to IOManager threads.

- - - - -
be6af732 by Andreas Klebinger at 2020-07-15T16:41:02-04:00
winio: Properly check for the tso of an incall to be zero.

- - - - -
e2c6dac7 by Andreas Klebinger at 2020-07-15T16:41:02-04:00
winio: Mark FD instances as unsupported under WINIO.

- - - - -
fd02ceed by Andreas Klebinger at 2020-07-15T16:41:02-04:00
winio: Fix threadDelay maxBound invocations.

Instead of letting the ns timer overflow now clamp it at
(maxBound :: Word64) ns. That still gives a few hundred
years.

- - - - -
bc79f9f1 by Andreas Klebinger at 2020-07-15T16:41:02-04:00
winio: Add comments/cleanup an import in base

- - - - -
1d197f4b by Andreas Klebinger at 2020-07-15T16:41:02-04:00
winio: Mark outstanding_service_requests volatile.

As far as I know C(99) gives no guarantees for code like

    bool condition;

    ...

    while(condition)
        sleep();

that condition will be updated if it's changed by another thread.
So we are explicit here and mark it as volatile, this will force
a reload from memory on each iteration.

- - - - -
dc438186 by Andreas Klebinger at 2020-07-15T16:41:02-04:00
winio: Make last_event a local variable

- - - - -
2fc957c5 by Andreas Klebinger at 2020-07-15T16:41:02-04:00
winio: Add comment about thread safety of processCompletion.

- - - - -
4c026b6c by Andreas Klebinger at 2020-07-15T16:41:02-04:00
winio: nonthreaded: Create io processing threads in main thread.

We now set a flag in the IO thread. The scheduler when looking for work
will check the flag and create/queue threads accordingly.

We used to create these in the IO thread. This improved performance
but caused frequent segfaults. Thread creation/allocation is only safe to
do if nothing currently accesses the storeagemanager. However without
locks in the non-threaded runtime this can't be guaranteed.

This shouldn't change performance all too much.

In the past we had:
* IO: Create/Queue thread.
* Scheduler: Runs a few times. Eventually picks up IO processing thread.

Now it's:
* IO: Set flag to queue thread.
* Scheduler: Pick up flag, if set create/queue thread. Eventually picks up IO processing thread.

- - - - -
f47c7208 by Andreas Klebinger at 2020-07-15T16:41:02-04:00
winio: Add an exported isHeapAlloced function to the RTS

- - - - -
cc5d7bb1 by Andreas Klebinger at 2020-07-15T16:41:02-04:00
winio: Queue IO processing threads at the front of the queue.

This will unblock the IO thread sooner hopefully leading to higher
throughput in some situations.

- - - - -
e7630115 by Andreas Klebinger at 2020-07-15T16:41:02-04:00
winio: ThreadDelay001: Use higher resolution timer.

- - - - -
451b5f96 by Andreas Klebinger at 2020-07-15T16:41:02-04:00
winio: Update T9681 output, disable T4808 on windows.

T4808 tests functionality of the FD interface which won't be supported
under WINIO.

T9681 just has it's expected output tweaked.

- - - - -
dd06f930 by Andreas Klebinger at 2020-07-15T16:41:02-04:00
winio: Wake io manager once per registerTimeout.

Which is implicitly done in editTimeouts, so need to wake it
up twice.

- - - - -
e87d0bf9 by Andreas Klebinger at 2020-07-15T16:41:03-04:00
winio: Update placeholder comment with actual function name.

- - - - -
fc9025db by Andreas Klebinger at 2020-07-15T16:41:03-04:00
winio: Always lock win32 event queue

- - - - -
c24c9a1f by Andreas Klebinger at 2020-07-15T16:41:03-04:00
winio: Display thread labels when tracing scheduler events.

- - - - -
06542b03 by Andreas Klebinger at 2020-07-15T16:41:03-04:00
winio: Refactor non-threaded runner thread and scheduler interface.

Only use a single communication point (registerAlertableWait) to inform
the C side aobut both timeouts to use as well as outstanding requests.

Also queue a haskell processing thread after each return from alertable
waits. This way there is no risk of us missing a timer event.

- - - - -
256299b1 by Andreas Klebinger at 2020-07-15T16:41:03-04:00
winio: Remove outstanding_requests from runner.

We used a variable to keep track of situations where we got
entries from the IO port, but all of them had already been
canceled. While we can avoid some work that way this case
seems quite rare.

So we give up on tracking this and instead always assume at
least one of the returned entries is valid.

If that's not the case no harm is done, we just perform some
additional work. But it makes the runner easier to reason about.

In particular we don't need to care if another thread modifies
oustanding_requests after we return from waiting on the IO Port.

- - - - -
3ebd8ad9 by Tamar Christina at 2020-07-15T16:41:03-04:00
winio: Various fixes related to rebase and testdriver

- - - - -
6be6bcba by Tamar Christina at 2020-07-15T16:41:03-04:00
winio: Fix rebase artifacts

- - - - -
2c649dc3 by Andreas Klebinger at 2020-07-15T16:41:03-04:00
winio: Rename unsafeSplat to unsafeCopyFromBuffer

- - - - -
a18b73f3 by Andreas Klebinger at 2020-07-15T16:41:03-04:00
winio: Remove unused size/iterate operations from IntTable

- - - - -
16bab48e by Andreas Klebinger at 2020-07-15T16:41:03-04:00
winio: Detect running IO Backend via peeking at RtsConfig

- - - - -
8b8405a0 by Tamar Christina at 2020-07-15T16:41:03-04:00
winio: update temp path so GCC etc can handle it.

Also fix PIPE support, clean up error casting, fix memory leaks

- - - - -
2092bc54 by Ben Gamari at 2020-07-15T16:41:03-04:00
winio: Minor comments/renamings

- - - - -
a5b5b6c0 by Andreas Klebinger at 2020-07-15T16:41:03-04:00
winio: Checking if an error code indicates completion is now a function.

- - - - -
362176fd by Andreas Klebinger at 2020-07-15T16:41:03-04:00
winio: Small refactor in withOverlappedEx

- - - - -
32e20597 by Andreas Klebinger at 2020-07-15T16:41:03-04:00
winio: A few comments and commented out dbxIO

- - - - -
a4bfc1d9 by Andreas Klebinger at 2020-07-15T16:41:03-04:00
winio: Don't drop buffer offset in byteView/cwcharView

- - - - -
b3ad2a54 by Tamar Christina at 2020-07-15T16:41:03-04:00
winio: revert BHandle changes.

- - - - -
3dcd87e2 by Ben Gamari at 2020-07-15T16:41:03-04:00
winio: Fix imports

- - - - -
5a371890 by Tamar Christina at 2020-07-15T16:41:03-04:00
winio: update ghc-cabal to handle new Cabal submodule bump

- - - - -
d07ebe0d by Ben Gamari at 2020-07-15T16:41:03-04:00
winio: Only compile sources on Windows

- - - - -
dcb42393 by Andreas Klebinger at 2020-07-15T16:41:03-04:00
winio: Actually return Nothing on EOF for non-blocking read

- - - - -
895a3beb by Andreas Klebinger at 2020-07-15T16:41:03-04:00
winio: Deduplicate logic in encodeMultiByte[Raw]IO.

- - - - -
e06e6734 by Andreas Klebinger at 2020-07-15T16:41:03-04:00
winio: Deduplicate openFile logic

- - - - -
b59430c0 by Tamar Christina at 2020-07-15T16:41:03-04:00
winio: fix -werror issue in encoding file

- - - - -
f8d39a51 by Andreas Klebinger at 2020-07-15T16:41:03-04:00
winio: Don't mention windows specific functions when building on Linux.

- - - - -
6a533d2a by Andreas Klebinger at 2020-07-15T16:41:03-04:00
winio: add a note about file locking in the RTS.

- - - - -
cf37ce34 by Andreas Klebinger at 2020-07-15T16:41:03-04:00
winio: Add version to @since annotation

- - - - -
0fafa2eb by Andreas Klebinger at 2020-07-15T16:41:03-04:00
winio: Rename GHC.Conc.IOCP -> GHC.Conc.WinIO

- - - - -
1854fc23 by Andreas Klebinger at 2020-07-15T16:41:03-04:00
winio: Expand GHC.Conc.POSIX description

It now explains users may not use these functions when
using the old IO manager.

- - - - -
fcc7ba41 by Andreas Klebinger at 2020-07-15T16:41:03-04:00
winio: Fix potential spaceleak in __createUUIDTempFileErrNo

- - - - -
6b3fd9fa by Andreas Klebinger at 2020-07-15T16:41:03-04:00
winio: Remove redundant -Wno-missing-signatures pragmas

- - - - -
916fc861 by Andreas Klebinger at 2020-07-15T16:41:03-04:00
winio: Make it explicit that we only create one IO manager

- - - - -
f260a721 by Andreas Klebinger at 2020-07-15T16:41:03-04:00
winio: Note why we don't use blocking waits.

- - - - -
aa0a4bbf by Andreas Klebinger at 2020-07-15T16:41:03-04:00
winio: Remove commented out pragma

- - - - -
d679b544 by Andreas Klebinger at 2020-07-15T16:41:03-04:00
winio: Remove redundant buffer write in Handle/Text.hs:bufReadEmpty

- - - - -
d3f94368 by Andreas Klebinger at 2020-07-15T16:41:03-04:00
winio: Rename SmartHandles to StdHandles

- - - - -
bd6b8ec1 by Andreas Klebinger at 2020-07-15T16:41:03-04:00
winio: add comment stating failure behaviour for getUniqueFileInfo.

- - - - -
12846b85 by Andreas Klebinger at 2020-07-15T16:41:03-04:00
winio: Update IOPort haddocks.

- - - - -
9f39fb14 by Andreas Klebinger at 2020-07-15T16:41:04-04:00
winio: Add a note cross reference

- - - - -
62dd5a73 by Andreas Klebinger at 2020-07-15T16:41:04-04:00
winio: Name Haskell/OS I/O Manager explicitly in Note

- - - - -
fa807828 by Andreas Klebinger at 2020-07-15T16:41:04-04:00
winio: Expand BlockedOnIOCompletion description.

- - - - -
f0880a1d by Andreas Klebinger at 2020-07-15T16:41:04-04:00
winio: Remove historical todos

- - - - -
8e58e714 by Andreas Klebinger at 2020-07-15T16:41:04-04:00
winio: Update note, remove debugging pragma.

- - - - -
aa4d84d5 by Andreas Klebinger at 2020-07-15T16:41:04-04:00
winio: flushCharReadBuffer shouldn't need to adjust offsets.

- - - - -
e580893a by Andreas Klebinger at 2020-07-15T16:41:04-04:00
winio: Remove obsolete comment about cond. variables

- - - - -
d54e9d79 by Andreas Klebinger at 2020-07-15T16:41:04-04:00
winio: fix initial linux validate build

- - - - -
3cd4de46 by Andreas Klebinger at 2020-07-15T16:41:04-04:00
winio: Fix ThreadDelay001 CPP

- - - - -
c88b1b9f by Andreas Klebinger at 2020-07-15T16:41:04-04:00
winio: Fix openFile009 merge conflict leftover

- - - - -
849e8889 by Andreas Klebinger at 2020-07-15T16:41:04-04:00
winio: Accept T9681 output.

GHC now reports String instead of [Char].

- - - - -
e7701818 by Andreas Klebinger at 2020-07-15T16:41:04-04:00
winio: Fix cabal006 after upgrading cabal submodule

Demand cabal 2.0 syntax instead of >= 1.20 as required by newer cabal versions.

- - - - -
a44f0373 by Andreas Klebinger at 2020-07-15T16:41:04-04:00
winio: Fix stderr output for ghci/linking/dyn tests.

We used to filter rtsopts, i opted to instead just accept the warning of it having no effect.
This works both for -rtsopts, as well as -with-rtsopts which winio adds.

- - - - -
515d9896 by Andreas Klebinger at 2020-07-15T16:41:04-04:00
winio: Adjust T15261b stdout for --io-manager flag.

- - - - -
949aaacc by Andreas Klebinger at 2020-07-15T16:41:04-04:00
winio: Adjust T5435_dyn_asm stderr

The warning about rtsopts having no consequences is expected.
So accept new stderr.

- - - - -
7d424e1e by Andreas Klebinger at 2020-07-15T16:41:04-04:00
winio: Also accept T7037 stderr

- - - - -
1f009768 by Andreas Klebinger at 2020-07-15T16:41:04-04:00
winio: fix cabal04 by filtering rts args

- - - - -
981a9f2e by Andreas Klebinger at 2020-07-15T16:41:04-04:00
winio: fix cabal01 by accepting expected stderr

- - - - -
b7b0464e by Andreas Klebinger at 2020-07-15T16:41:04-04:00
winio: fix safePkg01 by accepting expected stderr

- - - - -
32734b29 by Andreas Klebinger at 2020-07-15T16:41:04-04:00
winio: fix T5435_dyn_gcc by accepting expected stderr

- - - - -
acc5cebf by Andreas Klebinger at 2020-07-15T16:41:04-04:00
winio: fix tempfiles test on linux

- - - - -
c577b789 by Andreas Klebinger at 2020-07-15T16:41:04-04:00
winio: Accept accepted stderr for T3807

- - - - -
c108c527 by Andreas Klebinger at 2020-07-15T16:41:04-04:00
winio: Accept accepted stderr for linker_unload

- - - - -
2b0b9a08 by Andreas Klebinger at 2020-07-15T16:41:04-04:00
winio: Accept accepted stderr for linker_unload_multiple_objs

- - - - -
67afb03c by Tamar Christina at 2020-07-15T16:41:04-04:00
winio: clarify wording on conditional variables.

- - - - -
3bd41572 by Tamar Christina at 2020-07-15T16:41:04-04:00
winio: clarify comment on cooked mode.

- - - - -
ded58a03 by Tamar Christina at 2020-07-15T16:41:04-04:00
winio: update lockfile signature and remove mistaken symbol in rts.

- - - - -
2143c492 by Ben Gamari at 2020-07-15T16:41:04-04:00
testsuite: Add winio and winio_threaded ways

Reverts many of the testsuite changes

- - - - -
c0979cc5 by Ben Gamari at 2020-07-16T10:56:54-04:00
Merge remote-tracking branch 'origin/wip/winio'

- - - - -
750a1595 by Ben Gamari at 2020-07-18T07:26:41-04:00
rts: Add --copying-gc flag to reverse effect of --nonmoving-gc

Fixes #18281.

- - - - -
6ba6a881 by Hécate at 2020-07-18T07:26:42-04:00
Implement `fullCompilerVersion`

Follow-up of https://gitlab.haskell.org/ghc/ghc/-/issues/18403

This MR adds `fullCompilerVersion`, a function that shares the same
backend as the `--numeric-version` GHC flag, exposing a full,
three-digit version datatype.

- - - - -
e6cf27df by Hécate at 2020-07-18T07:26:43-04:00
Add a Lint hadrian rule and an .hlint.yaml file in base/

- - - - -
bcb177dd by Simon Peyton Jones at 2020-07-18T07:26:43-04:00
Allow multiple case branches to have a higher rank type

As #18412 points out, it should be OK for multiple case alternatives
to have a higher rank type, provided they are all the same.

This patch implements that change.  It sweeps away
GHC.Tc.Gen.Match.tauifyMultipleBranches, and friends, replacing it
with an enhanced version of fillInferResult.

The basic change to fillInferResult is to permit the case in which
another case alternative has already filled in the result; and in
that case simply unify.  It's very simple actually.

See the new Note [fillInferResult] in TcMType

Other refactoring:

- Move all the InferResult code to one place, in GHC.Tc.Utils.TcMType
  (previously some of it was in Unify)

- Move tcInstType and friends from TcMType to Instantiate, where it
  more properly belongs.  (TCMType was getting very long.)

- - - - -
e5525a51 by Simon Peyton Jones at 2020-07-18T07:26:43-04:00
Improve typechecking of NPlusK patterns

This patch (due to Richard Eisenberg) improves
documentation of the wrapper returned by tcSubMult
(see Note [Wrapper returned from tcSubMult] in
 GHC.Tc.Utils.Unify).

And, more substantially, it cleans up the multiplicity
handling in the typechecking of NPlusKPat

- - - - -
12f90352 by Krzysztof Gogolewski at 2020-07-18T07:26:45-04:00
Remove {-# CORE #-} pragma (part of #18048)

This pragma has no effect since 2011.
It was introduced for External Core, which no longer exists.

Updates haddock submodule.

- - - - -
e504c913 by Simon Peyton Jones at 2020-07-18T07:26:45-04:00
Refactor the simplification of join binders

This MR (for #18449) refactors the Simplifier's treatment
of join-point binders.

Specifically, it puts together, into
     GHC.Core.Opt.Simplify.Env.adjustJoinPointType
two currently-separate ways in which we adjust the type of
a join point. As the comment says:

-- (adjustJoinPointType mult new_res_ty join_id) does two things:
--
--   1. Set the return type of the join_id to new_res_ty
--      See Note [Return type for join points]
--
--   2. Adjust the multiplicity of arrows in join_id's type, as
--      directed by 'mult'. See Note [Scaling join point arguments]

I think this actually fixes a latent bug, by ensuring that the
seIdSubst and seInScope have the right multiplicity on the type
of join points.

I did some tidying up while I was at it.  No more
setJoinResTy, or modifyJoinResTy: instead it's done locally in
Simplify.Env.adjustJoinPointType

- - - - -
49b265f0 by Chaitanya Koparkar at 2020-07-18T07:26:46-04:00
Fix minor typos in a Core.hs note

- - - - -
8d59aed6 by Stefan Schulze Frielinghaus at 2020-07-18T07:26:47-04:00
GHCi: Fix isLittleEndian

- - - - -
c26e81d1 by Ben Gamari at 2020-07-18T07:26:47-04:00
testsuite: Mark ghci tests as fragile under unreg compiler

In particular I have seen T16012 fail repeatedly under the
unregisterised compiler.

- - - - -
868e4523 by Moritz Angermann at 2020-07-20T04:30:38-04:00
Revert "AArch32 symbols only on aarch32."

This reverts commit cdfeb3f24f76e8fd30452016676e56fbc827789a.

Signed-off-by: Moritz Angermann <moritz.angermann at gmail.com>

- - - - -
c915ba84 by Moritz Angermann at 2020-07-20T04:30:38-04:00
Revert "Fix (1)"

This reverts commit 7abffced01f5680efafe44f6be2733eab321b039.

Signed-off-by: Moritz Angermann <moritz.angermann at gmail.com>

- - - - -
777c452a by Moritz Angermann at 2020-07-20T04:30:38-04:00
Revert "better if guards."

This reverts commit 3f60b94de1f460ca3f689152860b108a19ce193e.

Signed-off-by: Moritz Angermann <moritz.angermann at gmail.com>

- - - - -
0dd40552 by Moritz Angermann at 2020-07-20T04:30:38-04:00
Revert "[linker/rtsSymbols] More linker symbols"

This reverts commit 686e72253aed3880268dd6858eadd8c320f09e97.

Signed-off-by: Moritz Angermann <moritz.angermann at gmail.com>

- - - - -
30caeee7 by Sylvain Henry at 2020-07-21T06:39:33-04:00
DynFlags: remove use of sdocWithDynFlags from GHC.Stg.* (#17957)

* add StgPprOpts datatype
* remove Outputable instances for types that need `StgPprOpts` to be
  pretty-printed and explicitly call type specific ppr functions
* add default `panicStgPprOpts` for panic messages (when it's not
  convenient to thread StgPprOpts or DynFlags down to the ppr function
  call)

- - - - -
863c544c by Mark at 2020-07-21T06:39:34-04:00
Fix a typo in existential_quantification.rst
- - - - -
05910be1 by Krzysztof Gogolewski at 2020-07-21T14:47:07-04:00
Add release notes entry for #17816

[skip ci]

- - - - -
a6257192 by Matthew Pickering at 2020-07-21T14:47:19-04:00
Use a newtype `Code` for the return type of typed quotations (Proposal #195)

There are three problems with the current API:

1. It is hard to properly write instances for ``Quote m => m (TExp a)`` as the type is the composition
   of two type constructors. Doing so in your program involves making your own newtype and
   doing a lot of wrapping/unwrapping.

   For example, if I want to create a language which I can either run immediately or
   generate code from I could write the following with the new API. ::

      class Lang r where
        _int :: Int -> r Int
        _if  :: r Bool -> r a -> r a -> r a

      instance Lang Identity where
        _int = Identity
        _if (Identity b) (Identity t) (Identity f) = Identity (if b then t else f)

      instance Quote m => Lang (Code m) where
        _int = liftTyped
        _if cb ct cf = [|| if $$cb then $$ct else $$cf ||]

2. When doing code generation it is common to want to store code fragments in
   a map. When doing typed code generation, these code fragments contain a
   type index so it is desirable to store them in one of the parameterised
   map data types such as ``DMap`` from ``dependent-map`` or ``MapF`` from
   ``parameterized-utils``.

   ::

      compiler :: Env -> AST a -> Code Q a

      data AST a where ...
      data Ident a = ...

      type Env = MapF Ident (Code Q)

      newtype Code m a = Code (m (TExp a))

   In this example, the ``MapF`` maps an ``Ident String`` directly to a ``Code Q String``.
   Using one of these map types currently requires creating your own newtype and constantly
   wrapping every quotation and unwrapping it when using a splice. Achievable, but
   it creates even more syntactic noise than normal metaprogramming.

3. ``m (TExp a)`` is ugly to read and write, understanding ``Code m a`` is
   easier. This is a weak reason but one everyone
   can surely agree with.

Updates text submodule.

- - - - -
58235d46 by Ben Gamari at 2020-07-21T14:47:28-04:00
users-guide: Fix :rts-flag:`--copying-gc` documentation

It was missing a newline.

- - - - -
19e80b9a by Vladislav Zavialov at 2020-07-21T14:50:01-04:00
Accumulate Haddock comments in P (#17544, #17561, #8944)

Haddock comments are, first and foremost, comments. It's very annoying
to incorporate them into the grammar. We can take advantage of an
important property: adding a Haddock comment does not change the parse
tree in any way other than wrapping some nodes in HsDocTy and the like
(and if it does, that's a bug).

This patch implements the following:

* Accumulate Haddock comments with their locations in the P monad.
  This is handled in the lexer.

* After parsing, do a pass over the AST to associate Haddock comments
  with AST nodes using location info.

* Report the leftover comments to the user as a warning (-Winvalid-haddock).

- - - - -
4c719460 by David Binder at 2020-07-22T20:17:35-04:00
Fix dead link to haskell prime discussion

- - - - -
f2f817e4 by BinderDavid at 2020-07-22T20:17:35-04:00
Replace broken links to old haskell-prime site by working links to gitlab instance.
[skip ci]

- - - - -
0bf8980e by Daniel Gröber at 2020-07-22T20:18:11-04:00
Remove length field from FastString

- - - - -
1010c33b by Daniel Gröber at 2020-07-22T20:18:11-04:00
Use ShortByteString for FastString

There are multiple reasons we want this:

- Fewer allocations: ByteString has 3 fields, ShortByteString just has one.
- ByteString memory is pinned:
  - This can cause fragmentation issues (see for example #13110) but also
  - makes using FastStrings in compact regions impossible.

Metric Decrease:
    T5837
    T12150
    T12234
    T12425

- - - - -
8336ba78 by Daniel Gröber at 2020-07-22T20:18:11-04:00
Pass specialised utf8DecodeChar# to utf8DecodeLazy# for performance

Currently we're passing a indexWord8OffAddr# type function to
utf8DecodeLazy# which then passes it on to utf8DecodeChar#. By passing one
of utf8DecodeCharAddr# or utf8DecodeCharByteArray# instead we benefit from
the inlining and specialization already done for those.

- - - - -
7484a9a4 by Daniel Gröber at 2020-07-22T20:18:11-04:00
Encoding: Add comment about tricky ForeignPtr lifetime

- - - - -
5536ed28 by Daniel Gröber at 2020-07-22T20:18:11-04:00
Use IO constructor instead of `stToIO . ST`

- - - - -
5b8902e3 by Daniel Gröber at 2020-07-22T20:18:11-04:00
Encoding: Remove redundant use of withForeignPtr

- - - - -
5976a161 by Daniel Gröber at 2020-07-22T20:18:11-04:00
Encoding: Reformat utf8EncodeShortByteString to be more consistent

- - - - -
9ddf1614 by Daniel Gröber at 2020-07-22T20:18:11-04:00
FastString: Reintroduce character count cache

Metric Increase:
    ManyConstructors

Metric Decrease:
    T4029

- - - - -
e9491668 by Ben Gamari at 2020-07-22T20:18:46-04:00
get-win32-tarballs: Fix detection of missing tarballs

This fixes the error message given by configure when the user
attempts to configure without first download the win32 tarballs.

- - - - -
9f3ff8fd by Andreas Klebinger at 2020-07-22T20:19:22-04:00
Enable BangPatterns, ScopedTypeVariables for ghc and hadrian by default.

This is only for their respective codebases.

- - - - -
0f17b930 by Sylvain Henry at 2020-07-22T20:19:59-04:00
Remove unused "ncg" flag

This flag has been removed in 066b369de2c6f7da03c88206288dca29ab061b31
in 2011.

- - - - -
bab4ec8f by Sylvain Henry at 2020-07-22T20:19:59-04:00
Don't panic if the NCG isn't built (it is always built)

- - - - -
8ea33edb by Sylvain Henry at 2020-07-22T20:19:59-04:00
Remove unused sGhcWithNativeCodeGen

- - - - -
e079bb72 by Sylvain Henry at 2020-07-22T20:19:59-04:00
Correctly test active backend

Previously we used a platform settings to detect if the native code
generator was used. This was wrong. We need to use the
`DynFlags.hscTarget` field instead.

- - - - -
735f9d6b by Sylvain Henry at 2020-07-22T20:19:59-04:00
Replace ghcWithNativeCodeGen with a proper Backend datatype

* Represent backends with a `Backend` datatype in GHC.Driver.Backend

* Don't detect the default backend to use for the target platform at
  compile time in Hadrian/make but at runtime. It makes "Settings"
  simpler and it is a step toward making GHC multi-target.

* The latter change also fixes hadrian which has not been updated to
  take into account that the NCG now supports AIX and PPC64 (cf
  df26b95559fd467abc0a3a4151127c95cb5011b9 and
  d3c1dda60d0ec07fc7f593bfd83ec9457dfa7984)

* Also we don't treat iOS specifically anymore (cf
  cb4878ffd18a3c70f98bdbb413cd3c4d1f054e1f)

- - - - -
f7cc4313 by Sylvain Henry at 2020-07-22T20:19:59-04:00
Replace HscTarget with Backend

They both have the same role and Backend name is more explicit.

Metric Decrease:
    T3064

Update Haddock submodule

- - - - -
15ce1804 by Andreas Klebinger at 2020-07-22T20:20:34-04:00
Deprecate -fdmd-tx-dict-sel.

It's behaviour is now unconditionally enabled as
it's slightly beneficial.

There are almost no benchmarks which benefit from
disabling it, so it's not worth the keep this
configurable.

This fixes #18429.

- - - - -
ff1b7710 by Sylvain Henry at 2020-07-22T20:21:11-04:00
Add test for #18064

It has been fixed by 0effc57d48ace6b719a9f4cbeac67c95ad55010b

- - - - -
cfa89149 by Krzysztof Gogolewski at 2020-07-22T20:21:48-04:00
Define type Void# = (# #) (#18441)

There's one backwards compatibility issue: GHC.Prim no longer exports
Void#, we now manually re-export it from GHC.Exts.

- - - - -
02f40b0d by Sebastian Graf at 2020-07-22T20:22:23-04:00
Add regression test for #18478

!3392 backported !2993 to GHC 8.10.2 which most probably is responsible
for fixing #18478, which triggered a pattern match checker performance
regression in GHC 8.10.1 as first observed in #17977.

- - - - -
7f44df1e by Sylvain Henry at 2020-07-22T20:23:00-04:00
Minor refactoring of Unit display

* for consistency, try to always use UnitPprInfo to display units to
  users

* remove some uses of `unitPackageIdString` as it doesn't show the
  component name and it uses String

- - - - -
dff1cb3d by Moritz Angermann at 2020-07-23T07:55:29-04:00
[linker] Fix out of range relocations.

mmap may return address all over the place. mmap_next will ensure we get
the next free page after the requested address.

This is especially important for linking on aarch64, where the memory model with PIC
admits relocations in the +-4GB range, and as such we can't work with
arbitrary object locations in memory.

Of note: we map the rts into process space, so any mapped objects must
not be ouside of the 4GB from the processes address space.

- - - - -
cdd0ff16 by Tamar Christina at 2020-07-24T18:12:23-04:00
winio: restore console cp on exit

- - - - -
c1f4f81d by Tamar Christina at 2020-07-24T18:13:00-04:00
winio: change memory allocation strategy and fix double free errors.

- - - - -
ba205046 by Simon Peyton Jones at 2020-07-24T18:13:35-04:00
Care with occCheckExpand in kind of occurrences

Issue #18451 showed that we could get an infinite type, through
over-use of occCheckExpand in the kind of an /occurrence/ of a
type variable.

See Note [Occurrence checking: look inside kinds] in GHC.Core.Type

This patch fixes the problem by making occCheckExpand less eager
to expand synonyms in kinds.

It also improves pretty printing of kinds, by *not* suppressing
the kind on a tyvar-binder like
    (a :: Const Type b)
where type Const p q = p.  Even though the kind of 'a' is Type,
we don't want to suppress the kind ascription.  Example: the
error message for polykinds/T18451{a,b}. See GHC.Core.TyCo.Ppr
Note [Suppressing * kinds].

- - - - -
02133353 by Zubin Duggal at 2020-07-25T00:44:30-04:00
Simplify XRec definition
Change `Located X` usage to `XRec pass X`
This increases the scope of the LPat experiment to almost all of GHC.
Introduce UnXRec and MapXRec classes

Fixes #17587 and #18408

Updates haddock submodule

Co-authored-by: Philipp Krüger <philipp.krueger1 at gmail.com>

- - - - -
e443846b by Sylvain Henry at 2020-07-25T00:45:07-04:00
DynFlags: store printer in TraceBinIfaceReading

We don't need to pass the whole DynFlags, just pass the logging
function, if any.

- - - - -
15b2b44f by Sylvain Henry at 2020-07-25T00:45:08-04:00
Rename GHC.Driver.Ways into GHC.Platform.Ways

- - - - -
342a01af by Sylvain Henry at 2020-07-25T00:45:08-04:00
Add GHC.Platform.Profile

- - - - -
6333d739 by Sylvain Henry at 2020-07-25T00:45:08-04:00
Put PlatformConstants into Platform

- - - - -
9dfeca6c by Sylvain Henry at 2020-07-25T00:45:08-04:00
Remove platform constant wrappers

Platform constant wrappers took a DynFlags parameter, hence implicitly
used the target platform constants. We removed them to allow support
for several platforms at once (#14335) and to avoid having to pass
the full DynFlags to every function (#17957).

Metric Decrease:
   T4801

- - - - -
73145d57 by Sylvain Henry at 2020-07-25T00:45:08-04:00
Remove dead code in utils/derivConstants

- - - - -
7721b923 by Sylvain Henry at 2020-07-25T00:45:08-04:00
Move GHC.Platform into the compiler

Previously it was in ghc-boot so that ghc-pkg could use it. However it
wasn't necessary because ghc-pkg only uses a subset of it: reading
target arch and OS from the settings file. This is now done via
GHC.Platform.ArchOS (was called PlatformMini before).

- - - - -
459afeb5 by Sylvain Henry at 2020-07-25T00:45:08-04:00
Fix build systems

- - - - -
9e2930c3 by Sylvain Henry at 2020-07-25T00:45:08-04:00
Bump CountParserDeps

- - - - -
6e2db34b by Sylvain Henry at 2020-07-25T00:45:08-04:00
Add accessors to ArchOS

- - - - -
fc0f6fbc by Stefan Schulze Frielinghaus at 2020-07-25T00:45:45-04:00
Require SMP support in order to build a threaded stage1

Fixes 18266

- - - - -
a7c4439a by Matthias Andreas Benkard at 2020-07-26T13:23:24-04:00
Document loadFramework changes. (#18446)

Adds commentary on the rationale for the changes made in merge request
!3689.

- - - - -
da7269a4 by Ben Gamari at 2020-07-26T13:23:59-04:00
rts/win32: Exit with EXIT_HEAPOVERFLOW if memory commit fails

Since switching to the two-step allocator, the `outofmem` test fails via
`osCommitMemory` failing to commit. However, this was previously exiting
with `EXIT_FAILURE`, rather than `EXIT_HEAPOVERFLOW`. I think the latter
is a more reasonable exit code for this case and matches the behavior on
POSIX platforms.

- - - - -
f153a1d0 by Ben Gamari at 2020-07-26T13:23:59-04:00
testsuite: Update win32 output for parseTree

- - - - -
e91672f0 by Ben Gamari at 2020-07-26T13:23:59-04:00
testsuite: Normalise WinIO error message differences

Previously the old Windows IO manager threw different errors than WinIO.
We now canonicalise these to the WinIO errors.

- - - - -
9cbfe086 by Ben Gamari at 2020-07-26T13:23:59-04:00
gitlab-ci: Kill ssh-agent after pushing test metrics

Otherwise the Windows builds hang forever waiting for the process to
terminate.

- - - - -
8236925f by Tamar Christina at 2020-07-26T13:24:35-04:00
winio: remove dead argument to stg_newIOPortzh

- - - - -
ce0a1d67 by Tamar Christina at 2020-07-26T13:25:11-04:00
winio: fix detection of tty terminals

- - - - -
52685cf7 by Tamar Christina at 2020-07-26T13:25:48-04:00
winio: update codeowners

- - - - -
aee45d9e by Vladislav Zavialov at 2020-07-27T07:06:56-04:00
Improve NegativeLiterals (#18022, GHC Proposal #344)

Before this patch, NegativeLiterals used to parse x-1 as x (-1).

This may not be what the user expects, and now it is fixed:
x-1 is parsed as (-) x 1.

We achieve this by the following requirement:

  * When lexing a negative literal,
    it must not be preceded by a 'closing token'.

This also applies to unboxed literals, e.g. -1#.

See GHC Proposal #229 for the definition of a closing token.

A nice consequence of this change is that -XNegativeLiterals becomes a
subset of -XLexicalNegation. In other words, enabling both of those
extensions has the same effect as enabling -XLexicalNegation alone.

- - - - -
667ab69e by leiftw at 2020-07-27T07:07:32-04:00
fix typo referring to non-existent `-ohidir` flag, should be `-hidir` I think
- - - - -
6ff89c17 by Vladislav Zavialov at 2020-07-27T07:08:07-04:00
Refactor the parser a little

* Create a dedicated production for type operators
* Create a dedicated type for the UNPACK pragma
* Remove an outdated part of Note [Parsing data constructors is hard]

- - - - -
0624a8b0 by Ben Gamari at 2020-07-27T16:20:40-04:00
testsuite: Allow baseline commit to be set explicitly

- - - - -
ec31a37c by Ben Gamari at 2020-07-27T16:20:40-04:00
gitlab-ci: Use MR base commit as performance baseline

- - - - -


30 changed files:

- .gitlab-ci.yml
- .gitlab/ci.sh
- .gitlab/test-metrics.sh
- CODEOWNERS
- Makefile
- compiler/GHC.hs
- compiler/GHC/Builtin/Names.hs
- compiler/GHC/Builtin/Names/TH.hs
- compiler/GHC/Builtin/PrimOps.hs
- + compiler/GHC/Builtin/RebindableNames.hs
- compiler/GHC/Builtin/Types.hs
- compiler/GHC/Builtin/Types/Prim.hs
- compiler/GHC/Builtin/Utils.hs
- compiler/GHC/Builtin/primops.txt.pp
- compiler/GHC/ByteCode/InfoTable.hs
- compiler/GHC/Cmm/CLabel.hs
- compiler/GHC/Cmm/CallConv.hs
- compiler/GHC/Cmm/Graph.hs
- compiler/GHC/Cmm/Info.hs
- compiler/GHC/Cmm/Info/Build.hs
- compiler/GHC/Cmm/LayoutStack.hs
- compiler/GHC/Cmm/Monad.hs
- compiler/GHC/Cmm/Parser.y
- compiler/GHC/Cmm/Pipeline.hs
- compiler/GHC/Cmm/Sink.hs
- compiler/GHC/Cmm/Switch.hs
- compiler/GHC/Cmm/Switch/Implement.hs
- compiler/GHC/Cmm/Type.hs
- compiler/GHC/Cmm/Utils.hs
- compiler/GHC/CmmToAsm.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/9636134e798e5964526dd0c5a82d025f8bf2518d...ec31a37c518785c69253e6d5627245b166f73e72

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/9636134e798e5964526dd0c5a82d025f8bf2518d...ec31a37c518785c69253e6d5627245b166f73e72
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/20200727/c90592b8/attachment-0001.html>


More information about the ghc-commits mailing list