[Git][ghc/ghc][wip/T18282] 19 commits: Enable large address space optimization on windows.

Ben Gamari gitlab at gitlab.haskell.org
Fri Jun 26 03:08:19 UTC 2020



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


Commits:
03a708ba by Andreas Klebinger at 2020-06-25T03:54:37-04:00
Enable large address space optimization on windows.

Starting with Win 8.1/Server 2012 windows no longer preallocates
page tables for reserverd memory eagerly, which prevented us from
using this approach in the past.

We also try to allocate the heap high in the memory space.
Hopefully this makes it easier to allocate things in the low
4GB of memory that need to be there. Like jump islands for the
linker.

- - - - -
7e6d3d09 by Roland Senn at 2020-06-25T03:54:38-04:00
In `:break ident` allow out of scope and nested identifiers (Fix #3000)

This patch fixes the bug and implements the feature request of #3000.

1. If `Module` is a real module name and `identifier` a name of a
top-level function in `Module` then `:break Module.identifer` works
also for an `identifier` that is out of scope.

2. Extend the syntax for `:break identifier` to:

    :break [ModQual.]topLevelIdent[.nestedIdent]...[.nestedIdent]

`ModQual` is optional and is either the effective name of a module or
the local alias of a qualified import statement.

`topLevelIdent` is the name of a top level function in the module
referenced by `ModQual`.

`nestedIdent` is optional and the name of a function nested in a let or
where clause inside the previously mentioned function `nestedIdent` or
`topLevelIdent`.

If `ModQual` is a module name, then `topLevelIdent` can be any top level
identifier in this module. If `ModQual` is missing or a local alias of a
qualified import, then `topLevelIdent` must be in scope.

Breakpoints can be set on arbitrarily deeply nested functions, but the
whole chain of nested function names must be specified.

3. To support the new functionality rewrite the code to tab complete `:break`.

- - - - -
30e42652 by Ben Gamari at 2020-06-25T03:54:39-04:00
make: Respect XELATEX variable

Previously we simply ignored the XELATEX variable when building
PDF documentation.

- - - - -
4acc2934 by Ben Gamari at 2020-06-25T03:54:39-04:00
hadrian/make: Detect makeindex

Previously we would simply assume that makeindex was available.
Now we correctly detect it in `configure` and respect this conclusion in
hadrian and make.

- - - - -
0d61f866 by Simon Peyton Jones at 2020-06-25T03:54:40-04:00
Expunge GhcTcId

GHC.Hs.Extension had

  type GhcPs   = GhcPass 'Parsed
  type GhcRn   = GhcPass 'Renamed
  type GhcTc   = GhcPass 'Typechecked
  type GhcTcId = GhcTc

The last of these, GhcTcId, is a vestige of the past.

This patch expunges it from GHC.

- - - - -
8ddbed4a by Adam Wespiser at 2020-06-25T03:54:40-04:00
add examples to Data.Traversable

- - - - -
284001d0 by Oleg Grenrus at 2020-06-25T03:54:42-04:00
Export readBinIface_

- - - - -
90f43872 by Zubin Duggal at 2020-06-25T03:54:43-04:00
Export everything from HsToCore.

This lets us reuse these functions in haddock, avoiding synchronization bugs.

Also fixed some divergences with haddock in that file

Updates haddock submodule

- - - - -
c7dd6da7 by Takenobu Tani at 2020-06-25T03:54:44-04:00
Clean up haddock hyperlinks of GHC.* (part1)

This updates haddock comments only.

This patch focuses to update for hyperlinks in GHC API's haddock comments,
because broken links especially discourage newcomers.

This includes the following hierarchies:
  - GHC.Hs.*
  - GHC.Core.*
  - GHC.Stg.*
  - GHC.Cmm.*
  - GHC.Types.*
  - GHC.Data.*
  - GHC.Builtin.*
  - GHC.Parser.*
  - GHC.Driver.*
  - GHC top

- - - - -
1eb997a8 by Takenobu Tani at 2020-06-25T03:54:44-04:00
Clean up haddock hyperlinks of GHC.* (part2)

This updates haddock comments only.

This patch focuses to update for hyperlinks in GHC API's haddock comments,
because broken links especially discourage newcomers.

This includes the following hierarchies:

  - GHC.Iface.*
  - GHC.Llvm.*

  - GHC.Rename.*
  - GHC.Tc.*

  - GHC.HsToCore.*
  - GHC.StgToCmm.*
  - GHC.CmmToAsm.*

  - GHC.Runtime.*

  - GHC.Unit.*
  - GHC.Utils.*
  - GHC.SysTools.*

- - - - -
67a86b4d by Oleg Grenrus at 2020-06-25T03:54:46-04:00
Add MonadZip and MonadFix instances for Complex

These instances are taken from
https://hackage.haskell.org/package/linear-1.21/docs/Linear-Instances.html

They are the unique possible, so let they be in `base`.

- - - - -
c50ef26e by Artem Pelenitsyn at 2020-06-25T03:54:47-04:00
test suite: add reproducer for #17516

- - - - -
fe281b27 by Roland Senn at 2020-06-25T03:54:48-04:00
Enable maxBound checks for OverloadedLists (Fixes #18172)

Consider the Literal `[256] :: [Data.Word.Word8]`

When the `OverloadedLists` extension is not active, then the `ol_ext` field
in the `OverLitTc` record that is passed to the function `getIntegralLit`
contains the type `Word8`. This is a simple type, and we can use its
type constructor immediately for the `warnAboutOverflowedLiterals` function.

When the `OverloadedLists` extension is active, then the `ol_ext` field
contains the type family `Item [Word8]`. The function `nomaliseType` is used
to convert it to the needed type `Word8`.

- - - - -
a788d4d1 by Ben Gamari at 2020-06-25T03:54:52-04:00
rts/Hash: Simplify freeing of HashListChunks

While looking at #18348 I noticed that the treatment of HashLists are a
bit more complex than necessary (which lead to some initial confusion on
my part). Specifically, we allocate HashLists in chunks. Each chunk
allocation makes two allocations: one for the chunk itself and one for a
HashListChunk to link together the chunks for the purposes of freeing.

Simplify this (and hopefully make the relationship between these
clearer) but allocating the HashLists and HashListChunk in a single
malloc. This will both make the implementation easier to follow and
reduce C heap fragmentation.

Note that even after this patch we fail to bound the size of the free
HashList pool. However, this is a separate bug.

- - - - -
d3c2d59b by Sylvain Henry at 2020-06-25T03:54:55-04:00
RTS: avoid overflow on 32-bit arch (#18375)

We're now correctly computing allocated bytes on 32-bit arch, so we get
huge increases.

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

- - - - -
a3d69dc6 by Sebastian Graf at 2020-06-25T23:06:18-04:00
GHC.Core.Unify: Make UM actions one-shot by default

This MR makes the UM monad in GHC.Core.Unify into a one-shot
monad.  See the long Note [The one-shot state monad trick].

See also #18202 and !3309, which applies this to all Reader/State-like
monads in GHC for compile-time perf improvements. The pattern used
here enables something similar to the state-hack, but is applicable to
user-defined monads, not just `IO`.

Metric Decrease 'runtime/bytes allocated' (test_env='i386-linux-deb9'):
    haddock.Cabal

- - - - -
3f889ad5 by Simon Peyton Jones at 2020-06-25T23:08:17-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.

- - - - -
2d7f3b2e by Simon Peyton Jones at 2020-06-25T23:08:17-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.

- - - - -
bcfcd275 by Simon Peyton Jones at 2020-06-25T23:08:17-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

- - - - -


30 changed files:

- compiler/GHC.hs
- compiler/GHC/Builtin/Types.hs
- compiler/GHC/Builtin/Types/Prim.hs
- compiler/GHC/Builtin/Utils.hs
- compiler/GHC/ByteCode/Types.hs
- compiler/GHC/Cmm/CLabel.hs
- compiler/GHC/Cmm/Dataflow/Block.hs
- compiler/GHC/Cmm/Info.hs
- compiler/GHC/CmmToAsm/CFG.hs
- compiler/GHC/CmmToAsm/Dwarf/Constants.hs
- compiler/GHC/CmmToAsm/Monad.hs
- compiler/GHC/CmmToAsm/Reg/Graph/SpillClean.hs
- compiler/GHC/CmmToAsm/SPARC/CodeGen/Base.hs
- compiler/GHC/Core.hs
- compiler/GHC/Core/Class.hs
- compiler/GHC/Core/Coercion.hs
- compiler/GHC/Core/DataCon.hs
- compiler/GHC/Core/FVs.hs
- compiler/GHC/Core/InstEnv.hs
- compiler/GHC/Core/Lint.hs
- compiler/GHC/Core/Make.hs
- compiler/GHC/Core/Map.hs
- compiler/GHC/Core/Opt/Arity.hs
- compiler/GHC/Core/Opt/OccurAnal.hs
- compiler/GHC/Core/Opt/Simplify.hs
- compiler/GHC/Core/Opt/Simplify/Utils.hs
- compiler/GHC/Core/Rules.hs
- compiler/GHC/Core/SimpleOpt.hs
- compiler/GHC/Core/Subst.hs
- compiler/GHC/Core/TyCo/FVs.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/24966551c7d9dc9e56662b7bd9f77cd2b8714bf8...bcfcd27528d6b7794b7ca778eaed444c979b9282

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/24966551c7d9dc9e56662b7bd9f77cd2b8714bf8...bcfcd27528d6b7794b7ca778eaed444c979b9282
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/20200625/e9da6b1f/attachment-0001.html>


More information about the ghc-commits mailing list