[Git][ghc/ghc][wip/T18550] 80 commits: hadrian: depend on boot compiler version #18001

Ben Gamari gitlab at gitlab.haskell.org
Thu Sep 3 22:28:28 UTC 2020



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


Commits:
a11c9678 by Adam Sandberg Ericsson at 2020-08-09T11:32:25+02:00
hadrian: depend on boot compiler version #18001

- - - - -
c8873b52 by Alan Zimmerman at 2020-08-09T21:17:54-04:00
Api Annotations : Adjust SrcSpans for prefix bang (!).

And prefix ~

(cherry picked from commit 8dbee2c578b1f642d45561be3f416119863e01eb)

- - - - -
77398b67 by Sylvain Henry at 2020-08-09T21:18:34-04:00
Avoid allocations in `splitAtList` (#18535)

As suspected by @simonpj in #18535, avoiding allocations in
`GHC.Utils.Misc.splitAtList` when there are no leftover arguments is
beneficial for performance:

   On CI validate-x86_64-linux-deb9-hadrian:
    T12227 -7%
    T12545 -12.3%
    T5030  -10%
    T9872a -2%
    T9872b -2.1%
    T9872c -2.5%

Metric Decrease:
    T12227
    T12545
    T5030
    T9872a
    T9872b
    T9872c

- - - - -
8ba41a0f by Felix Yan at 2020-08-10T20:23:29-04:00
Correct a typo in ghc.mk
- - - - -
1c469264 by Felix Yan at 2020-08-10T20:23:29-04:00
Add a closing parenthesis too

- - - - -
acf537f9 by Sylvain Henry at 2020-08-10T20:24:09-04:00
Make splitAtList strict in its arguments

Also fix its slightly wrong comment

Metric Decrease:
    T5030
    T12227
    T12545

- - - - -
ab4d1589 by Ben Gamari at 2020-08-11T22:18:03-04:00
typecheck: Drop SPECIALISE pragmas when there is no unfolding

Previously the desugarer would instead fall over when it realized that
there was no unfolding for an imported function with a SPECIALISE
pragma. We now rather drop the SPECIALISE pragma and throw a warning.

Fixes #18118.

- - - - -
0ac8c0a5 by Ben Gamari at 2020-08-11T22:18:03-04:00
testsuite: Add test for #18118

- - - - -
c43078d7 by Sven Tennie at 2020-08-11T22:18:38-04:00
Add hie.yaml to ghc-heap

This enables IDE support by haskell-language-server for ghc-heap.

- - - - -
f1088b3f by Ben Gamari at 2020-08-11T22:19:15-04:00
testsuite: Specify metrics collected by T17516

Previously it collected everything, including "max bytes used". This is
problematic since the test makes no attempt to control for deviations in
GC timing, resulting in high variability. Fix this by only collecting
"bytes allocated".

- - - - -
accbc242 by Sylvain Henry at 2020-08-12T03:50:12-04:00
DynFlags: disentangle Outputable

- put panic related functions into GHC.Utils.Panic
- put trace related functions using DynFlags in GHC.Driver.Ppr

One step closer making Outputable fully independent of DynFlags.

Bump haddock submodule

- - - - -
db6dd810 by Ben Gamari at 2020-08-12T03:50:48-04:00
testsuite: Increase tolerance of T16916

T16916 (testing #16916) has been slightly fragile in CI due to its
reliance on CPU times. While it's hard to see how to eliminate
the time-dependence entirely, we can nevertheless make it more tolerant.

Fixes #16966.

- - - - -
bee43aca by Sylvain Henry at 2020-08-12T20:52:50-04:00
Rewrite and move the monad-state hack note

The note has been rewritten by @simonpj in !3851

[skip ci]

- - - - -
25fdf25e by Alan Zimmerman at 2020-08-12T20:53:26-04:00
ApiAnnotations: Fix parser for new GHC 9.0 features

- - - - -
7831fe05 by Ben Gamari at 2020-08-13T03:44:17-04:00
parser: Suggest ImportQualifiedPost in prepositive import warning

As suggested in #18545.

- - - - -
55dec4dc by Sebastian Graf at 2020-08-13T03:44:52-04:00
PmCheck: Better long-distance info for where bindings (#18533)

Where bindings can see evidence from the pattern match of the `GRHSs`
they belong to, but not from anything in any of the guards (which belong
to one of possibly many RHSs).

Before this patch, we did *not* consider said evidence, causing #18533,
where the lack of considering type information from a case pattern match
leads to failure to resolve the vanilla COMPLETE set of a data type.

Making available that information required a medium amount of
refactoring so that `checkMatches` can return a
`[(Deltas, NonEmpty Deltas)]`; one `(Deltas, NonEmpty Deltas)` for each
`GRHSs` of the match group. The first component of the pair is the
covered set of the pattern, the second component is one covered set per
RHS.

Fixes #18533.
Regression test case: T18533

- - - - -
cf97889a by Hécate at 2020-08-13T03:45:29-04:00
Re-add BangPatterns to CodePage.hs

- - - - -
ffc0d578 by Sylvain Henry at 2020-08-13T09:49:56-04:00
Add HomeUnit type

Since Backpack the "home unit" is much more involved than what it was
before (just an identifier obtained with `-this-unit-id`). Now it is
used in conjunction with `-component-id` and `-instantiated-with` to
configure module instantiations and to detect if we are type-checking an
indefinite unit or compiling a definite one.

This patch introduces a new HomeUnit datatype which is much easier to
understand. Moreover to make GHC support several packages in the same
instances, we will need to handle several HomeUnits so having a
dedicated (documented) type is helpful.

Finally in #14335 we will also need to handle the case where we have no
HomeUnit at all because we are only loading existing interfaces for
plugins which live in a different space compared to units used to
produce target code. Several functions will have to be refactored to
accept "Maybe HomeUnit" parameters instead of implicitly querying the
HomeUnit fields in DynFlags. Having a dedicated type will make this
easier.

Bump haddock submodule

- - - - -
8a51b2ab by Sylvain Henry at 2020-08-13T21:09:15-04:00
Make IOEnv monad one-shot (#18202)

On CI (x86_64-linux-deb9-hadrian, compile_time/bytes_allocated):

    T10421     -1.8%    (threshold: +/- 1%)
    T10421a    -1.7%    (threshold: +/- 1%)
    T12150     -4.9%    (threshold: +/- 2%)
    T12227     -1.6     (threshold: +/- 1%)
    T12425     -1.5%    (threshold: +/- 1%)
    T12545     -3.8%    (threshold: +/- 1%)
    T12707     -3.0%    (threshold: +/- 1%)
    T13035     -3.0%    (threshold: +/- 1%)
    T14683     -10.3%   (threshold: +/- 2%)
    T3064      -6.9%    (threshold: +/- 2%)
    T4801      -4.3%    (threshold: +/- 2%)
    T5030      -2.6%    (threshold: +/- 2%)
    T5321FD    -3.6%    (threshold: +/- 2%)
    T5321Fun   -4.6%    (threshold: +/- 2%)
    T5631      -19.7%   (threshold: +/- 2%)
    T5642      -13.0%   (threshold: +/- 2%)
    T783       -2.7     (threshold: +/- 2%)
    T9020      -11.1    (threshold: +/- 2%)
    T9961      -3.4%    (threshold: +/- 2%)

    T1969 (compile_time/bytes_allocated)  -2.2%  (threshold: +/-1%)
    T1969 (compile_time/max_bytes_used)   +24.4% (threshold: +/-20%)

Additionally on other CIs:

    haddock.Cabal                  -10.0%   (threshold: +/- 5%)
    haddock.compiler               -9.5%    (threshold: +/- 5%)
    haddock.base (max bytes used)  +24.6%   (threshold: +/- 15%)
    T10370 (max bytes used, i386)  +18.4%   (threshold: +/- 15%)

Metric Decrease:
    T10421
    T10421a
    T12150
    T12227
    T12425
    T12545
    T12707
    T13035
    T14683
    T3064
    T4801
    T5030
    T5321FD
    T5321Fun
    T5631
    T5642
    T783
    T9020
    T9961
    haddock.Cabal
    haddock.compiler
Metric Decrease 'compile_time/bytes allocated':
    T1969
Metric Increase 'compile_time/max_bytes_used':
    T1969
    T10370
    haddock.base

- - - - -
9f66fdf6 by Ben Gamari at 2020-08-14T15:50:34-04:00
testsuite: Drop --io-manager flag from testsuite configuration

This is no longer necessary as there are now dedicated testsuite ways
which run tests with WinIO.

- - - - -
55fd1dc5 by Ben Gamari at 2020-08-14T15:51:10-04:00
llvm-targets: Add i686 targets

Addresses #18422.

- - - - -
f4cc57fa by Ben Gamari at 2020-08-18T15:38:55-04:00
Allow unsaturated runRW# applications

Previously we had a very aggressive Core Lint check which caught
unsaturated applications of runRW#. However, there is nothing
wrong with such applications and they may naturally arise in desugared
Core. For instance, the desugared Core of Data.Primitive.Array.runArray#
from the `primitive` package contains:

    case ($) (runRW# @_ @_) (\s -> ...) of ...

In this case it's almost certain that ($) will be inlined, turning the
application into a saturated application. However, even if this weren't
the case there isn't a problem: CorePrep (after deleting an unnecessary
case) can simply generate code in its usual way, resulting in a call to
the Haskell definition of runRW#.

Fixes #18291.

- - - - -
3ac6ae7c by Ben Gamari at 2020-08-18T15:38:55-04:00
testsuite: Add test for #18291

- - - - -
a87a0b49 by Eli Schwartz at 2020-08-18T15:39:30-04:00
install: do not install sphinx doctrees

These files are 100% not needed at install time, and they contain
unreproducible info. See https://reproducible-builds.org/ for why this
matters.

- - - - -
194b25ee by Ben Gamari at 2020-08-18T15:40:05-04:00
testsuite: Allow baseline commit to be set explicitly

- - - - -
fdcf7645 by Ben Gamari at 2020-08-18T15:40:05-04:00
gitlab-ci: Use MR base commit as performance baseline

- - - - -
9ad5cab3 by Fendor at 2020-08-18T15:40:42-04:00
Expose UnitInfoMap as it is part of the public API

- - - - -
aa4b744d by Ben Gamari at 2020-08-18T22:11:36-04:00
testsuite: Only run llvm ways if llc is available

As noted in #18560, we previously would always run the LLVM ways since
`configure` would set `SettingsLlcCommand` to something non-null when
it otherwise couldn't find the `llc` executable. Now we rather probe for
the existence of the `llc` executable in the testsuite driver.

Fixes #18560.

- - - - -
0c5ed5c7 by Sylvain Henry at 2020-08-18T22:12:13-04:00
DynFlags: refactor GHC.CmmToAsm (#17957, #10143)

This patch removes the use of `sdocWithDynFlags` from GHC.CmmToAsm.*.Ppr

To do that I've had to make some refactoring:

* X86' and PPC's `Instr` are no longer `Outputable` as they require a
  `Platform` argument

* `Instruction` class now exposes `pprInstr :: Platform -> instr -> SDoc`

* as a consequence, I've refactored some modules to avoid .hs-boot files

* added (derived) functor instances for some datatypes parametric in the
  instruction type. It's useful for pretty-printing as we just have to
  map `pprInstr` before pretty-printing the container datatype.

- - - - -
731c8d3b by nineonine at 2020-08-19T18:47:39-04:00
Implement -Wredundant-bang-patterns (#17340)

Add new flag '-Wredundant-bang-patterns' that enables checks for "dead" bangs.
Dead bangs are the ones that under no circumstances can force a thunk that
wasn't already forced. Dead bangs are a form of redundant bangs. The new check
is performed in Pattern-Match Coverage Checker along with other checks (namely,
redundant and inaccessible RHSs). Given

    f :: Bool -> Int
    f True = 1
    f !x   = 2

we can detect dead bang patterns by checking whether @x ~ ⊥@ is satisfiable
where the PmBang appears in 'checkGrdTree'. If not, then clearly the bang is
dead. Such a dead bang is then indicated in the annotated pattern-match tree by
a 'RedundantSrcBang' wrapping. In 'redundantAndInaccessibles', we collect
all dead bangs to warn about.

Note that we don't want to warn for a dead bang that appears on a redundant
clause. That is because in that case, we recommend to delete the clause wholly,
including its leading pattern match.

Dead bang patterns are redundant. But there are bang patterns which are
redundant that aren't dead, for example

    f !() = 0

the bang still forces the match variable, before we attempt to match on (). But
it is redundant with the forcing done by the () match. We currently don't
detect redundant bangs that aren't dead.

- - - - -
eb9bdaef by Simon Peyton Jones at 2020-08-19T18:48:14-04:00
Add right-to-left rule for pattern bindings

Fix #18323 by adding a few lines of code to handle non-recursive
pattern bindings.  see GHC.Tc.Gen.Bind
Note [Special case for non-recursive pattern bindings]

Alas, this confused the pattern-match overlap checker; see #18323.

Note that this patch only affects pattern bindings like that
for (x,y) in this program

  combine :: (forall a . [a] -> a) -> [forall a. a -> a]
          -> ((forall a . [a] -> a), [forall a. a -> a])

  breaks = let (x,y) = combine head ids
           in x y True

We need ImpredicativeTypes for those [forall a. a->a] types to be
valid. And with ImpredicativeTypes the old, unprincipled "allow
unification variables to unify with a polytype" story actually
works quite well. So this test compiles fine (if delicatedly) with
old GHCs; but not with QuickLook unless we add this patch

- - - - -
293c7fba by Sylvain Henry at 2020-08-21T09:36:38-04:00
Put CFG weights into their own module (#17957)

It avoids having to query DynFlags to get them

- - - - -
50eb4460 by Sylvain Henry at 2020-08-21T09:36:38-04:00
Don't use DynFlags in CmmToAsm.BlockLayout (#17957)

- - - - -
659eb31b by Sylvain Henry at 2020-08-21T09:36:38-04:00
NCG: Dwarf configuration

* remove references to DynFlags in GHC.CmmToAsm.Dwarf
* add specific Dwarf options in NCGConfig instead of directly querying
  the debug level

- - - - -
2d8ca917 by Sylvain Henry at 2020-08-21T09:37:15-04:00
Fix -ddump-stg flag

-ddump-stg was dumping the initial STG (just after Core-to-STG pass)
which was misleading because we want the final STG to know if a function
allocates or not. Now we have a new flag -ddump-stg-from-core for this and
-ddump-stg is deprecated.

- - - - -
fddddbf4 by Vladislav Zavialov at 2020-08-21T09:37:49-04:00
Import qualified Prelude in Cmm/Parser.y

In preparation for the next version of 'happy', c95920 added a qualified
import to GHC/Parser.y but for some reason neglected GHC/Cmm/Parser.y

This patch adds the missing qualified import to GHC/Cmm/Parser.y and
also adds a clarifying comment to explain why this import is needed.

- - - - -
989c1c27 by Ben Gamari at 2020-08-21T11:27:53-04:00
gitlab-ci: Test master branch as well

While these builds are strictly speaking redundant (since every commit
is tested by @marge-bot before making it into `master`), they are nevertheless
useful as they are displayed in the branch's commit list in GitLab's web interface.

Fixes #18595.
- - - - -
e67ae884 by Aditya Gupta at 2020-08-22T03:29:00-04:00
mkUnique refactoring (#18362)

Move uniqFromMask from Unique.Supply to Unique.
Move the the functions that call mkUnique from Unique to Builtin.Uniques

- - - - -
03cfcfd4 by Wander Hillen at 2020-08-22T03:29:36-04:00
Add ubuntu 20.04 jobs for nightly and release

- - - - -
3f501545 by Craig Ferguson at 2020-08-22T03:30:13-04:00
Utils: clarify docs slightly

The previous comment implies `nTimes n f` is either `f^{n+1}` or
`f^{2^n}` (when in fact it's `f^n`).

- - - - -
8b865092 by Krzysztof Gogolewski at 2020-08-23T14:12:53+02:00
Do not print synonyms in :i (->), :i Type (#18594)

This adds a new printing flag `sdocPrintTypeAbbreviations` that is used
specifically to avoid ghci printing 'type (->) = (->)' and 'type Type = Type'.

- - - - -
d8f61182 by Krzysztof Gogolewski at 2020-08-23T14:12:56+02:00
Move pprTyTcApp' inside pprTyTcApp

No semantic change

- - - - -
364258e0 by Krzysztof Gogolewski at 2020-08-24T00:32:31-04:00
Fix types in silly shifts (#18589)

Patch written by Simon. I have only added a testcase.

- - - - -
b1eb38a0 by Sylvain Henry at 2020-08-24T00:33:13-04:00
Perf: make SDoc monad one-shot (#18202)

With validate-x86_64-linux-deb9-hadrian:
   T1969  -3.4% (threshold: +/-1%)
   T3294  -3.3% (threshold: +/-1%)
   T12707 -1.4% (threshold: +/-1%)

Additionally with validate-x86_64-linux-deb9-unreg-hadrian:
   T4801  -2.4% (threshold: +/-2%)
   T13035 -1.4% (threshold: +/-1%)
   T13379 -2.4% (threshold: +/-2%)
   ManyAlternatives -2.5% (threshold: +/-2%)
   ManyConstructors -3.0% (threshold: +/-2%)

Metric Decrease:
    T12707
    T1969
    T3294
    ManyAlternatives
    ManyConstructors
    T13035
    T13379
    T4801

- - - - -
a77b9ec2 by Krzysztof Gogolewski at 2020-08-24T10:04:20-04:00
Add a test for #18397

The bug was fixed by !3421.

- - - - -
05550a5a by Sylvain Henry at 2020-08-24T10:04:59-04:00
Avoid roundtrip through SDoc

As found by @monoidal on https://gitlab.haskell.org/ghc/ghc/-/merge_requests/3885#note_295126

- - - - -
0a1ecc5f by Ben Gamari at 2020-08-25T07:37:05-04:00
SysTools.Process: Handle exceptions in readCreateProcessWithExitCode'

In #18069 we are observing MVar deadlocks from somewhere in ghc.exe.
This use of MVar stood out as being one of the more likely culprits.
Here we make sure that it is exception-safe.

- - - - -
db8793ad by Richard Eisenberg at 2020-08-25T07:37:40-04:00
Use tcView, not coreView, in the pure unifier.

Addresses a lingering point within #11715.

- - - - -
fb77207a by Simon Peyton Jones at 2020-08-25T07:38:16-04:00
Use LIdP rather than (XRec p (IdP p))

This patch mainly just replaces use of
    XRec p (IdP p)
with
    LIdP p

One slightly more significant change is to parameterise
HsPatSynDetails over the pass rather than the argument type,
so that it's uniform with HsConDeclDetails and HsConPatDetails.

I also got rid of the dead code GHC.Hs.type.conDetailsArgs

But this is all just minor refactoring. No change in functionality.

- - - - -
8426a136 by Krzysztof Gogolewski at 2020-08-25T07:38:54-04:00
Add a test for #18585

- - - - -
2d635a50 by Takenobu Tani at 2020-08-26T04:50:21-04:00
linters: Make CPP linter skip image files

This patch adds an exclusion rule for `docs/users_guide/images`,
to avoid lint errors of PDF files.

- - - - -
b7d98cb2 by Takenobu Tani at 2020-08-26T04:50:21-04:00
users-guide: Color the logo on the front page of the PDF

This patch updates the logo with a recent color scheme.
This affects only the PDF version of the user's guide.

See also:
* https://mail.haskell.org/pipermail/ghc-devs/2020-August/019139.html
* https://gitlab.haskell.org/ghc/ghc/-/wikis/logo

- - - - -
0b17fa18 by Sylvain Henry at 2020-08-26T04:50:58-04:00
Refactor UnitId pretty-printing

When we pretty-print a UnitId for the user, we try to map it back to its
origin package name, version and component to print
"package-version:component" instead of some hash.

The UnitId type doesn't carry these information, so we have to look into
a UnitState to find them. This is why the Outputable instance of
UnitId used `sdocWithDynFlags` in order to access the `unitState` field
of DynFlags.

This is wrong for several reasons:

1. The DynFlags are accessed when the message is printed, not when it is
   generated. So we could imagine that the unitState may have changed
   in-between. Especially if we want to allow unit unloading.

2. We want GHC to support several independent sessions at once, hence
   several UnitState. The current approach supposes there is a unique
   UnitState as a UnitId doesn't indicate which UnitState to use.

See the Note [Pretty-printing UnitId] in GHC.Unit for the new approach
implemented by this patch.

One step closer to remove `sdocDynFlags` field from `SDocContext`
(#10143).

Fix #18124.

Also fix some Backpack code to use SDoc instead of String.

- - - - -
dc476a50 by Sylvain Henry at 2020-08-26T04:51:35-04:00
Bignum: fix BigNat subtraction (#18604)

There was a confusion between the boolean expected by
withNewWordArrayTrimedMaybe and the boolean returned by subtracting
functions.

- - - - -
fcb10b6c by Peter Trommler at 2020-08-26T10:42:30-04:00
PPC and X86: Portable printing of IEEE floats

GNU as and the AIX assembler support floating point literals.
SPARC seems to have support too but I cannot test on SPARC.
Curiously, `doubleToBytes` is also used in the LLVM backend.

To avoid endianness issues when cross-compiling float and double literals
are printed as C-style floating point values. The assembler then takes
care of memory layout and endianness.

This was brought up in #18431 by @hsyl20.

- - - - -
770100e0 by Krzysztof Gogolewski at 2020-08-26T10:43:13-04:00
primops: Remove Monadic and Dyadic categories

There were four categories of primops: Monadic, Dyadic, Compare, GenPrimOp.

The compiler does not treat Monadic and Dyadic in any special way,
we can just replace them with GenPrimOp.

Compare is still used in isComparisonPrimOp.

- - - - -
01ff8c89 by Aditya Gupta at 2020-08-27T14:19:26-04:00
Consolidate imports in getMinimalImports (#18264)

- - - - -
bacccb73 by Ryan Scott at 2020-08-27T14:20:01-04:00
Make {hsExpr,hsType,pat}NeedsParens aware of boxed 1-tuples

`hsExprNeedsParens`, `hsTypeNeedsParens`, and `patNeedsParens`
previously assumed that all uses of explicit tuples in the source
syntax never need to be parenthesized. This is true save for one
exception: boxed one-tuples, which use the `Solo` data type from
`GHC.Tuple` instead of special tuple syntax. This patch adds the
necessary logic to the three `*NeedsParens` functions to handle
`Solo` correctly.

Fixes #18612.

- - - - -
c6f50cea by Krzysztof Gogolewski at 2020-08-28T02:22:36-04:00
Add missing primop documentation (#18454)

- Add three pseudoops to primops.txt.pp, so that Haddock renders
  the documentation
- Update comments
- Remove special case for "->" - it's no longer exported from GHC.Prim
- Remove reference to Note [Compiling GHC.Prim] - the ad-hoc fix is no
  longer there after updates to levity polymorphism.
- Document GHC.Prim
- Remove the comment that lazy is levity-polymorphic.
  As far as I can tell, it never was: in 80e399639,
  only the unfolding was given an open type variable.
- Remove haddock hack in GHC.Magic - no longer neccessary after
  adding realWorld# to primops.txt.pp.

- - - - -
f065b6b0 by Tamar Christina at 2020-08-28T02:23:13-04:00
Fix use distro toolchian

- - - - -
4517a382 by Tamar Christina at 2020-08-28T02:23:13-04:00
document how build system find toolchains on Windows

- - - - -
329f7cb9 by Ben Gamari at 2020-08-31T22:59:14-04:00
base: Better error message on invalid getSystemTimerManager call

Previously we would produce a rather unhelpful pattern match failure
error in the case where the user called `getSystemTimerManager` in a
program which isn't built with `-threaded`. This understandably confused
the user in #15616.

Fixes #15616.

- - - - -
f6d70a8f by Roland Senn at 2020-08-31T22:59:50-04:00
Add tests for #15617.

Avoid a similar regression in the future.

- - - - -
e5969fd0 by Roland Senn at 2020-08-31T23:00:27-04:00
Add additional tests for #18172 (Followup MR 3543)

There was still one active discussion [thread](https://gitlab.haskell.org/ghc/ghc/-/merge_requests/3543#note_284325) when MR !3543 got merged.

This MR adds the requested tests exercising the changes in
`compiler/GHC/HsToCore/Match/Literal.hs:warnAboutEmptyEnumerations` and its sub-functions.

- - - - -
fe18b482 by Ben Gamari at 2020-08-31T23:01:02-04:00
Bump Win32 and process submodules

- - - - -
2da93308 by Sylvain Henry at 2020-08-31T23:01:39-04:00
Hadrian: fix slow-validate flavour (#18586)

- - - - -
85e13008 by Andreas Klebinger at 2020-08-31T23:02:15-04:00
Update dominator code with fixes from the dom-lt package.

Two bugs turned out in the package that have been fixed since.
This MR includes this fixes in the GHC port of the code.

- - - - -
dffb38fa by Andreas Klebinger at 2020-08-31T23:02:15-04:00
Dominators.hs: Use unix line endings

- - - - -
6189cc04 by Moritz Angermann at 2020-08-31T23:02:50-04:00
[fixup 3433] move debugBelch into IF_DEBUG(linker)

The commit in dff1cb3d9c111808fec60190747272b973547c52 incorrectly left
the `debugBelch` function without a comment or IF_DEBUG(linker,)
decoration. This rectifies it.

Needs at least a 8.10 backport, as it was backported in 6471cc6aff80d5deebbdb1bf7b677b31ed2af3d5

- - - - -
bcb68a3f by Sylvain Henry at 2020-08-31T23:03:27-04:00
Don't store HomeUnit in UnitConfig

Allow the creation of a UnitConfig (hence of a UnitState) without having
a HomeUnit. It's required for #14335.

- - - - -
0a372387 by Sylvain Henry at 2020-08-31T23:04:04-04:00
Fix documentation and fix "check" bignum backend (#18604)

- - - - -
eb85f125 by Moritz Angermann at 2020-08-31T23:04:39-04:00
Set the dynamic-system-linker flag to Manual

This flag should be user controllable, hence Manual: True.

- - - - -
380ef845 by Sven Tennie at 2020-08-31T23:05:14-04:00
Ignore more files

Ignore files from "new style" cabal builds (dist-newstyle folders) and
from clangd (C language server).

- - - - -
74a7fbff by Takenobu Tani at 2020-08-31T23:05:51-04:00
Limit upper version of Happy for ghc-9.0 and earlier (#18620)

This patch adds the upper bound of a happy version for ghc-9.0
and earlier.

Currently, we can't use happy-1.20.0 for ghc-9.0.

See #18620.

- - - - -
a4473f02 by Takenobu Tani at 2020-08-31T23:05:51-04:00
Limit upper version of Happy for ghc-9.2 (#18620)

This patch adds the upper bound of a happy version for ghc-9.2.

Currently, We can use happy-1.19 or happy-1.20 for ghc-9.2.

See #18620.

- - - - -
a8a2568b by Sylvain Henry at 2020-08-31T23:06:28-04:00
Bignum: add BigNat compat functions (#18613)

- - - - -
884245dd by Sylvain Henry at 2020-09-01T12:39:36-04:00
Fix FastString lexicographic ordering (fix #18562)

- - - - -
4b4fbc58 by Sylvain Henry at 2020-09-01T12:39:36-04:00
Remove "Ord FastString" instance

FastStrings can be compared in 2 ways: by Unique or lexically. We don't
want to bless one particular way with an "Ord" instance because it leads
to bugs (#18562) or to suboptimal code (e.g. using lexical comparison
while a Unique comparison would suffice).

UTF-8 encoding has the advantage that sorting strings by their encoded
bytes also sorts them by their Unicode code points, without having to
decode the actual code points. BUT GHC uses Modified UTF-8 which
diverges from UTF-8 by encoding \0 as 0xC080 instead of 0x00 (to avoid
null bytes in the middle of a String so that the string can still be
null-terminated). This patch adds a new `utf8CompareShortByteString`
function that performs sorting by bytes but that also takes Modified
UTF-8 into account. It is much more performant than decoding the strings
into [Char] to perform comparisons (which we did in the previous patch).

Bump haddock submodule

- - - - -
f1a71820 by GHC GitLab CI at 2020-09-03T18:26:59-04:00
configure: Avoid hard-coded ld path on Windows

The fix to #17962 ended up regressing on Windows as it failed to
replicate the logic responsible for overriding the toolchain paths on
Windows. This resulted in a hard-coded path to a directory that likely
doesn't exist on the user's system (#18550).

- - - - -
d56b9fc1 by Ben Gamari at 2020-09-03T18:26:59-04:00
WIP

- - - - -


30 changed files:

- .gitignore
- .gitlab-ci.yml
- .gitlab/ci.sh
- .gitlab/linters/check-cpp.py
- 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/Literals.hs
- compiler/GHC/Builtin/Types/Prim.hs
- compiler/GHC/Builtin/Uniques.hs
- compiler/GHC/Builtin/Uniques.hs-boot
- compiler/GHC/Builtin/Utils.hs
- compiler/GHC/Builtin/primops.txt.pp
- compiler/GHC/ByteCode/Asm.hs
- compiler/GHC/Cmm.hs
- compiler/GHC/Cmm/CLabel.hs
- compiler/GHC/Cmm/CallConv.hs
- compiler/GHC/Cmm/CommonBlockElim.hs
- compiler/GHC/Cmm/DebugBlock.hs
- compiler/GHC/Cmm/Expr.hs
- compiler/GHC/Cmm/Info/Build.hs
- compiler/GHC/Cmm/LayoutStack.hs
- compiler/GHC/Cmm/Liveness.hs
- compiler/GHC/Cmm/Opt.hs
- compiler/GHC/Cmm/Parser.y
- compiler/GHC/Cmm/Ppr/Decl.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/0d79c84ba8ce032336d8f01a69a68684e90fb451...d56b9fc1845a13d5eb3703f247d1f1fb043b0fe7

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/0d79c84ba8ce032336d8f01a69a68684e90fb451...d56b9fc1845a13d5eb3703f247d1f1fb043b0fe7
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/20200903/a50af887/attachment-0001.html>


More information about the ghc-commits mailing list