[Git][ghc/ghc][wip/bump-ci] 283 commits: TTG for IPBind had wrong extension name

Ben Gamari gitlab at gitlab.haskell.org
Tue Nov 10 16:24:07 UTC 2020



Ben Gamari pushed to branch wip/bump-ci at Glasgow Haskell Compiler / GHC


Commits:
0c701b69 by Alan Zimmerman at 2018-06-24T11:12:34-04:00
TTG for IPBind had wrong extension name

The standard[1] for extension naming is to use the XC prefix for the
internal extension points, rather than for a new constructor.

This is violated for IPBind, having

    data IPBind id
      = IPBind
            (XIPBind id)
            (Either (Located HsIPName) (IdP id))
            (LHsExpr id)
      | XCIPBind (XXIPBind id)

Swap the usage of XIPBind and XCIPBind

[1] https://ghc.haskell.org/trac/ghc/wiki/ImplementingTreesThatGrow#Namingconventions

Closes #15302

(cherry picked from commit 5f06cf6b6199c8f0e4921f4126f6eb15e2ff18ac)

- - - - -
abd66223 by Vladislav Zavialov at 2018-06-24T15:11:45-04:00
Do not imply NoStarIsType by TypeOperators/TypeInType

Implementation of the "Embrace TypeInType" proposal was done according
to the spec, which specified that TypeOperators must imply NoStarIsType.
This implication was meant to prevent breakage and to be removed in 2
releases.  However, compiling head.hackage has shown that this
implication only magnified the breakage, so there is no reason to have
it in the first place.

To remain in compliance with the three-release policy, we add a
workaround to define the (*) type operator even when -XStarIsType is on.

Test Plan: ./validate

Reviewers: bgamari, RyanGlScott, goldfire, phadej, hvr

Subscribers: rwbarton, thomie, carter

Differential Revision: https://phabricator.haskell.org/D4865

- - - - -
867e861b by Alan Zimmerman at 2018-06-25T18:08:56-04:00
Tweak API Annotations for ConDeclGADT

(cherry picked from commit 5db9f9129e7519db0c9841fbe7c14f350c23284c)

- - - - -
61adfbe6 by Simon Peyton Jones at 2018-06-27T17:07:55-04:00
Instances in no-evidence implications

Trac #15290 showed that it's possible that we might attempt to use a
quantified constraint to solve an equality in a situation where we
don't have anywhere to put the evidence bindings.  This made GHC crash.

This patch stops the crash, but still rejects the pogram.  See
Note [Instances in no-evidence implications] in TcInteract.

Finding this bug revealed another lurking bug:

* An infelicity in the treatment of superclasses -- we were expanding
  them locally at the leaves, rather than at their binding site; see
  (3a) in Note [The superclass story].

  As a consequence, TcRnTypes.superclassesMightHelp must look inside
  implications.

In more detail:

* Stop the crash, by making TcInteract.chooseInstance test for
  the no-evidence-bindings case.  In that case we simply don't
  use the instance.  This entailed a slight change to the type
  of chooseInstance.

* Make TcSMonad.getPendingScDicts (now renamed getPendingGivenScs)
  return only Givens from the /current level/; and make
  TcRnTypes.superClassesMightHelp look inside implications.

* Refactor the simpl_loop and superclass-expansion stuff in
  TcSimplify.  The logic is much easier to understand now, and
  has less duplication.

(cherry picked from commit 32eb41994f7448caf5fb6b06ed0678d79d029deb)

- - - - -
7e19610c by Simon Peyton Jones at 2018-06-27T17:07:55-04:00
Refactor the kind-checking of tyvar binders

The refactoring here is driven by the ghastly mess described in
comment:24 of Trac #1520.  The overall goal is to simplify the
kind-checking of typev-variable binders, and in particular to narrow
the use of the "in-scope tyvar binder" stuff,
which is needed only for associated types: see the new
Note [Kind-checking tyvar binders for associated types] in TcHsType.

Now

* The "in-scope tyvar binder" stuff is done only in
     - kcLHsQTyVars, which is used for the LHsQTyVars of a
       data/newtype, or type family declaration.

     - tcFamTyPats, which is used for associated family instances;
       it now calls tcImplicitQTKBndrs, which in turn usese
       newFlexiKindedQTyVar

* tcExpicitTKBndrs (which is used only for function signatures,
  data con signatures, pattern synonym signatures, and expression
  type signatures) now does not go via the "in-scope tyvar binder"
  stuff at all.

While I'm still not happy with all this code, the code is generally
simpler, and I think this is a useful step forward. It does cure
the problem too.

(It's hard to trigger the problem in vanilla Haskell code, because
the renamer would normally use different names for nested binders,
so I can't offer a test.)

(cherry picked from commit 9fc40c733ba8822a04bd92883801b214dee099ca)

- - - - -
145f7c66 by Simon Peyton Jones at 2018-06-27T17:07:56-04:00
Fix TcLevel manipulation in TcDerivInfer.simplifyDeriv

The level numbers we were getting simply didn't obey the
invariant (ImplicInv) in TcType
   Note [TcLevel and untouchable type variables]

That leads to chaos. Easy to fix.  I improved the documentation.

I also added an assertion in TcSimplify that checks that
level numbers go up by 1 as we dive inside implications, so
that we catch the problem at source rather than than through
its obscure consequences.

That in turn showed up that TcRules was also generating
constraints that didn't obey (ImplicInv), so I fixed that too.
I have no idea what consequences were lurking behing that
bug, but anyway now it's fixed.  Hooray.

(cherry picked from commit 261dd83cacec71edd551e9c581d05285c9ea3226)

- - - - -
4cfeca02 by Alan Zimmerman at 2018-06-27T17:07:56-04:00
API Annotations when parsing typapp

Make sure the original annotations are still accessible for a promoted
type.

Closes #15303

(cherry picked from commit e53c113dcfeca9ee957722ede3d8b6a2c4c751a1)

- - - - -
149d7912 by Simon Peyton Jones at 2018-06-27T17:07:56-04:00
Fix error recovery for pattern synonyms

As Trac #15289 showed, we were carrying on after a type error
in a pattern synonym, and then crashing.  This patch improves
error handling for pattern synonyms.

I also moved a bit of code from TcBinds into TcPatSyn, which
helpfully narrows the API.

(cherry picked from commit 2896082ec79f02b6388e038a8dae6cb22fe72dfc)

- - - - -
5059edb0 by Ben Gamari at 2018-07-10T20:21:43-04:00
Bump xhtml submodule to 3000.2.2.1

(cherry picked from commit 5a1290a8317056065f409ffd47fa6114172a1a15)

- - - - -
31f7d21b by Sylvain Henry at 2018-07-11T22:02:00-04:00
Fix for built-in Natural literals desugaring

The recent patch "Built-in Natural literals in Core"
(https://phabricator.haskell.org/rGHCfe770c211631e7b4c9b0b1e88ef9b6046c6
585ef) introduced a regression when desugaring large numbers.

This patch fixes it and adds a regression test.

Reviewers: hvr, bgamari

Reviewed By: bgamari

Subscribers: rwbarton, thomie, carter

GHC Trac Issues: #15301

Differential Revision: https://phabricator.haskell.org/D4885

(cherry picked from commit 987b5e7fbacd8afd2c8463c16eac28cd68f43155)

- - - - -
634c07dc by Richard Eisenberg at 2018-07-12T15:25:45-04:00
Expand and implement Note [The tcType invariant]

Read that note -- it's necessary to make sure that we can
always call typeKind without panicking. As discussed on #14873,
there were more checks and zonking to do, implemented here.
There are no known bugs fixed by this patch, but there are likely
unknown ones.

(cherry picked from commit cf67e59a90bcaba657a9f5db3d5defb6289c274f)

- - - - -
113bdb8b by Ryan Scott at 2018-07-12T15:28:30-04:00
Make ppr_tc_args aware of -fprint-explicit-kinds

Summary:
`ppr_tc_args` was printing invisible kind arguments even
when `-fprint-explicit-kinds` wasn't enabled. Easily fixed.

Test Plan: make test TEST=T15341

Reviewers: goldfire, bgamari, simonpj

Reviewed By: simonpj

Subscribers: simonpj, rwbarton, thomie, carter

GHC Trac Issues: #15341

Differential Revision: https://phabricator.haskell.org/D4932

(cherry picked from commit dbdcacfc55f28d8a85484cc1cf13dd78c45bf7ee)

- - - - -
f663e507 by Ryan Scott at 2018-07-12T17:06:02-04:00
Fix #15331 with careful blasts of parenthesizeHsType

Another `-ddump-splices` bug that can be solved with more
judicious use of parentheses.

Test Plan: make test TEST=T15331

Reviewers: goldfire, bgamari, alanz, tdammers

Reviewed By: tdammers

Subscribers: rwbarton, thomie, carter

GHC Trac Issues: #15331

Differential Revision: https://phabricator.haskell.org/D4920

(cherry picked from commit b6a3386186b77333b7a6cdc163499d7dae0dad1c)

- - - - -
a6a83d9a by Ryan Scott at 2018-07-12T17:06:11-04:00
Parenthesize rank-n contexts in Convert

Summary: A simple oversight.

Test Plan: make test TEST=T15324

Reviewers: goldfire, bgamari

Reviewed By: bgamari

Subscribers: rwbarton, thomie, carter

GHC Trac Issues: #15324

Differential Revision: https://phabricator.haskell.org/D4910

(cherry picked from commit 57733978482dc1e566a7d4cd90d4cbbd1315e3b2)

- - - - -
423a8eff by Matthew Pickering at 2018-07-12T17:06:11-04:00
Export findImportUsage and ImportDeclUsage

Reviewers: bgamari, alpmestan

Reviewed By: alpmestan

Subscribers: alpmestan, rwbarton, thomie, carter

GHC Trac Issues: #15335

Differential Revision: https://phabricator.haskell.org/D4927

(cherry picked from commit 2b1adaa7817c453df868d928312a9a99a0481eb1)

- - - - -
a39b58d5 by Alan Zimmerman at 2018-07-12T17:06:11-04:00
Fix mkGadtDecl does not set con_forall correctly

A GADT declaration surrounded in parens does not det the con_forall
field correctly.

e.g.

data MaybeDefault v where
    TestParens  :: (forall v . (Eq v) => MaybeDefault v)

Closes #15323

(cherry picked from commit 6e4e6d1c674a9d0257ca5c6caa26da18edf8ad8c)

- - - - -
22c951e6 by Matthías Páll Gissurarson at 2018-07-12T17:06:11-04:00
Fix errors caused by invalid candidates leaking from hole fits

This is a one line fix (and a note) that fixes four tickets, #15007,
 #15321 and #15202, #15314

The issue was that errors caused by illegal candidates (according to GHC
stage or being internal names) were leaking to the user, causing
bewildering error messages. If a candidate causes the type checker to
error, it is not a valid hole fit, and should be discarded.

As mentioned in #15321, this can cause a pattern of omissions, which
might be hard to discover. A better approach would be to gather the
error messages, and ask users to report them as GHC bugs. This will be
implemented in a subsequent change.

Reviewers: bgamari, simonpj

Reviewed By: simonpj

Subscribers: simonpj, rwbarton, thomie, carter

GHC Trac Issues: #15007, #15321, #15202, #15314

Differential Revision: https://phabricator.haskell.org/D4909

(cherry picked from commit 39de4e3d33dd9879398062620ad00b1e3b8481ce)

- - - - -
1fca115b by Ömer Sinan Ağacan at 2018-07-12T17:06:11-04:00
Add regression test for #15321

(cherry picked from commit e835fdb18cca66820728afce9c924a1c71f17fee)

- - - - -
eb680f2c by Ryan Scott at 2018-07-12T17:06:12-04:00
Fix newtype instance GADTs

Summary: This was taken from Richard's branch, which in turn was
submitted to Phab by Matthew, which in turn was commandeered by Ryan.

This fixes an issue with newtype instances in which too many
coercions were being applied in the worker. This fixes the issue by
removing the data family instance axiom from the worker and moving
to the wrapper. Moreover, we now require all newtype instances
to have wrappers, for symmetry with data instances.

Reviewers: goldfire, bgamari, simonpj, mpickering

Reviewed By: mpickering

Subscribers: simonpj, rwbarton, thomie, carter

GHC Trac Issues: #15318

Differential Revision: https://phabricator.haskell.org/D4902

(cherry picked from commit 927518668111584a06f12bd9eb1b0910a38acf4f)

- - - - -
b52cfe41 by Matthew Pickering at 2018-07-12T17:06:12-04:00
Run the renamed source plugin after each HsGroup

This allows modification of each `HsGroup` after it has been renamed.

The old behaviour of keeping the renamed source until later can be
recovered if desired by using the `keepRenamedSource` plugin but it
shouldn't really be necessary as it can be inspected in the `TcGblEnv`.

Reviewers: nboldi, bgamari, alpmestan

Reviewed By: nboldi, alpmestan

Subscribers: alpmestan, rwbarton, thomie, carter

GHC Trac Issues: #15315

Differential Revision: https://phabricator.haskell.org/D4947

(cherry picked from commit 1a79270c72cfcd98d683cfe7b2c777d8dd353b78)

- - - - -
42396113 by Simon Peyton Jones at 2018-07-12T17:06:12-04:00
Add commnent about binder order

...provoked by Trac #15308

(cherry picked from commit 3d002087dce9c61932dd17047902baa83581f4df)

- - - - -
9bcbb222 by Ryan Scott at 2018-07-12T17:06:12-04:00
Fix #15308 by suppressing invisble args more rigorously

Summary:
There was a buglet in `stripInvisArgs` (which is part of the
pretty-printing pipeline for types) in which only invisble arguments
which came before any visible arguments would be suppressed, but any
invisble arguments that came //after// visible ones would still be
printed, even if `-fprint-explicit-kinds`  wasn't enabled.
The fix is simple: make `stripInvisArgs` recursively process the
remaining types even after a visible argument is encountered.

Test Plan: make test TEST=T15308

Reviewers: goldfire, bgamari

Reviewed By: bgamari

Subscribers: simonpj, rwbarton, thomie, carter

GHC Trac Issues: #15308

Differential Revision: https://phabricator.haskell.org/D4891

(cherry picked from commit 93b7ac8d73885369f61f6eb6147352d45de4e957)

- - - - -
92925b3d by Ryan Scott at 2018-07-12T17:06:12-04:00
Fix #15307 by making nlHsFunTy parenthesize more

Summary:
`nlHsFunTy` wasn't parenthesizing its arguments at all,
which led to `-ddump-deriv` producing incorrectly parenthesized
types (since it uses `nlHsFunTy` to construct those types), as
demonstrated in #15307. Fix this by changing `nlHsFunTy` to add
parentheses à la `ppr_ty`: always parenthesizing the argument type
with function precedence, and recursively processing the result type,
adding parentheses for each function type it encounters.

Test Plan: make test TEST=T14578

Reviewers: bgamari

Reviewed By: bgamari

Subscribers: rwbarton, thomie, carter

GHC Trac Issues: #15307

Differential Revision: https://phabricator.haskell.org/D4890

(cherry picked from commit 59a15a56e180b59656e45df04f7df61de8298881)

- - - - -
cfc4afad by Simon Peyton Jones at 2018-07-12T17:06:12-04:00
Add nakedSubstTy and use it in TcHsType.tcInferApps

This was a tricky one.

During type checking we maintain TcType:
   Note [The well-kinded type invariant]
That is, types are well-kinded /without/ zonking.

But in tcInferApps we were destroying that invariant by calling
substTy, which in turn uses smart constructors, which eliminate
apparently-redundant Refl casts.

This is horribly hard to debug beause they really are Refls and
so it "ought" to be OK to discard them. But it isn't, as the
above Note describes in some detail.

Maybe we should review the invariant?  But for now I just followed
it, tricky thought it is.

This popped up because (for some reason) when I fixed Trac #15343,
that exposed this bug by making test polykinds/T14174a fail (in
Trac #14174 which indeed has the same origin).

So this patch fixes a long standing and very subtle bug.

One interesting point: I defined nakedSubstTy in a few lines by
using the generic mapType stuff.  I note that the "normal"
TyCoRep.substTy does /not/ use mapType.  But perhaps it should:
substTy has lots of $! strict applications in it, and they could
all be eliminated just by useing the StrictIdentity monad.  And
that'd make it much easier to experiment with switching between
strict and lazy versions.

(cherry picked from commit 5067b205a8abb5a9f98335d3a929f647c88c0aa2)

- - - - -
d0dfc5cc by Richard Eisenberg at 2018-07-12T17:06:12-04:00
Kind-check CUSK associated types separately

Previously, we kind-checked associated types while while still
figuring out the kind of a CUSK class. This caused trouble, as
documented in Note [Don't process associated types in kcLHsQTyVars]
in TcTyClsDecls. This commit moves this process after the initial
kind of the class is determined.

Fixes #15142.

Test case: indexed-types/should_compile/T15142.hs

(cherry picked from commit 030211d21207dabb7a4bf21cc9af6fa5eb066db1)

- - - - -
23b4d83f by Ömer Sinan Ağacan at 2018-07-12T17:06:12-04:00
Fix nptr field alignment in RtClosureInspect

`extractSubTerms` (which is extracting pointer and non-pointer fields of a
closure) was computing the alignment incorrectly when aligning a 64-bit value
(e.g. a Double) on i386 by aligning it to 64-bits instead of to word size
(32-bits). This is documented in `mkVirtHeapOffsetsWithPadding`:

> Align the start offset (eg, 2-byte value should be 2-byte aligned).
> But not more than to a word.

Fixes #15061

Test Plan:
Validated on both 32-bit and 64-bit. 32-bit fails with various unrelated stat
failures, but no actual test failures.

Reviewers: hvr, bgamari

Reviewed By: bgamari

Subscribers: simonpj, rwbarton, thomie, carter

GHC Trac Issues: #15061

Differential Revision: https://phabricator.haskell.org/D4906

(cherry picked from commit 15bb4e0b6c08b1f8f5511f04af14242f13833ed1)

- - - - -
c0323d97 by Ryan Scott at 2018-07-12T17:22:26-04:00
Instantiate GND bindings with an explicit type signature

Summary:
Before, we were using visible type application to apply
impredicative types to `coerce` in
`GeneralizedNewtypeDeriving`-generated bindings. This approach breaks
down when combined with `QuantifiedConstraints` in certain ways,
which #14883 and #15290 provide examples of. See
Note [GND and QuantifiedConstraints] for all the gory details.

To avoid this issue, we instead use an explicit type signature to
instantiate each GND binding, and use that to bind any type variables
that might be bound by a class method's type signature. This reduces
the need to impredicative type applications, and more importantly,
makes the programs from #14883 and #15290 work again.

Test Plan: make test TEST="T15290b T15290c T15290d T14883"

Reviewers: simonpj, bgamari

Reviewed By: simonpj

Subscribers: rwbarton, thomie, carter

GHC Trac Issues: #14883, #15290

Differential Revision: https://phabricator.haskell.org/D4895

(cherry picked from commit 132273f34e394bf7e900d0c15e01e91edd711890)

- - - - -
e5b1ec95 by Simon Marlow at 2018-07-14T11:58:19-04:00
submodule update

(cherry picked from commit e40eb738bb15795a22b2765e12c3add20efa91a5)

- - - - -
148310fd by Ben Gamari at 2018-07-14T11:58:19-04:00
Bump haskeline submodule to 0.7.4.3

(cherry picked from commit cbd4b33317b6cd3751878bbe7a0cc7601bd169e7)

- - - - -
736f4bce by Ben Gamari at 2018-07-14T11:58:19-04:00
Bump mtl submodule to v2.2.2

(cherry picked from commit c67cf9e9e66f629440c80ae3bf1616e2aac7002b)

- - - - -
ca59fa76 by Ben Gamari at 2018-07-14T11:58:19-04:00
Bump directory submodule to v1.3.3.0

(cherry picked from commit b794c7ed7d515a98b350417143fb46dd5e6d39df)

- - - - -
3f965941 by Ben Gamari at 2018-07-14T11:58:19-04:00
Bump unix submodule

(cherry picked from commit c3328ff354db2be5994807fed6b5b132489a9e3e)

- - - - -
391ee977 by Ben Gamari at 2018-07-14T11:58:19-04:00
Remove random submodule

I believe this was originally introduced to help test DPH, which is now
gone.

(cherry picked from commit 0905fec089b3270f540c7ee33959cbf8ecfcb4d7)

- - - - -
5b10d537 by Simon Peyton Jones at 2018-07-14T14:22:20-04:00
Fix decompsePiCos and visible type application

Trac #15343 was caused by two things

First, in TcHsType.tcHsTypeApp, which deals with the type argment
in visible type application, we were failing to call
solveLocalEqualities. But the type argument is like a user type
signature so it's at least inconsitent not to do so.

I thought that would nail it.  But it didn't. It turned out that we
were ended up calling decomposePiCos on a type looking like this
    (f |> co) Int

where co :: (forall a. ty) ~ (t1 -> t2)

Now, 'co' is insoluble, and we'll report that later.  But meanwhile
we don't want to crash in decomposePiCos.

My fix involves keeping track of the type on both sides of the
coercion, and ensuring that the outer shape matches before
decomposing.  I wish there was a simpler way to do this. But
I think this one is at least robust.

I suppose it is possible that the decomposePiCos fix would
have cured the original report, but I'm leaving the one-line
tcHsTypeApp fix in too because it just seems more consistent.

(cherry picked from commit aedbf7f1c402ecbcb5ff192d5fb4dd6dd4771bf8)

- - - - -
1cdc3ecc by Simon Marlow at 2018-07-14T14:22:20-04:00
Fix deadlock between STM and throwTo

There was a lock-order reversal between lockTSO() and the TVar lock,
see #15136 for the details.

It turns out we can fix this pretty easily by just deleting all the
locking code(!).  The principle for unblocking a `BlockedOnSTM` thread
then becomes the same as for other kinds of blocking: if the TSO
belongs to this capability then we do it directly, otherwise we send a
message to the capability that owns the TSO. That is, a thread blocked
on STM is owned by its capability, as it should be.

The possible downside of this is that we might send multiple messages
to wake up a thread when the thread is on another capability. This is
safe, it's just not very efficient.  I'll try to do some experiments
to see if this is a problem.

Test Plan: Test case from #15136 doesn't deadlock any more.

Reviewers: bgamari, osa1, erikd

Reviewed By: osa1

Subscribers: rwbarton, thomie, carter

GHC Trac Issues: #15136

Differential Revision: https://phabricator.haskell.org/D4956

(cherry picked from commit 7fc418df856d9b58034eeec48915646e67a7a562)

- - - - -
30a4bcc3 by Ömer Sinan Ağacan at 2018-07-14T14:22:20-04:00
Fix processHeapClosureForDead CONSTR_NOCAF case

CONSTR_NOCAF was introduced with 55d535da10d as a replacement for
CONSTR_STATIC and CONSTR_NOCAF_STATIC, however, as explained in Note
[static constructors], we copy CONSTR_NOCAFs (which can also be seen in
evacuate) during GC, and they can become dead, like other CONSTR_X_Ys.
processHeapClosureForDead is updated to reflect this.

Test Plan: Validates on x86_64. Existing failures on i386.

Reviewers: simonmar, bgamari, erikd

Reviewed By: simonmar, bgamari

Subscribers: rwbarton, thomie, carter

GHC Trac Issues: #7836, #15063, #15087, #15165

Differential Revision: https://phabricator.haskell.org/D4928

(cherry picked from commit 2625f1310edeff62eb3876cc6efbe105a80fe4ad)

- - - - -
c15ba1fb by Simon Marlow at 2018-07-16T18:26:56-04:00
Optimise wakeups for STM

Avoids repeated wakeup messages being sent when a TVar is written to
multiple times. See comments for details.

Test Plan:
* Test from #15136 (will be added to stm shortly)
* existing stm tests

Reviewers: bgamari, osa1, erikd

Reviewed By: bgamari

Subscribers: rwbarton, thomie, carter

GHC Trac Issues: #15136

Differential Revision: https://phabricator.haskell.org/D4961

(cherry picked from commit 502640c90c3d0fbb6c46257be14fdc7e3c694c6c)

- - - - -
655c6175 by Antti Siponen at 2018-07-16T18:36:15-04:00
#15387 Fix setting testsuite verbose to zero

(cherry picked from commit 0d6ef6d71e5077eb217456fdd8a515a8cab724ad)

- - - - -
c6774421 by Ben Gamari at 2018-07-16T19:32:23-04:00
Revert "Do not imply NoStarIsType by TypeOperators/TypeInType"

This reverts commit abd6622324733c67b05e0cbd0c8c3d12c6332f61.

- - - - -
bb5aa616 by Vladislav Zavialov at 2018-07-16T19:32:35-04:00
Do not imply NoStarIsType by TypeOperators/TypeInType

Implementation of the "Embrace TypeInType" proposal was done according
to the spec, which specified that TypeOperators must imply NoStarIsType.
This implication was meant to prevent breakage and to be removed in 2
releases.  However, compiling head.hackage has shown that this
implication only magnified the breakage, so there is no reason to have
it in the first place.

To remain in compliance with the three-release policy, we add a
workaround to define the (*) type operator even when -XStarIsType is on.

Test Plan: ./validate

Reviewers: bgamari, RyanGlScott, goldfire, phadej, hvr

Reviewed By: bgamari, RyanGlScott

Subscribers: harpocrates, rwbarton, thomie, carter

Differential Revision: https://phabricator.haskell.org/D4865

(cherry picked from commit 65c186f0fdde95fd7c63ab9bd9b33a0213dba7d1)

- - - - -
10fa8041 by Alan Zimmerman at 2018-07-30T17:46:45-04:00
TTG typo: XFieldOcc should be XCFieldOcc

In the following

  data FieldOcc pass = FieldOcc { extFieldOcc     :: XFieldOcc pass
                                , rdrNameFieldOcc :: Located RdrName
                                   -- ^ See Note [Located RdrNames] in HsExpr
                                }

    | XFieldOcc
        (XXFieldOcc pass)

we are using XFieldOcc for both the extFieldOcc type and the extra constructor.

The first one should be XCFieldOcc

Updates haddock submodule
closes #15386

(cherry picked from commit 926954196f9ffd7b89cba53061b39ef996e1650c)

- - - - -
f14c087a by Tamar Christina at 2018-07-30T17:46:45-04:00
split-obj: disable split-objects on Windows.

A change has caused GHC to generate excessive specializations.
This is making GHC generate 1800 splits for a simple GHC.Prim module,
which means 1800 fork/exec calls.

Due to this compilation times on Windows with split-objs on take over
24 hours to complete depending on your disk speed.  Also the end
compiler
compiling medium to large project is also much slower.

So I think we need to just disable split-objects. As there's nothing
that
can be done about this.

Test Plan: ./validate

Reviewers: bgamari

Subscribers: tdammers, rwbarton, thomie, erikd, carter

GHC Trac Issues: #15051

Differential Revision: https://phabricator.haskell.org/D4915

(cherry picked from commit 53649947223f197cf93e26393486f578d56c46c6)

- - - - -
dafffdc0 by Krzysztof Gogolewski at 2018-07-30T17:46:45-04:00
Add an expect_broken test for #14185

Test Plan: validate

Reviewers: goldfire, bgamari, alpmestan

Reviewed By: alpmestan

Subscribers: rwbarton, thomie, carter

GHC Trac Issues: #14185

Differential Revision: https://phabricator.haskell.org/D4981

(cherry picked from commit 3581212e3a5ba42114f47ed83a96322e0e8028ab)

- - - - -
72dc7989 by Ömer Sinan Ağacan at 2018-07-30T17:46:45-04:00
Run StgCse after unarise, fixes #15300

Given two unboxed sum terms:

    (# 1 | #) :: (# Int | Int# #)
    (# 1 | #) :: (# Int | Int  #)

These two terms are not equal as they unarise to different unboxed
tuples. However StgCse was thinking that these are equal, and replacing
one of these with a binder to the other.

To not deal with unboxed sums in StgCse we now do it after unarise. For
StgCse to maintain post-unarise invariants we factor-out case binder
in-scopeness check to `stgCaseBndrInScope` and use it in StgCse.

Also did some refactoring in SimplStg.

Another way to fix this would be adding a special case in StgCse to not
bring unboxed sum binders in scope:

    diff --git a/compiler/simplStg/StgCse.hs
b/compiler/simplStg/StgCse.hs
    index 6c740ca4cb..93a0f8f6ad 100644
    --- a/compiler/simplStg/StgCse.hs
    +++ b/compiler/simplStg/StgCse.hs
    @@ -332,7 +332,11 @@ stgCseExpr env (StgLetNoEscape binds body)
     stgCseAlt :: CseEnv -> OutId -> InStgAlt -> OutStgAlt
     stgCseAlt env case_bndr (DataAlt dataCon, args, rhs)
         = let (env1, args') = substBndrs env args
    -          env2 = addDataCon case_bndr dataCon (map StgVarArg
args') env1
    +          env2
    +            | isUnboxedSumCon dataCon
    +            = env1
    +            | otherwise
    +            = addDataCon case_bndr dataCon (map StgVarArg args')
env1
                 -- see note [Case 2: CSEing case binders]
               rhs' = stgCseExpr env2 rhs
           in (DataAlt dataCon, args', rhs')

I think this patch seems better in that it doesn't add a special case to
StgCse.

Test Plan:
Validate.

I tried to come up with a minimal example but failed. I thought a simple
program like

    data T = T (# Int | Int #) (# Int# | Int #)

    case T (# 1 | #) (# 1 | #) of ...

should be enough to trigger this bug, but for some reason StgCse
doesn't do
anything on this program.

Reviewers: simonpj, bgamari

Reviewed By: simonpj

Subscribers: rwbarton, thomie, carter

GHC Trac Issues: #15300

Differential Revision: https://phabricator.haskell.org/D4962

(cherry picked from commit 3c311e50e760c3ba00dc9692ad1536c79820598d)

- - - - -
50e4e48b by Mitsutoshi Aoe at 2018-07-30T17:46:45-04:00
rts: Flush eventlog in hs_init_ghc (fixes #15440)

Without this change RTS typically doesn't flush some important
events until the process terminates or it doesn't write them at
all in case it terminates abnormally.

Here is a list of such events:

* EVENT_WALL_CLOCK_TIME
* EVENT_OS_PROCESS_PID
* EVENT_OS_PROCESS_PPID
* EVENT_RTS_IDENTIFIER
* EVENT_PROGRAM_ARGS
* EVENT_PROGRAM_ENV

(cherry picked from commit 7a3e1b25ff9a570851a59c4cf3600daa49867b9b)

- - - - -
9a190caf by Ben Gamari at 2018-07-30T17:46:45-04:00
Bump terminfo submodule to 0.4.1.2

(cherry picked from commit b2852a440cac3310bbe443a9010949dbea94e7db)

- - - - -
3795b454 by Peter Trommler at 2018-07-30T17:46:45-04:00
Fix endian issues in ghc-heap

In test heap_all arity and n_args were swapped on big endian
systems.

Take care of endianness when reading parts of a machine word
from a `Word`.

This fixes one out of 36 failing tests reported in #15399.

Test Plan: validate

Reviewers: simonmar, bgamari, hvr, erikd

Reviewed By: simonmar

Subscribers: rwbarton, thomie, carter

GHC Trac Issues: #15399

Differential Revision: https://phabricator.haskell.org/D5001

(cherry picked from commit d7cb1bbc26719cf6082abe0d91d80be466e25bfc)

- - - - -
4c158eeb by Josh Price at 2018-07-30T17:46:46-04:00
Fix minor formatting issue in users_guide/bugs.rst

(cherry picked from commit fb11a104018dfb4065fd91c549fec6d46fa77945)

- - - - -
3ec1d931 by Ben Gamari at 2018-07-30T17:46:46-04:00
base: Make Foreign.Marshal.Alloc.allocBytes[Aligned] NOINLINE

As noted in #14346, touch# may be optimized away when the simplifier can see
that the continuation passed to allocaBytes will not return. Marking CPS-style
functions with NOINLINE ensures that the simplier can't draw any unsound
conclusions.

Ultimately the right solution here will be to do away with touch# and instead
introduce a scoped primitive as is suggested in #14375.

(cherry picked from commit 404bf05ed3193e918875cd2f6c95ae0da5989be2)

- - - - -
386aad8a by Ben Gamari at 2018-07-30T17:46:46-04:00
base: Fix documentation of System.Environment.Blank

- - - - -
26a7f850 by Ben Gamari at 2018-07-30T17:46:46-04:00
testsuite: Fix up testsuite

- - - - -
96609122 by Sylvain Henry at 2018-07-31T13:18:41-04:00
testsuite: Add test for #14346

(cherry picked from commit f8e5da92c0160a675e1666a5d6ed6a8ffcae193c)

- - - - -
a107cced by Simon Peyton Jones at 2018-07-31T14:18:32-04:00
Fix a nasty bug in piResultTys

I was failing to instantiate vigorously enough in Type.piResultTys
and in the very similar function ToIface.toIfaceAppArgsX

This caused Trac #15428.  The fix is easy.

See Note [Care with kind instantiation] in Type.hs

(cherry picked from commit e1b5a1174e42e390855b153015ce5227b3251d89)

- - - - -
b6a2c0d9 by Tamar Christina at 2018-07-31T14:18:37-04:00
stack: fix stack allocations on Windows

Summary:
On Windows one is not allowed to drop the stack by more than a page size.
The reason for this is that the OS only allocates enough stack till what
the TEB specifies. After that a guard page is placed and the rest of the
virtual address space is unmapped.

The intention is that doing stack allocations will cause you to hit the
guard which will then map the next page in and move the guard.  This is
done to prevent what in the Linux world is known as stack clash
vulnerabilities https://access.redhat.com/security/cve/cve-2017-1000364.

There are modules in GHC for which the liveliness analysis thinks the
reserved 8KB of spill slots isn't enough.  One being DynFlags and the
other being Cabal.

Though I think the Cabal one is likely a bug:

```
  4d6544:       81 ec 00 46 00 00       sub    $0x4600,%esp
  4d654a:       8d 85 94 fe ff ff       lea    -0x16c(%ebp),%eax
  4d6550:       3b 83 1c 03 00 00       cmp    0x31c(%ebx),%eax
  4d6556:       0f 82 de 8d 02 00       jb     4ff33a <_cLpg_info+0x7a>
  4d655c:       c7 45 fc 14 3d 50 00    movl   $0x503d14,-0x4(%ebp)
  4d6563:       8b 75 0c                mov    0xc(%ebp),%esi
  4d6566:       83 c5 fc                add    $0xfffffffc,%ebp
  4d6569:       66 f7 c6 03 00          test   $0x3,%si
  4d656e:       0f 85 a6 d7 02 00       jne    503d1a <_cLpb_info+0x6>
  4d6574:       81 c4 00 46 00 00       add    $0x4600,%esp
```

It allocates nearly 18KB of spill slots for a simple 4 line function
and doesn't even use it.  Note that this doesn't happen on x64 or
when making a validate build.  Only when making a build without a
validate and build.mk.

This and the allocation in DynFlags means the stack allocation will jump
over the guard page into unmapped memory areas and GHC or an end program
segfaults.

The pagesize on x86 Windows is 4KB which means we hit it very easily for
these two modules, which explains the total DOA of GHC 32bit for the past
3 releases and the "random" segfaults on Windows.

```
0:000> bp 00503d29
0:000> gn
Breakpoint 0 hit
WARNING: Stack overflow detected. The unwound frames are extracted from outside
         normal stack bounds.
eax=03b6b9c9 ebx=00dc90f0 ecx=03cac48c edx=03cac43d esi=03b6b9c9 edi=03abef40
eip=00503d29 esp=013e96fc ebp=03cf8f70 iopl=0         nv up ei pl nz na po nc
cs=0023  ss=002b  ds=002b  es=002b  fs=0053  gs=002b             efl=00000202
setup+0x103d29:
00503d29 89442440        mov     dword ptr [esp+40h],eax ss:002b:013e973c=????????
WARNING: Stack overflow detected. The unwound frames are extracted from outside
         normal stack bounds.
WARNING: Stack overflow detected. The unwound frames are extracted from outside
         normal stack bounds.
0:000> !teb
TEB at 00384000
    ExceptionList:        013effcc
    StackBase:            013f0000
    StackLimit:           013eb000
```

This doesn't fix the liveliness analysis but does fix the allocations, by
emitting a function call to `__chkstk_ms` when doing allocations of larger
than a page, this will make sure the stack is probed every page so the kernel
maps in the next page.

`__chkstk_ms` is provided by `libGCC`, which is under the
`GNU runtime exclusion license`, so it's safe to link against it, even for
proprietary code. (Technically we already do since we link compiled C code in.)

For allocations smaller than a page we drop the stack and probe the new address.
This avoids the function call and still makes sure we hit the guard if needed.

PS: In case anyone is Wondering why we didn't notice this before, it's because we
only test x86_64 and on Windows 10.  On x86_64 the page size is 8KB and also the
kernel is a bit more lenient on Windows 10 in that it seems to catch the segfault
and resize the stack if it was unmapped:

```
0:000> t
eax=03b6b9c9 ebx=00dc90f0 ecx=03cac48c edx=03cac43d esi=03b6b9c9 edi=03abef40
eip=00503d2d esp=013e96fc ebp=03cf8f70 iopl=0         nv up ei pl nz na po nc
cs=0023  ss=002b  ds=002b  es=002b  fs=0053  gs=002b             efl=00000202
setup+0x103d2d:
00503d2d 8b461b          mov     eax,dword ptr [esi+1Bh] ds:002b:03b6b9e4=03cac431
0:000> !teb
TEB at 00384000
    ExceptionList:        013effcc
    StackBase:            013f0000
    StackLimit:           013e9000
```

Likely Windows 10 has a guard page larger than previous versions.

This fixes the stack allocations, and as soon as I get the time I will look at
the liveliness analysis. I find it highly unlikely that simple Cabal function
requires ~2200 spill slots.

Test Plan: ./validate

Reviewers: simonmar, bgamari

Reviewed By: bgamari

Subscribers: AndreasK, rwbarton, thomie, carter

GHC Trac Issues: #15154

Differential Revision: https://phabricator.haskell.org/D4917

(cherry picked from commit d0bbe1bf351c8b85c310afb0dd1fb1f12f9474bf)

- - - - -
9a4ac756 by Krzysztof Gogolewski at 2018-07-31T14:18:37-04:00
Fix a major copy'n'paste error in LLVM CodeGen

Summary:
In D4592, `AddWordC` is lowered as an unsigned subtraction instead
of an unsigned addition when compiling with LLVM.

This patch rectifies that.

Reviewers: angerman, bgamari, monoidal

Reviewed By: angerman, bgamari, monoidal

Subscribers: osa1, rwbarton, thomie, carter

Differential Revision: https://phabricator.haskell.org/D4969

(cherry picked from commit f629442be93f4608e6bb53bfe2264a406230c546)

- - - - -
39ab54c9 by David Feuer at 2018-07-31T15:53:19-04:00
Harden fixST

Trac #15349 reveals that lazy blackholing can cause trouble for
`fixST` much like it can for `fixIO`. Make `fixST` work just
like `fixIO`.

Reviewers: simonmar, hvr, bgamari

Reviewed By: simonmar

Subscribers: rwbarton, thomie, carter

GHC Trac Issues: #15349

Differential Revision: https://phabricator.haskell.org/D4948

(cherry picked from commit 5a49651f3161473b383ec497af38e9daa022b9ac)

- - - - -
4c044ed1 by Krzysztof Gogolewski at 2018-07-31T15:53:19-04:00
Fix pretty-printing of data declarations in splices

Test Plan: validate

Reviewers: RyanGlScott, bgamari

Reviewed By: RyanGlScott

Subscribers: rwbarton, thomie, carter

GHC Trac Issues: #15365

Differential Revision: https://phabricator.haskell.org/D4998

(cherry picked from commit 3aa09cc5af9cacba91915c095f9652ee5ed31ec7)

- - - - -
04805078 by Krzysztof Gogolewski at 2018-07-31T15:53:19-04:00
Fix Ar crashing on odd-sized object files (Trac #15396)

Summary: All the work was done by Moritz Angermann.

Test Plan: validate

Reviewers: angerman, RyanGlScott, bgamari

Reviewed By: angerman

Subscribers: rwbarton, thomie, carter

GHC Trac Issues: #15396

Differential Revision: https://phabricator.haskell.org/D5013

(cherry picked from commit 754c3a55a603b155fa5d9a282de73d41a4694ffc)

- - - - -
8bed1400 by Ryan Scott at 2018-07-31T15:53:19-04:00
Suppress -Winaccessible-code in derived code

Summary:
It's rather unfortunate that derived code can produce inaccessible
code warnings (as demonstrated in #8128, #8740, and #15398), since
the programmer has no control over the generated code. This patch
aims to suppress `-Winaccessible-code` in all derived code. It
accomplishes this by doing the following:

* Generalize the `ic_env :: TcLclEnv` field of `Implication` to
  be of type `Env TcGblEnc TcLclEnv` instead. This way, it also
  captures `DynFlags`, which record the flag state at the time
  the `Implication` was created.
* When typechecking derived code, turn off `-Winaccessible-code`.
  This way, any insoluble given `Implication`s that are created when
  typechecking this derived code will remember that
  `-Winaccessible-code` was disabled.
* During error reporting, consult the `DynFlags` of an
  `Implication` before making the decision to report an inaccessible
  code warning.

Test Plan: make test TEST="T8128 T8740 T15398"

Reviewers: simonpj, bgamari

Reviewed By: simonpj

Subscribers: monoidal, rwbarton, thomie, carter

GHC Trac Issues: #8128, #8740, #15398

Differential Revision: https://phabricator.haskell.org/D4993

(cherry picked from commit 44a7b9baa45c4ab939c7d996519b5e3de3e13c5a)

- - - - -
d170083b by Simon Marlow at 2018-07-31T15:53:19-04:00
Fix the GHCi debugger with ApplicativeDo

Summary:
`collectLStmtsBinders` was returning nothing for `ApplicativeStmts`, which
caused the debugger to not track free variables in many cases when using
`ApplicativeDo`.

Test Plan:
* new test case
* validate

Reviewers: bgamari, erikd

Reviewed By: bgamari

Subscribers: rwbarton, thomie, carter

GHC Trac Issues: #15422

Differential Revision: https://phabricator.haskell.org/D4991

(cherry picked from commit 4ea9311cc5c3b99ea6915bee23f0a6776731f20e)

- - - - -
ff839f20 by Ryan Scott at 2018-07-31T15:53:19-04:00
Fix #15423 by using pprAStmtContext

Summary:
Previously, we were using `pprStmtContext` instead, which
led to error messages missing indefinite articles where they were
required.

Test Plan: make test TEST="T13242a T7786 Typeable1"

Reviewers: bgamari

Subscribers: rwbarton, thomie, carter

GHC Trac Issues: #15423

Differential Revision: https://phabricator.haskell.org/D4992

(cherry picked from commit 99f45e2a751dda4fdf00256d397a2932d430f3a7)

- - - - -
09abd1c4 by Simon Peyton Jones at 2018-07-31T15:53:19-04:00
Stop marking soluble ~R# constraints as insoluble

We had a constraint (a b ~R# Int), and were marking it as 'insoluble'.
That's bad; it isn't.  And it caused Trac #15431. Soultion is simple.

I did a tiny refactor on can_eq_app, so that it is used only for
nominal equalities.

(cherry picked from commit f0d27f515ffbc476144d1d1dd1a71bf9fa93c94b)

- - - - -
851f3341 by Simon Peyton Jones at 2018-07-31T15:53:19-04:00
Fix PrelRules.caseRules to account for out-of-range tags

As Trac #15436 points out, it is possible to get
   case dataToTag# (x :: T) of
      DEFAULT -> blah1
      -1#     -> blah2
      0       -> blah3

The (-1#) alterantive is unreachable, because dataToTag# returns
tags in the range [0..n-1] where n is the number of data constructors
in type T.

This actually made GHC crash; now we simply discard the unreachable
alterantive.  See Note [Unreachable caseRules alternatives]
in PrelRules

(cherry picked from commit 9897f6783a58265d5eaef5fb06f04320c7737e87)

- - - - -
2a162eba by Sylvain Henry at 2018-07-31T15:53:19-04:00
Fix Git commit ID detection in Git worktrees

Summary: When using a Git worktree, ".git" is a file, not a directory

Reviewers: bgamari, monoidal

Reviewed By: monoidal

Subscribers: rwbarton, thomie, erikd, carter

Differential Revision: https://phabricator.haskell.org/D5016

(cherry picked from commit 3539561b24b78aee2b37280ddf6bb64e2db3a67d)

- - - - -
06c29ddc by Ben Gamari at 2018-07-31T16:44:12-04:00
Fix some casts.

This fixes #15346, and is a team effort between Ryan Scott and
myself (mostly Ryan). We discovered two errors related to FC's
"push" rules, one in the TPush rule (as implemented in pushCoTyArg)
and one in KPush rule (it shows up in liftCoSubstVarBndr).

The solution: do what the paper says, instead of whatever random
thoughts popped into my head as I was actually implementing.

Note that this is a backport of the fix merged to master,
af624071fa063158d6e963e171280676f9c0a0b0.

Also fixes #15419, which is actually the same underlying problem.

Test case: dependent/should_compile/T{15346,15419}.

- - - - -
f579162a by Richard Eisenberg at 2018-07-31T16:46:44-04:00
testsuite: Add test for #15346

Test case: dependent/should_compile/T{15346,15419}.

- - - - -
79e13610 by Ben Gamari at 2018-07-31T20:22:49-04:00
Enable two-step allocator on FreeBSD

Simplify #ifdef nesting and use MAP_GUARD on FreeBSD and similar
systems. This allows the two-step allocator to be used on FreeBSD,
fixing #15348.

(cherry picked from commit 123aeb916cba93018039e583d42408dae80a6dc9)

- - - - -
eb2b71c5 by Ningning Xie at 2018-07-31T20:24:39-04:00
Fix #15453: bug in ForAllCo case in opt_trans_rule

Summary:
Given

```
co1 = \/ tv1 : eta1. r1
co2 = \/ tv2 : eta2. r2
```

We would like to optimize `co1; co2` so we push transitivity inside forall.
It should be

```
\/tv1 : (eta1;eta2).  (r1; r2[tv2 |-> tv1 |> eta1])
```

It is implemented in the ForAllCo case in opt_trans_rule in OptCoercion.
However current implementation is not right:

```
r2' = substCoWithUnchecked [tv2] [TyVarTy tv1] r2 -- ill-kinded!
```

This patch corrects it to be

```
r2' = substCoWithUnchecked [tv2] [mkCastTy (TyVarTy tv1) eta1] r2
```

Test Plan: validate

Reviewers: bgamari, goldfire, RyanGlScott

Reviewed By: RyanGlScott

Subscribers: rwbarton, thomie, carter

GHC Trac Issues: #15453

Differential Revision: https://phabricator.haskell.org/D5018

(cherry picked from commit 11de4380c2f16f374c6e8fbacf8dce00376e7efb)

- - - - -
c9be8596 by Moritz Angermann at 2018-08-01T19:40:45-04:00
linker: Nub rpaths

When compiling and linking files in `ghci`, we keep adding rpath
arguments to the linker command invoation.  If those are identical we
should `nub` them out.  Otherwise we not only risk overflowing the
argument limit, but also embed huge amounts of identical rpath values
into the dynamic library, eventually leading to the overflow of the load
command size limit, due to the number of rpath entries alone.

A further improvement could be to pass `-Xlinker -dead_strip_dylibs`;
that however might be stipping too aggressively, and potentially lead to
missing symbols?

For the time being I suggest to only do the nubbing and if need be to
provide -Wl,-dead_strip_dylibs when invoking ghci.

Test Plan: ./validate

Reviewers: bgamari, hvr

Reviewed By: bgamari

Subscribers: rwbarton, thomie, carter

GHC Trac Issues: #15446

Differential Revision: https://phabricator.haskell.org/D5021

(cherry picked from commit b803c40608119469bdda330cb88860be2cbed25b)

- - - - -
a97ead78 by Vladislav Zavialov at 2018-08-01T19:40:45-04:00
Fix #15415 and simplify tcWildCardBinders

Test Plan: Validate

Reviewers: goldfire, simonpj, bgamari

Reviewed By: simonpj

Subscribers: RyanGlScott, rwbarton, thomie, carter

GHC Trac Issues: #15415

Differential Revision: https://phabricator.haskell.org/D5022

(cherry picked from commit 120cc9f85ee1120072eb44c5bf37ac3055883605)

- - - - -
ebd773a0 by Ryan Scott at 2018-08-01T19:41:21-04:00
Fix #15450 by refactoring checkEmptyCase'

`checkEmptyCase'` (the code path for coverage-checking
`EmptyCase` expressions) had a fair bit of code duplication from the
code path for coverage-checking non-`EmptyCase` expressions, and to
make things worse, it behaved subtly different in some respects (for
instance, emitting different warnings under unsatisfiable
constraints, as shown in #15450). This patch attempts to clean up
both this discrepancy and the code duplication by doing the
following:

* Factor out a `pmInitialTmTyCs` function, which returns the initial
  set of term and type constraints to use when beginning coverage
  checking. If either set of constraints is unsatisfiable, we use an
  empty set in its place so that we can continue to emit as many
  warnings as possible. (The code path for non-`EmptyCase`
  expressions was doing this already, but not the code path for
  `EmptyCase` expressions, which is the root cause of #15450.)

  Along the way, I added a `Note` to explain why we do this.
* Factor out a `pmIsSatisfiable` constraint which checks if a set of
  term and type constraints are satisfiable. This does not change any
  existing behavior; this is just for the sake of deduplicating code.

Test Plan: make test TEST=T15450

Reviewers: simonpj, bgamari

Subscribers: rwbarton, thomie, carter

GHC Trac Issues: #15450

Differential Revision: https://phabricator.haskell.org/D5017

(cherry picked from commit 7f3cb50dd311caefb536d582f1e3d1b33d6650f6)

- - - - -
ff086cc1 by Ben Gamari at 2018-08-01T20:35:19-04:00
Bump Cabal submodule to 2.4

- - - - -
59f38587 by Richard Eisenberg at 2018-08-01T20:54:11-04:00
Remove the type-checking knot.

Bug #15380 hangs because a knot-tied TyCon ended up in a kind.
Looking at the code in tcInferApps, I'm amazed this hasn't happened
before! I couldn't think of a good way to fix it (with dependent
types, we can't really keep types out of kinds, after all), so
I just went ahead and removed the knot.

This was remarkably easy to do. In tcTyVar, when we find a TcTyCon,
just use it. (Previously, we looked up the knot-tied TyCon and used
that.) Then, during the final zonk, replace TcTyCons with the real,
full-blooded TyCons in the global environment. It's all very easy.

The new bit is explained in the existing
Note [Type checking recursive type and class declarations]
in TcTyClsDecls.

Naturally, I removed various references to the knot and the
zonkTcTypeInKnot (and related) functions. Now, we can print types
during type checking with abandon!

NB: There is a teensy error message regression with this patch,
around the ordering of quantified type variables. This ordering
problem is fixed (I believe) with the patch for #14880. The ordering
affects only internal variables that cannot be instantiated with
any kind of visible type application.

There is also a teensy regression around the printing of types
in TH splices. I think this is really a TH bug and will file
separately.

Test case: dependent/should_fail/T15380

(cherry picked from commit f8618a9b15177ee8c84771b927cb3583c9cd8408)

- - - - -
42c51e2f by Simon Peyton Jones at 2018-08-01T20:54:51-04:00
Small refactor in desugar of pattern matching

In reviewing Phab:D4968 for Trac #15385 I saw a small
but simple refactor to avoid unnecessary work in the
desugarer.

This patch just arranges to call
   matchSinglePatVar v ...
rather than
   matchSinglePat (Var v) ...

The more specialised function already existed, as
   match_single_pat_var

I also added more comments about decideBangHood

(cherry picked from commit 45cfe6514afb47c26883687e25ff7eb1e40c5a52)

- - - - -
e649085b by Ryan Scott at 2018-08-01T20:55:32-04:00
Fix #15385 by using addDictsDs in matchGuards

When coverage checking pattern-matches, we rely on the call
sites in the desugarer to populate the local dictionaries and term
evidence in scope using `addDictsDs` and `addTmCsDs`. But it turns
out that only the call site for desugaring `case` expressions was
actually doing this properly. In another part of the desugarer,
`matchGuards` (which handles pattern guards), it did not update the
local dictionaries in scope at all, leading to #15385.

Fixing this is relatively straightforward: just augment the
`BindStmt` case of `matchGuards` to use `addDictsDs` and `addTmCsDs`.
Accomplishing this took a little bit of import/export tweaking:

* We now need to export `collectEvVarsPat` from `HsPat.hs`.
* To avoid an import cycle with `Check.hs`, I moved `isTrueLHsExpr`
  from `DsGRHSs.hs` to `DsUtils.hs`, which resides lower on the
  import chain.

Test Plan: make test TEST=T15385

Reviewers: simonpj, bgamari

Reviewed By: simonpj

Subscribers: rwbarton, thomie, carter

GHC Trac Issues: #15385

Differential Revision: https://phabricator.haskell.org/D4968

(cherry picked from commit 9d388eb83e797fd28e14868009c4786f3f1a8aa6)

- - - - -
6a7cb806 by Simon Peyton Jones at 2018-08-01T22:42:22-04:00
Treat isConstraintKind more consistently

It turned out that we were not being consistent
about our use of isConstraintKind.

It's delicate, because the typechecker treats Constraint and Type as
/distinct/, whereas they are the /same/ in the rest of the compiler
(Trac #11715).

And had it wrong, which led to Trac #15412.  This patch does the
following:

* Rename isConstraintKind      to tcIsConstraintKind
         returnsConstraintKind to tcReturnsConstraintKind
  to emphasise that they use the 'tcView' view of types.

* Move these functions, and some related ones (tcIsLiftedTypeKind),
  from Kind.hs, to group together in Type.hs, alongside isPredTy.

It feels very unsatisfactory that these 'tcX' functions live in Type,
but it happens because isPredTy is called later in the compiler
too.  But it's a consequence of the 'Constraint vs Type' dilemma.

(cherry picked from commit c5d31df70b16dc346b5860077c8bbe585ddb7a78)

- - - - -
e86db0d5 by Christiaan Baaij at 2018-08-01T22:42:22-04:00
Plugin dependency information is stored separately

We need to store the used plugins so that we recompile
a module when a plugin that it uses is recompiled.

However, storing the `ModuleName`s of the plugins used by a
module in the `dep_mods` field made the rest of GHC think
that they belong in the HPT, causing at least the issues
reported in #15234

We therefor store the `ModuleName`s of the plugins in a
new field, `dep_plgins`, which is only used the the
recompilation logic.

Reviewers: mpickering, bgamari

Reviewed By: mpickering, bgamari

Subscribers: alpmestan, rwbarton, thomie, carter

GHC Trac Issues: #15234

Differential Revision: https://phabricator.haskell.org/D4937

(cherry picked from commit 52065e95c6df89d0048c6e3f35d6cc26ce8246f9)

- - - - -
588364c3 by Matthías Páll Gissurarson at 2018-08-01T22:45:04-04:00
Clone relevant constraints to avoid side-effects on HoleDests. Fixes #15370.

Summary: When looking for valid hole fits, the constraints relevant
to the hole may sometimes contain a HoleDest. Previously,
these were not cloned, which could cause the filling of filled
coercion hole being, which would cause an assert to fail. This is now fixed.

Test Plan: Regression test included.

Reviewers: simonpj, bgamari, goldfire

Reviewed By: simonpj

Subscribers: rwbarton, thomie, carter

GHC Trac Issues: #15370

Differential Revision: https://phabricator.haskell.org/D5004

(cherry picked from commit 0dc86f6bc454253969dedc31bed477eded4cf82d)

- - - - -
48fe84e2 by Krzysztof Gogolewski at 2018-08-03T16:18:24-04:00
fixup! Disable T10962 on llvm for now

(cherry picked from commit a606750b36862367d038813f9fe7170f93c36222)

- - - - -
d53e51ff by Ben Gamari at 2018-08-06T18:23:35-04:00
Bump Cabal submodule

- - - - -
e384b96d by Ben Gamari at 2018-08-06T18:23:35-04:00
Bump binary submodule

(cherry picked from commit 3110428dd63a2014fe131cb2abff192570cc89e9)

- - - - -
751febe4 by Ben Gamari at 2018-08-06T18:23:35-04:00
Bump filepath submodule

(cherry picked from commit 9472db132d2e455c106778c7daa30af71fbf6fee)

- - - - -
26b6ffb3 by Herbert Valerio Riedel at 2018-08-06T18:23:35-04:00
Turn on MonadFail desugaring by default

This contains two commits:

----

Make GHC's code-base compatible w/ `MonadFail`

There were a couple of use-sites which implicitly used pattern-matches
in `do`-notation even though the underlying `Monad` didn't explicitly
support `fail`

This refactoring turns those use-sites into explicit case
discrimations and adds an `MonadFail` instance for `UniqSM`
(`UniqSM` was the worst offender so this has been postponed for a
follow-up refactoring)

---

Turn on MonadFail desugaring by default

This finally implements the phase scheduled for GHC 8.6 according to

https://prime.haskell.org/wiki/Libraries/Proposals/MonadFail#Transitiona
lstrategy

This also preserves some tests that assumed MonadFail desugaring to be
active; all ghc boot libs were already made compatible with this
`MonadFail` long ago, so no changes were needed there.

Test Plan: Locally performed ./validate --fast

Reviewers: bgamari, simonmar, jrtc27, RyanGlScott

Reviewed By: bgamari

Subscribers: bgamari, RyanGlScott, rwbarton, thomie, carter

Differential Revision: https://phabricator.haskell.org/D5028

- - - - -
f4e54330 by Matthías Páll Gissurarson at 2018-08-06T18:23:35-04:00
Fix the TcLevel not being set correctly when finding valid hole fits

Summary:
This fixes the problem revealed by a new assert as it relates to valid
hole fits. However, tests `T10384`, `T14040a` and `TcStaticPointersFail02`
still fail the assert, but they are unrelated to valid hole fits.

Reviewers: bgamari, simonpj

Reviewed By: simonpj

Subscribers: simonpj, rwbarton, thomie, carter

GHC Trac Issues: #15384

Differential Revision: https://phabricator.haskell.org/D4994

(cherry picked from commit b202e7a48401bd8e805a92dcfe5ea059cbd8e41c)

- - - - -
f6e889fd by vrom911 at 2018-08-06T18:23:35-04:00
Refactor printMinimalImports (#15439)

Summary:
Split into getMinimalImports and printMinimalImports.
Export both functions from RnNames module.

Reviewers: bgamari, mpickering

Reviewed By: mpickering

Subscribers: mpickering, rwbarton, carter

GHC Trac Issues: #15439

Differential Revision: https://phabricator.haskell.org/D5045

(cherry picked from commit 73683f143d352343b00b1ab4f3abeb38b81794be)

- - - - -
9f1b1abe by Ben Gamari at 2018-08-06T18:23:35-04:00
circleci: Don't build validate-x86_64-linux-debug unregisterised

Summary: This was a cut-and-paste error.

Reviewers: alpmestan

Reviewed By: alpmestan

Subscribers: alpmestan, rwbarton, thomie, carter

GHC Trac Issues: #15466

Differential Revision: https://phabricator.haskell.org/D5037

(cherry picked from commit f355b72113e646cb3785937f5506ee4c084c127f)

- - - - -
87a79e39 by Ben Gamari at 2018-08-06T18:32:44-04:00
rts: Ensure that the_gc_thread is aligned

Since we cast this to a gc_thread the compiler may assume that it's aligned.
Make sure that this is so. Fixes #15482.

(cherry picked from commit c6cc93bca69abc258513af8cf2370b14e70fd8fb)

- - - - -
b4302fd5 by Alexander Biehl at 2018-08-06T18:32:44-04:00
Add since annotation to GHC.ByteOrder

(cherry picked from commit 6fb2620dbc420c976dc9da90b0efc6eae533ebff)
(cherry picked from commit 8b357c6ad17bfe802c4a818b0cd7440bced024a3)

- - - - -
6369aab2 by Mathieu Boespflug at 2018-08-06T18:32:44-04:00
docs: Fix wrong module name in hsig example

In the module signatures section, two modules were defined, `Str` and
`A`, but `A` was importing `Text`, not `Str`.

(cherry picked from commit 26ab3635ca342c88310321d7f310f1c12c23ec4c)
(cherry picked from commit ce9b459de30e15f2d65518ca12974a692256d477)

- - - - -
eefac048 by Simon Jakobi at 2018-08-06T18:32:44-04:00
Unhide GHC.List for haddock

The unhidden module GHC.OldList recommends using GHC.List instead.
In consequence we should also have haddocks for GHC.List.

(cherry picked from commit e3df129c8bf4c35693d01ea66238882f3e3b6fe1)
(cherry picked from commit 672f177300b2df1b8a4cd49d560a6fd6da2415d2)

- - - - -
8edc4b4b by Maximilian Tagher at 2018-08-06T18:32:45-04:00
[docs] Add missed specialisations warnings to list of those not enabled by -Wall

Enabling `-Weverything` does enable those warnings.

(cherry picked from commit b062bd10a88ea407ae91610f822f0c352909bcce)
(cherry picked from commit 24b76d1bef7e61791907fbd063f85643eeb1211a)

- - - - -
2bbff4dc by Krzysztof Gogolewski at 2018-08-06T18:32:45-04:00
Testsuite driver: fix encoding issue when calling ghc-pkg

Summary:
In Python 3, subprocess.communicate() returns a pair of bytes, which
need to be decoded. In runtests.py, we were just calling str() instead,
which converts b'x' to "b'x'". As a result, the loop that was checking
pkginfo for lines starting with 'library-dirs' couldn't work.

Reviewers: bgamari, thomie, Phyx

Reviewed By: thomie

Subscribers: Phyx, rwbarton, carter

Differential Revision: https://phabricator.haskell.org/D5046

(cherry picked from commit 36a4c19494e2cb7e968f1d0e0c09926a660e1a56)

- - - - -
5140b23a by Ben Gamari at 2018-08-07T09:22:24-04:00
Bump hadrian submodule

- - - - -
d0923219 by Ben Gamari at 2018-08-07T13:26:09-04:00
Bump binary submodule to 0.8.6.0

This is actually a decrease in the version number since a bump to 0.10
wasn't actually necessary.

(cherry picked from commit 960a7d17a79417300ee81e884e867bf3de4e535b)

- - - - -
68268150 by Ben Gamari at 2018-08-07T20:10:01-04:00
Bump Cabal submodule

- - - - -
6328e89f by Ben Gamari at 2018-08-08T23:17:39-04:00
Allow arbitrary options to be passed to tar compression

(cherry picked from commit 4d6dfc35c06abb747de318ada2f27985c9369a6d)

- - - - -
d414a115 by Ben Gamari at 2018-08-08T23:17:39-04:00
circleci: Fix documentation building

(cherry picked from commit 9f937142f67ccf1c8bff9bb809539deca39a7a6f)

- - - - -
1741e858 by Ben Gamari at 2018-08-08T23:18:20-04:00
circleci: Reduce build verbosity

(cherry picked from commit 5be646f251b25c22ba24ad2a4eb5af66b3f95d74)

- - - - -
e734b8c5 by Ben Gamari at 2018-08-08T23:18:21-04:00
circleci: Reduce compression effort to 3

(cherry picked from commit 60e12f26a28ce4ed0ecb905baef207a0388947f1)

- - - - -
38932150 by Viktor Dukhovni at 2018-08-09T09:23:20-04:00
Add FreeBSD amd64 LLVM target

(cherry picked from commit 396aac4c65a47b6252e0a73d2a3066e924d53f11)

- - - - -
fd7cedc8 by Ben Gamari at 2018-08-09T12:31:59-04:00
Bump unix submodule

- - - - -
1a0a971b by Ben Gamari at 2018-08-09T12:31:59-04:00
testsuite: Bump for unix 2.7

- - - - -
da117270 by Ben Gamari at 2018-08-10T09:21:05-04:00
Revert "rts: Ensure that the_gc_thread is aligned"

This reverts commit 87a79e394013e5f722496900227b126015d0d780.

- - - - -
15b53479 by Ben Gamari at 2018-08-11T12:00:44-04:00
Bump parsec submodule

- - - - -
13105a1a by Christiaan Baaij at 2018-08-19T08:31:46-04:00
Filter plugin dylib locations

Summary:
Previously we just created a cartesian product of the library
paths of the plugin package and the libraries of the package.
Of course, some of these combinations result in a filepath of
a file doesn't exists, leading to #15475.

Instead of making `haskFile` return Nothing in case a file
doesn't exist (which would hide errors), we look at all the
possible dylib locations and ensure that at least one of those
locations is an existing file. If the list turns out to be
empty however, we panic.

Reviewers: mpickering, bgamari

Reviewed By: mpickering

Subscribers: monoidal, rwbarton, carter

GHC Trac Issues: #15475

Differential Revision: https://phabricator.haskell.org/D5048

(cherry picked from commit b324c5624432f2c3d5b0a689fdff75a1ccc563f5)

- - - - -
fb8b2cb1 by Ryan Scott at 2018-08-19T08:32:10-04:00
Fix #15527 by pretty-printing an RdrName prefixly

Summary:
When `(.) @Int` is used without enabling `TypeApplications`,
the resulting error message will pretty-print the (symbolic)
`RdrName` `(.)`. However, it does so without parenthesizing it, which
causes the pretty-printed expression to appear as `. at Int`. Yuck.

Since the expression in a type application will always be prefix,
we can fix this issue by using `pprPrefixOcc` instead of plain ol'
`ppr`.

Test Plan: make test TEST=T15527

Reviewers: bgamari, monoidal, simonpj

Reviewed By: monoidal, simonpj

Subscribers: rwbarton, carter

GHC Trac Issues: #15527

Differential Revision: https://phabricator.haskell.org/D5071

(cherry picked from commit 5238f204482ac7f05f4e2d2e92576288cc00d42d)

- - - - -
033d6ac7 by Zubin Duggal at 2018-08-19T08:32:19-04:00
Check if files are same in combineSrcSpans

Summary: If this is not checked, SrcSpans are sometimes mangled by CPP.

Test Plan: ./validate

Reviewers: bgamari, dfeuer

Reviewed By: bgamari

Subscribers: dfeuer, rwbarton, thomie, carter

GHC Trac Issues: #15279

Differential Revision: https://phabricator.haskell.org/D4866

(cherry picked from commit f7f9820e8f5601e9a072e504f3d772fd78df6700)

- - - - -
beca6421 by Ben Gamari at 2018-08-20T15:04:31-04:00
Bump stm submodule

- - - - -
2d308da2 by Ryan Scott at 2018-08-21T16:35:22-04:00
Be mindful of GADT tyvar order when desugaring record updates

After commit ef26182e2014b0a2a029ae466a4b121bf235e4e4,
the type variable binders in GADT constructor type signatures
are now quantified in toposorted order, instead of always having
all the universals before all the existentials. Unfortunately, that
commit forgot to update some code (which was assuming the latter
scenario) in `DsExpr` which desugars record updates. This wound
up being the cause of #15499.

This patch makes up for lost time by desugaring record updates in
a way such that the desugared expression applies type arguments to
the right-hand side constructor in the correct order—that is, the
order in which they were quantified by the user.

Test Plan: make test TEST=T15499

Reviewers: simonpj, bgamari

Reviewed By: simonpj

Subscribers: rwbarton, carter

GHC Trac Issues: #15499

Differential Revision: https://phabricator.haskell.org/D5060

(cherry picked from commit 63b6a1d44849c479d2a7cb59211f5c64d133bc62)

- - - - -
b81fc821 by Simon Peyton Jones at 2018-08-21T16:40:02-04:00
Set strictness correctly for JoinIds

We were failing to keep correct strictness info when eta-expanding
join points; Trac #15517.   The situation was something like

  \q v eta ->
     let j x = error "blah
         -- STR Lx   bottoming!
     in case y of
           A -> j x eta
           B -> blah
           C -> j x eta

So we spot j as a join point and eta-expand it.  But we must
also adjust the stricness info, else it vlaimes to bottom after
one arg is applied but now it has become two.

I fixed this in two places:

 - In CoreOpt.joinPointBinding_maybe, adjust strictness info

 - In SimplUtils.tryEtaExpandRhs, return consistent values
   for arity and bottom-ness

(cherry picked from commit ce6ce788251b6102f5c1b878ffec53ba7ad678b5)

- - - - -
c3e50b05 by Ben Gamari at 2018-08-21T19:03:43-04:00
rts: Align the_gc_thread to 64 bytes

In a previous attempt (c6cc93bca69abc258513af8cf2370b14e70fd8fb) I had
tried aligning to 8 bytes under the assumption that the problem was that
the_gc_thread, a StgWord8[], wasn't being aligned to 8-bytes as the
gc_thread struct would expect. However, we actually need even stronger
alignment due to the alignment attribute attached to gen_workspace,
which claims it should be aligned to a 64-byte boundary.

This fixes #15482.

Reviewers: erikd, simonmar

Reviewed By: simonmar

Subscribers: rwbarton, carter

GHC Trac Issues: #15482

Differential Revision: https://phabricator.haskell.org/D5052

(cherry picked from commit 68a1fc29b4bb3eae54e4d96c9aec20e700040f34)

- - - - -
767f5660 by Bodigrim at 2018-08-23T15:16:21-04:00
Fix gcdExtInteger (trac#15350)

(cherry picked from commit 7c207c86ab0de955ebec70eeeb366ba0d94acc4a)

- - - - -
c53a9f73 by DavidEichamnn at 2018-08-23T15:16:22-04:00
Correct limb length and assertion for gcdExtInteger

Reviewers: hvr, bgamari, monoidal

Reviewed By: monoidal

Subscribers: monoidal, rwbarton, thomie, carter

GHC Trac Issues: #15350

Differential Revision: https://phabricator.haskell.org/D5042

(cherry picked from commit c331592130ef592b92084e7417581a4039bfa7d2)

- - - - -
18cb44df by Alec Theriault at 2018-08-23T15:16:22-04:00
Explicitly tell 'getNameToInstances' mods to load

Calculating which modules to load based on the InteractiveContext means
maintaining a potentially very large GblRdrEnv.

In Haddock's case, it is much cheaper (from a memory perspective) to
just keep track of which modules interfaces we want loaded then hand
these off explicitly to 'getNameToInstancesIndex'.

Bumps haddock submodule.

Reviewers: alexbiehl, bgamari

Reviewed By: alexbiehl

Subscribers: rwbarton, thomie, carter

Differential Revision: https://phabricator.haskell.org/D5003

(cherry picked from commit c971e1193fa44bb507d1806d5bb61768670dc912)

- - - - -
7c819cbe by Ben Gamari at 2018-08-23T15:48:58-04:00
testsuite: Add (broken) test for #15473

(cherry picked from commit 5487f305d9dea298f0822082389d8a0225956c55)

- - - - -
d3ce8842 by Simon Peyton Jones at 2018-08-23T16:19:37-04:00
Turn infinite loop into a panic

In these two functions
  * TcIface.toIfaceAppTyArgsX
  * Type.piResultTys
we take a type application (f t1 .. tn) and try to find
its kind. It turned out that, if (f t1 .. tn) was ill-kinded
the function would go into an infinite loop.

That's not good: it caused the loop in Trac #15473.

This patch doesn't fix the bug in #15473, but it does turn the
loop into a decent panic, which is a step forward.

(cherry picked from commit db6f1d9cfc74690798645a7cc5b25040c36bb35d)

- - - - -
047c17a4 by Simon Peyton Jones at 2018-08-23T18:39:34-04:00
Fix a typo in TcValidity.checkFamInstRhs

In error message generation we were using the wrong
type constructor in inst_head.  Result: the type became
ill-kinded, and that sent the compiler into a loop.

A separate patch fixes the loop. This patch fixes the
actual bug -- Trac #15473.

I also improved the "occurs more often" error message
a bit.  But it's still pretty terrible:

    * Variable ‘a’ occurs more often
      in the type family application ‘Undefined’
      than in the instance head ‘LetInterleave xs t ts is y z’

It looks like nonsense, but all becomes clear if you use
-fprint-explicit-kinds.  Really we should fix this by spotting
when invisible arguments are involved and at least suggesting
-fprint-explicit-kinds.

(cherry picked from commit 8c7f90abcc1e8f9f29b751f23174e8db89ba6983)

- - - - -
02829747 by Simon Peyton Jones at 2018-08-23T18:39:34-04:00
Accommodate API change in transSuperClasses

In this patch

    commit 6eabb6ddb7c53784792ee26b1e0657bde7eee7fb
    Author: Simon Peyton Jones <simonpj at microsoft.com>
    Date:   Tue Dec 15 14:26:13 2015 +0000

    Allow recursive (undecidable) superclasses

I changed (transSuperClasses p) to return only the
superclasses of p, but not p itself. (Previously it always
returned p as well.)

The use of transSuperClasses in TcErrors.warnRedundantConstraints
really needs 'p' in the result -- but I faild to fix this
call site, and instead crippled the test for Trac #10100.

This patch sets things right

* Accomodates the API change
* Re-enables T10100
* And thereby fixes Trac #11474

(cherry picked from commit 4293a80a3ea835412737911bcb2a6703e9af378b)

- - - - -
c69c9d39 by Simon Jakobi at 2018-08-23T18:39:34-04:00
--show-iface: Qualify all non-local names

Summary:
In order to disambiguate names from different modules, qualify all names
that don't originate in the current module.

Also update docs for QueryQualifyName

Test Plan: validate

Reviewers: simonpj, bgamari

Reviewed By: simonpj

Subscribers: rwbarton, thomie, carter, tdammers

GHC Trac Issues: #15269

Differential Revision: https://phabricator.haskell.org/D4852

(cherry picked from commit d42eef344a71990d12f27e88cdf10ba0b2a2f34b)

- - - - -
89ad5fed by Ryan Scott at 2018-08-23T18:50:23-04:00
Suppress redundant givens during error reporting

Summary:
When GHC reports that it cannot solve a constraint in error
messages, it often reports what given constraints it has in scope.
Unfortunately, sometimes redundant constraints (like `* ~ *`,
from  #15361) can sneak in. The fix is simple: blast away these
redundant constraints using `mkMinimalBySCs`.

Test Plan: make test TEST=T15361

Reviewers: simonpj, bgamari

Subscribers: rwbarton, thomie, carter

GHC Trac Issues: #15361

Differential Revision: https://phabricator.haskell.org/D5002

(cherry picked from commit c552feea127d8ed8cbf4994a157c4bbe254b96c3)

- - - - -
e57a15d8 by Ryan Scott at 2018-08-23T18:50:28-04:00
Properly designate LambdaCase alts as CaseAlt in TH

Summary:
When `\case` expressions are parsed normally, their
alternatives are marked as `CaseAlt` (which means that they are
pretty-printed without a `\` character in front of them, unlike for
lambda expressions). However, `\case` expressions created by way of
Template Haskell (in `Convert`) inconsistently designated the case
alternatives as `LambdaExpr`, causing them to be pretty-printed
poorly (as shown in #15518). The fix is simple: use `CaseAlt`
consistently.

Test Plan: make test TEST=T15518

Reviewers: goldfire, bgamari

Subscribers: rwbarton, carter

GHC Trac Issues: #15518

Differential Revision: https://phabricator.haskell.org/D5069

(cherry picked from commit 32008a9d0e09f0cc8899aa871d9a6b63fcc28a1a)

- - - - -
768cc53d by David Feuer at 2018-08-23T18:50:28-04:00
Expose the StableName constructor

* Move the definition of `StableName` from `System.Mem.StableName`
  to a new `GHC.StableName` module.

* Expose the `StableName` data constructor from `GHC.StableName`.
  Once we have `UnliftedArray#`, this will enable `StableName`s to
  be stored in `UnliftedArray`s (from `primitive`) without unsafe
  coercions.

Reviewers: hvr, bgamari, andrewthad, osa1

Reviewed By: osa1

Subscribers: osa1, rwbarton, carter

GHC Trac Issues: #15535

Differential Revision: https://phabricator.haskell.org/D5078

(cherry picked from commit 9c4e6c6b1affd410604f8f76ecf56abfcc5cccb6)

- - - - -
e8f79c95 by Ben Gamari at 2018-09-07T07:18:19-04:00
Do a final pass over the changelogs

- - - - -
3b998a93 by Ben Gamari at 2018-09-07T08:11:48-04:00
Bump Cabal submodule to 2.4.0.0

- - - - -
d46dd452 by Ömer Sinan Ağacan at 2018-09-07T08:11:48-04:00
Fix a race between GC threads in concurrent scavenging

While debugging #15285 I realized that free block lists (free_list in
BlockAlloc.c) get corrupted when multiple scavenge threads allocate and
release blocks concurrently. Here's a picture of one such race:

    Thread 2 (Thread 32573.32601):
    #0  check_tail
        (bd=0x940d40 <stg_TSO_info>) at rts/sm/BlockAlloc.c:860
    #1  0x0000000000928ef7 in checkFreeListSanity
        () at rts/sm/BlockAlloc.c:896
    #2  0x0000000000928979 in freeGroup
        (p=0x7e998ce02880) at rts/sm/BlockAlloc.c:721
    #3  0x0000000000928a17 in freeChain
        (bd=0x7e998ce02880) at rts/sm/BlockAlloc.c:738
    #4  0x0000000000926911 in freeChain_sync
        (bd=0x7e998ce02880) at rts/sm/GCUtils.c:80
    #5  0x0000000000934720 in scavenge_capability_mut_lists
        (cap=0x1acae80) at rts/sm/Scav.c:1665
    #6  0x000000000092b411 in gcWorkerThread
        (cap=0x1acae80) at rts/sm/GC.c:1157
    #7  0x000000000090be9a in yieldCapability
        (pCap=0x7f9994e69e20, task=0x7e9984000b70, gcAllowed=true) at rts/Capability.c:861
    #8  0x0000000000906120 in scheduleYield
        (pcap=0x7f9994e69e50, task=0x7e9984000b70) at rts/Schedule.c:673
    #9  0x0000000000905500 in schedule
        (initialCapability=0x1acae80, task=0x7e9984000b70) at rts/Schedule.c:293
    #10 0x0000000000908d4f in scheduleWorker
        (cap=0x1acae80, task=0x7e9984000b70) at rts/Schedule.c:2554
    #11 0x000000000091a30a in workerStart
        (task=0x7e9984000b70) at rts/Task.c:444
    #12 0x00007f99937fa6db in start_thread
        (arg=0x7f9994e6a700) at pthread_create.c:463
    #13 0x000061654d59f88f in clone
        () at ../sysdeps/unix/sysv/linux/x86_64/clone.S:95

    Thread 1 (Thread 32573.32573):
    #0  checkFreeListSanity
        () at rts/sm/BlockAlloc.c:887
    #1  0x0000000000928979 in freeGroup
        (p=0x7e998d303540) at rts/sm/BlockAlloc.c:721
    #2  0x0000000000926f23 in todo_block_full
        (size=513, ws=0x1aa8ce0) at rts/sm/GCUtils.c:264
    #3  0x00000000009583b9 in alloc_for_copy
        (size=513, gen_no=0) at rts/sm/Evac.c:80
    #4  0x000000000095850d in copy_tag_nolock
        (p=0x7e998c675f28, info=0x421d98 <Main_Large_con_info>, src=0x7e998d075d80, size=513,
        gen_no=0, tag=1) at rts/sm/Evac.c:153
    #5  0x0000000000959177 in evacuate
        (p=0x7e998c675f28) at rts/sm/Evac.c:715
    #6  0x0000000000932388 in scavenge_small_bitmap
        (p=0x7e998c675f28, size=1, bitmap=0) at rts/sm/Scav.c:271
    #7  0x0000000000934aaf in scavenge_stack
        (p=0x7e998c675f28, stack_end=0x7e998c676000) at rts/sm/Scav.c:1908
    #8  0x0000000000934295 in scavenge_one
        (p=0x7e998c66e000) at rts/sm/Scav.c:1466
    #9  0x0000000000934662 in scavenge_mutable_list
        (bd=0x7e998d300440, gen=0x1b1d880) at rts/sm/Scav.c:1643
    #10 0x0000000000934700 in scavenge_capability_mut_lists
        (cap=0x1aaa340) at rts/sm/Scav.c:1664
    #11 0x00000000009299b6 in GarbageCollect
        (collect_gen=0, do_heap_census=false, gc_type=2, cap=0x1aaa340, idle_cap=0x1b38aa0)
        at rts/sm/GC.c:378
    #12 0x0000000000907a4a in scheduleDoGC
        (pcap=0x7ffdec5b5310, task=0x1b36650, force_major=false) at rts/Schedule.c:1798
    #13 0x0000000000905de7 in schedule
        (initialCapability=0x1aaa340, task=0x1b36650) at rts/Schedule.c:546
    #14 0x0000000000908bc4 in scheduleWaitThread
        (tso=0x7e998c0067c8, ret=0x0, pcap=0x7ffdec5b5430) at rts/Schedule.c:2537
    #15 0x000000000091b5a0 in rts_evalLazyIO
        (cap=0x7ffdec5b5430, p=0x9c11f0, ret=0x0) at rts/RtsAPI.c:530
    #16 0x000000000091ca56 in hs_main
        (argc=1, argv=0x7ffdec5b5628, main_closure=0x9c11f0, rts_config=...) at rts/RtsMain.c:72
    #17 0x0000000000421ea0 in main
        ()

In particular, dbl_link_onto() which is used to add a freed block to a
doubly-linked free list is not thread safe and corrupts the list when
called concurrently.

Note that thread 1 is to blame here as thread 2 is properly taking the
spinlock. With this patch we now take the spinlock when freeing a todo
block in GC, avoiding this race.

Test Plan:
- Tried slow validate locally: this patch does not introduce new failures.
- circleci: https://circleci.com/gh/ghc/ghc-diffs/283 The test got killed
  because it took 5 hours but T7919 (which was previously failing on circleci)
  passed.

Reviewers: simonmar, bgamari, erikd

Reviewed By: simonmar

Subscribers: rwbarton, carter

GHC Trac Issues: #15285

Differential Revision: https://phabricator.haskell.org/D5115

(cherry picked from commit c6fbac6a6a69a2f4be89701b2c386ae53214f9a3)

- - - - -
aeb24707 by Ömer Sinan Ağacan at 2018-09-07T08:11:48-04:00
Skip eventlog tests in GHCi way

Summary: (GHCi doesn't generate event logs)

Test Plan:
These tests were failing in GHCi way, they're now skipped in GHCi way as GHCi
doesn't generate eventlogs

Reviewers: bgamari, simonmar, maoe, alpmestan

Reviewed By: alpmestan

Subscribers: rwbarton, carter

GHC Trac Issues: #15587

Differential Revision: https://phabricator.haskell.org/D5119

(cherry picked from commit c0e5087d01e2912f00feede6c259a2ee87685c90)

- - - - -
21545666 by Krzysztof Gogolewski at 2018-09-07T08:11:48-04:00
Fix typo in 8.6.1 notes

(cherry picked from commit 34b8e613606653187f1ffae36a83e33f0c673720)

- - - - -
f6595773 by Andrey Mokhov at 2018-09-07T08:11:48-04:00
Fix a constant folding rule

Summary:
One of the constant folding rules introduced in D2858 is:

```
(L y :-:   v) :-: (L x :-: w) -> return $ mkL (y-x)   `add` (w `add` v)
```

Or, after removing syntactic noise: `(y - v) - (x - w) ==> (y - x) + (w + v)`.
This is incorrect, since the sign of `v` is changed from negative to positive.
As a consequence, the following program prints `3` when compiled with `-O`:

```
-- This is just subtraction in disguise
minus :: Int -> Int -> Int
minus x y = (8 - y) - (8 - x)
{-# NOINLINE minus #-}

main :: IO ()
main = print (2 `minus` 1)
```

The correct rule is: `(y - v) - (x - w) ==> (y - x) + (w - v)`.

This commit does the fix. I haven't found any other issues with the constant
folding code, but it's difficult to be certain without some automated checking.

Reviewers: bgamari, tdammers

Subscribers: hsyl20, tdammers, rwbarton, carter

GHC Trac Issues: #15569

Differential Revision: https://phabricator.haskell.org/D5109

(cherry picked from commit 65eec9cfd4410c0e30b0ed06116c15f8ce3de49d)

- - - - -
95b7b0a0 by chris-bacon at 2018-09-07T08:11:48-04:00
Fixed typo in exponent example

(cherry picked from commit 36c1431d9d2d06049190cc0888dbfaee8e2179d6)

- - - - -
76a23314 by Ben Gamari at 2018-09-07T08:11:48-04:00
rts: Handle SMALL_MUT_ARR_PTRS in retainer profilter

Summary: These can be treated similarly to MUT_ARRY_PTRS. Fixes #15529.

Reviewers: erikd, simonmar

Reviewed By: simonmar

Subscribers: RyanGlScott, rwbarton, carter

GHC Trac Issues: #15529

Differential Revision: https://phabricator.haskell.org/D5075

(cherry picked from commit 2cf98e2207421200fc73c25a08f6435859cdff92)

- - - - -
d2ac6e95 by Ben Gamari at 2018-09-12T19:26:35-04:00
template-haskell: Fix typo in changelog

- - - - -
75d3415b by Simon Marlow at 2018-09-12T19:26:35-04:00
Fix gcCAFs()

The test here should have been changed after D1106.  It was harmless
but we caught fewer GC'd CAFs than we should have.

Test Plan:
Using `nofib/imaginary/primes` compiled with `-debug`.

Before:
```
> ./primes 100 +RTS -G1 -A32k -DG
CAF gc'd at 0x0x7b0960
CAF gc'd at 0x0x788728
CAF gc'd at 0x0x790db0
CAF gc'd at 0x0x790de0
12 CAFs live
CAF gc'd at 0x0x788880
12 CAFs live
12 CAFs live
12 CAFs live
12 CAFs live
12 CAFs live
12 CAFs live
12 CAFs live
12 CAFs live
12 CAFs live
12 CAFs live
12 CAFs live
547
CAF gc'd at 0x0x7995c8
13 CAFs live
```

After:

```
> ./primes 100 +RTS -G1 -A32k -DG
CAF gc'd at 0x0x7b0960
CAF gc'd at 0x0x788728
CAF gc'd at 0x0x790db0
CAF gc'd at 0x0x790de0
12 CAFs live
CAF gc'd at 0x0x788880
12 CAFs live
12 CAFs live
12 CAFs live
12 CAFs live
12 CAFs live
12 CAFs live
12 CAFs live
12 CAFs live
12 CAFs live
12 CAFs live
12 CAFs live
547
CAF gc'd at 0x0x7995c8
CAF gc'd at 0x0x790ea0
12 CAFs live
```

Reviewers: bgamari, osa1, erikd, noamz

Reviewed By: bgamari

Subscribers: rwbarton, thomie, carter

Differential Revision: https://phabricator.haskell.org/D4963

(cherry picked from commit e431d75f8350f25159f9aaa49fe9a504e94bc0a4)

- - - - -
279d69d3 by Ömer Sinan Ağacan at 2018-09-13T13:44:31-04:00
Revert incorrect STM wakeup optimisation

Summary: (see the comments)

Reviewers: simonmar, bgamari, erikd

Reviewed By: simonmar

Subscribers: rwbarton, carter

Differential Revision: https://phabricator.haskell.org/D5144

(cherry picked from commit 36740b4c346c619e31d24d6672caa6f4f7fea123)

- - - - -
c15d44f8 by Simon Marlow at 2018-09-13T13:44:31-04:00
Revert "Disable the SRT offset optimisation on MachO platforms"

This reverts commit bf10456edaa03dc010821cd4c3d9f49cb11d89da.

- - - - -
d82e8af8 by Ben Gamari at 2018-09-13T13:44:31-04:00
Revert "Fix a bug in SRT generation"

This reverts commit d424d4a46a729f8530e9273282d22b6b8f34daaa.

- - - - -
25765469 by Ben Gamari at 2018-09-13T13:44:31-04:00
Revert "Fix retainer profiling after SRT overhaul"

This reverts commit d78dde9ff685830bc9d6bb24a158eb31bb8a7028.

- - - - -
b0f06f53 by Ben Gamari at 2018-09-13T13:44:31-04:00
Revert "Comments and refactoring only"

This reverts commit f2d27c1ad69321872a87a37144fe41e815301f5b.

- - - - -
6f2596b4 by Ben Gamari at 2018-09-13T13:44:31-04:00
Revert "Merge FUN_STATIC closure with its SRT"

This reverts commit 838b69032566ce6ab3918d70e8d5e098d0bcee02.

- - - - -
dee22948 by Ben Gamari at 2018-09-13T13:44:31-04:00
Revert "Save a word in the info table on x86_64"

This reverts commit 2b0918c9834be1873728176e4944bec26271234a.

- - - - -
ceffd7fe by Ben Gamari at 2018-09-13T13:44:32-04:00
Revert "An overhaul of the SRT representation"

This reverts commit eb8e692cab7970c495681e14721d05ecadd21581.

- - - - -
8344588e by Ryan Scott at 2018-09-16T12:31:14-04:00
Fix #15502 by not casting to Int during TH conversion

Summary:
When turning an `IntegerL` to an `IntegralLit` during TH
conversion, we were stupidly casting an `Integer` to an `Int` in
order to determine how it should be pretty-printed. Unsurprisingly,
this causes problems when the `Integer` doesn't lie within the bounds
of an `Int`, as demonstrated in #15502.

The fix is simple: don't cast to an `Int`.

Test Plan: make test TEST=T15502

Reviewers: bgamari, simonpj

Reviewed By: simonpj

Subscribers: simonpj, rwbarton, carter

GHC Trac Issues: #15502

Differential Revision: https://phabricator.haskell.org/D5089

(cherry picked from commit 7a3cda534d1447c813aa37cdd86e20b8d782cb02)

- - - - -
83ca9bb2 by Simon Peyton Jones at 2018-09-16T12:31:17-04:00
canCFunEqCan: use isTcReflexiveCo (not isTcReflCo)

As Trac #15577 showed, it was possible for a /homo-kinded/
constraint to trigger the /hetero-kinded/ branch of canCFunEqCan,
and that triggered an infinite loop.

The fix is easier, but there remains a deeper questions: why is
the flattener producing giant refexive coercions?

(cherry picked from commit 2e226a46c422c12f78dc3d3f62fe5a15e22bd986)

- - - - -
2cdb2de1 by Ryan Scott at 2018-09-16T12:31:17-04:00
Fix #15550 by quoting RULE names during TH conversion

Summary:
When converting a `RuleP` to a GHC source `RuleD` during TH
conversion, we were stupidly not double-quoting the name of the rule.
Easily fixed.

Test Plan: make test TEST=T15550

Reviewers: goldfire, bgamari, simonpj

Reviewed By: simonpj

Subscribers: simonpj, rwbarton, carter

GHC Trac Issues: #15550

Differential Revision: https://phabricator.haskell.org/D5090

(cherry picked from commit 5e6cf2a9301a5473ff9c5319b96de941b1ad72dd)

- - - - -
ebc8ebf8 by Ryan Scott at 2018-09-16T12:31:17-04:00
Fix #15572 by checking for promoted names in ConT

Summary:
When converting `ConT`s to `HsTyVar`s in `Convert`, we were
failing to account for the possibility of promoted data constructor
names appearing in a `ConT`, which could result in improper
pretty-printing results (as observed in #15572). The fix is
straightforward: use `Promoted` instead of `NotPromoted` when the
name of a `ConT` is a data constructor name.

Test Plan: make test TEST=T15572

Reviewers: goldfire, bgamari, simonpj, monoidal

Reviewed By: goldfire, simonpj

Subscribers: monoidal, rwbarton, carter

GHC Trac Issues: #15572

Differential Revision: https://phabricator.haskell.org/D5112

(cherry picked from commit c46a5f2002f6694ea58f79f505d57f3b7bd450e7)

- - - - -
bc907262 by Chaitanya Koparkar at 2018-09-16T12:31:17-04:00
Fix #10859 by using foldr1 while deriving Eq instances

Summary:
Previously, we were using foldl1 instead, which led to the derived
code to be wrongly associated.

Test Plan: ./validate

Reviewers: RyanGlScott, nomeata, simonpj, bgamari

Reviewed By: RyanGlScott, nomeata

Subscribers: rwbarton, carter

GHC Trac Issues: #10859

Differential Revision: https://phabricator.haskell.org/D5104

(cherry picked from commit 2d953a60489ba30433e5f2fe27c50aa9da75f802)

- - - - -
2116932e by Ben Gamari at 2018-09-16T15:46:29-04:00
base: showEFloat: Handle negative precisions the same of zero precision

Test Plan: Validate

Reviewers: hvr, alpmestan

Reviewed By: alpmestan

Subscribers: rwbarton, carter

GHC Trac Issues: #15509

Differential Revision: https://phabricator.haskell.org/D5083

(cherry picked from commit e71e341f87c055ecc01f85ddd8d7a2094dfa8e9a)

- - - - -
c5debde5 by Chaitanya Koparkar at 2018-09-16T15:46:29-04:00
Update hsc2hs submodule

Test Plan: ./validate

Reviewers: bgamari, hvr, RyanGlScott

Reviewed By: RyanGlScott

Subscribers: monoidal, rwbarton, carter

Differential Revision: https://phabricator.haskell.org/D5114

(cherry picked from commit ce240b3f998b68853c47ab131126eb9a245256c5)

- - - - -
f458bca3 by Ben Gamari at 2018-09-16T16:54:10-04:00
Bump stm submodule

- - - - -
a512f1e3 by Ben Gamari at 2018-09-16T16:56:33-04:00
Bump text submodule

- - - - -
4b094c6d by Ben Gamari at 2018-09-16T16:56:33-04:00
Bump Cabal submodule

- - - - -
c4209ba8 by Ben Gamari at 2018-09-16T16:56:33-04:00
Bump deepseq submodule

- - - - -
6cad8e31 by Krzysztof Gogolewski at 2018-09-18T09:27:42-04:00
Fix T15502 on 32-bit

Summary:
The expected output uses a hardcoded value for
maxBound :: Int.

This should fix one of circleci failures on i386.

Test Plan: make test TEST=T15502

Reviewers: RyanGlScott, bgamari

Reviewed By: RyanGlScott

Subscribers: rwbarton, carter

GHC Trac Issues: #15502

Differential Revision: https://phabricator.haskell.org/D5151

(cherry picked from commit ecbe26b6966a3a64f4e22e862370536b1dd4440f)

- - - - -
058e3b7d by Ben Gamari at 2018-09-18T11:45:21-04:00
Revert "Revert "An overhaul of the SRT representation""

This reverts commit ceffd7fe3f310cb30fec870f768e8047af309d99.

- - - - -
547ccb52 by Ben Gamari at 2018-09-18T11:45:22-04:00
Revert "Revert "Save a word in the info table on x86_64""

This reverts commit dee229487fccc6a994d4bb9c4ceda0903bec707b.

- - - - -
c0eb1abf by Ben Gamari at 2018-09-18T11:45:23-04:00
Revert "Revert "Merge FUN_STATIC closure with its SRT""

This reverts commit 6f2596b432a9915d648286195b48c48ccdd14a2c.

- - - - -
5e6c217d by Ben Gamari at 2018-09-18T11:45:25-04:00
Revert "Revert "Comments and refactoring only""

This reverts commit b0f06f53761820167e8b2cda61bc8c3137a83f92.

- - - - -
b97867cd by Ben Gamari at 2018-09-18T11:45:25-04:00
Revert "Revert "Fix retainer profiling after SRT overhaul""

This reverts commit 25765469b312aa21422c635aa5852a69e29f24f1.

- - - - -
aef47537 by Ben Gamari at 2018-09-18T11:45:26-04:00
Revert "Revert "Fix a bug in SRT generation""

This reverts commit d82e8af82d4be11252294290564044ef956ec2a4.

- - - - -
f442bc6c by Ben Gamari at 2018-09-18T11:45:27-04:00
Revert "Revert "Disable the SRT offset optimisation on MachO platforms""

This reverts commit c15d44f8b3f00bfe152c2f9d3c6f60efd204fb23.

- - - - -
28356f21 by Simon Marlow at 2018-09-18T11:49:05-04:00
Don't shortcut SRTs for static functions (#15544)

Shortcutting the SRT for a static function can lead to resurrecting a
static object at runtime, which violates assumptions in the GC. See
comments for details.

Test Plan:
- manual testing (in progress)
- validate

Reviewers: osa1, bgamari, erikd

Reviewed By: bgamari

Subscribers: rwbarton, carter

GHC Trac Issues: #15544

Differential Revision: https://phabricator.haskell.org/D5145

(cherry picked from commit a324dfdf3b505ea30d134dc8183d7b4bb441ced4)

- - - - -
14e58640 by Takenobu Tani at 2018-09-19T10:29:13-04:00
users-guide: Fix code-block layout for QuantifiedConstraints

Summary:
Fix code-block layout for QuantifiedConstraints.

[ci skip]

Test Plan: build

Reviewers: bgamari, monoidal

Reviewed By: monoidal

Subscribers: rwbarton, carter

Differential Revision: https://phabricator.haskell.org/D5121

(cherry picked from commit 43967c0c7d2d0110cfc5f9d64a7dab3a3dda8953)

- - - - -
be14113c by Ben Gamari at 2018-09-19T14:56:41-04:00
Bump stm submodule

- - - - -
35959490 by Ben Gamari at 2018-09-19T15:30:39-04:00
users-guide: Fill out release highlights

- - - - -
6f717bc6 by Ben Gamari at 2018-09-20T10:25:58-04:00
users-guide: Fix build with sphinx 1.8

It seems that both add_object_type and add_directive_to_domain both register a
directive. Previously sphinx didn't seem to mind this but as of Sphinx 1.8 it
crashes with an exception.

(cherry picked from commit 4eebc8016f68719e1ccdf460754a97d1f4d6ef05)

- - - - -
5ed9c861 by Zejun Wu at 2018-09-20T16:06:01-04:00
users_guide: fix sphinx error caused by non-explicit override

Encouter following error when `make`:

```
Extension error:
The 'ghc-flag' directive is already registered to domain std
```

as we register `ghc-flag` to `std` in `add_object_type` first and then
overtride it in `add_directive_to_domain`.

Test Plan:
  make -C utils/haddock/doc html SPHINX_BUILD=/usr/bin/sphinx-build

Reviewers: austin, bgamari, patrickdoc

Subscribers: rwbarton, carter

Differential Revision: https://phabricator.haskell.org/D5161

(cherry picked from commit 8c7d33a8ff6d3ea55b5dc8108d9441521af68ab8)

- - - - -
af0bf169 by Ben Gamari at 2018-09-20T18:18:23-04:00
user-guide: Allow build with sphinx < 1.8

Apparently the override argument to add_directive_to_domain was added in sphinx
1.8.

(cherry picked from commit a257782f56e5e330349d4cc7db71e297d8396c67)

- - - - -
0d2cdec7 by Ben Gamari at 2018-09-21T12:39:51-04:00
Set RELEASE=YES

- - - - -
f28b05b5 by Ben Gamari at 2018-09-21T16:05:30-04:00
circleci: Run cabal update with -v

The cabal update command appears to be timing out with no output after 10 minutes.

- - - - -
94cadce6 by Ben Gamari at 2018-10-05T18:47:47-04:00
Add testcase for #14251

(cherry picked from commit ba086ca72ee6c77abba685f3100ad513e38a1a87)

- - - - -
4338398f by Ben Gamari at 2018-10-05T18:47:55-04:00
testsuite: Don't force run of llvm ways in T14251

This breaks if LLVM is not available.

(cherry picked from commit d0d74842868ceb6716b7334eb6310f61f90023bf)

- - - - -
73273be4 by Kavon Farvardin at 2018-10-05T18:48:16-04:00
Multiple fixes / improvements for LLVM backend

- Fix for #13904 -- stop "trashing" callee-saved registers, since it is
  not actually doing anything useful.

- Fix for #14251 -- fixes the calling convention for functions passing
  raw SSE-register values by adding padding as needed to get the values
  in the right registers. This problem cropped up when some args were
  unused an dropped from the live list.

- Fixed a typo in 'readnone' attribute

- Added 'lower-expect' pass to level 0 LLVM optimization passes to
  improve block layout in LLVM for stack checks, etc.

Test Plan: `make test WAYS=optllvm` and `make test WAYS=llvm`

Reviewers: bgamari, simonmar, angerman

Reviewed By: angerman

Subscribers: rwbarton, carter

GHC Trac Issues: #13904, #14251

Differential Revision: https://phabricator.haskell.org/D5190

(cherry picked from commit adcb5fb47c0942671d409b940d8884daa9359ca4)

- - - - -
bf256ef2 by Ben Gamari at 2018-10-05T18:48:18-04:00
Bump array submodule

- - - - -
a2e3334c by Tamar Christina at 2018-10-05T18:48:18-04:00
Drop accidental write-attributes request

Summary:
The new filesystem code accidentally asks for write attributes
permissions when doing read-only access.

I believe this is what's causing the GHC 8.6.1 tarballs to fail
when installed to a privileged location.
I haven't been able to reproduce the issue yet, but this permission
bit is wrong anyway.

Test Plan: I'm still trying to workout how to test that this works,
changing the permissions on the folder doesn't seem to reproduce
the error on a tarball I made from before the change.

Reviewers: bgamari, tdammers

Reviewed By: bgamari

Subscribers: tdammers, monoidal, rwbarton, carter

GHC Trac Issues: #15667

Differential Revision: https://phabricator.haskell.org/D5177

(cherry picked from commit deceb21b7ec64ae60377addc2679692ca500b6ae)

- - - - -
0af55c12 by Ryan Scott at 2018-10-05T18:48:18-04:00
Be mindful of GADT tyvar order when desugaring record updates

After commit ef26182e2014b0a2a029ae466a4b121bf235e4e4,
the type variable binders in GADT constructor type signatures
are now quantified in toposorted order, instead of always having
all the universals before all the existentials. Unfortunately, that
commit forgot to update some code (which was assuming the latter
scenario) in `DsExpr` which desugars record updates. This wound
up being the cause of #15499.

This patch makes up for lost time by desugaring record updates in
a way such that the desugared expression applies type arguments to
the right-hand side constructor in the correct order—that is, the
order in which they were quantified by the user.

Test Plan: make test TEST=T15499

Reviewers: simonpj, bgamari

Reviewed By: simonpj

Subscribers: rwbarton, carter

GHC Trac Issues: #15499

Differential Revision: https://phabricator.haskell.org/D5060

(cherry picked from commit 63b6a1d44849c479d2a7cb59211f5c64d133bc62)

- - - - -
facf7cce by Ben Gamari at 2018-10-07T11:54:13-04:00
users guide: Drop old release notes

- - - - -
87266ea7 by Alec Theriault at 2018-10-12T23:30:38-04:00
Don't show constraint tuples in errors (#14907)

Summary:
This means that 'GHC.Classes.(%,%)' is no longer mentioned in
error messages for things like

   class (a,b,c)  -- outside of 'GHC.Classes'
   class (a,Bool)

Test Plan: make TEST=T14907a && make TEST=T14907b

Reviewers: RyanGlScott, bgamari

Reviewed By: RyanGlScott

Subscribers: rwbarton, carter

GHC Trac Issues: #14907

Differential Revision: https://phabricator.haskell.org/D5172

(cherry picked from commit 9bfbc4e16d511678cffa9f7f76b369c8cfca7a66)

- - - - -
377975e0 by Ben Gamari at 2018-10-12T23:31:00-04:00
testsuite: Add test for #15053

Reviewers: Phyx

Reviewed By: Phyx

Subscribers: Phyx, rwbarton, thomie, carter

GHC Trac Issues: #15053

Differential Revision: https://phabricator.haskell.org/D4883

(cherry picked from commit f03f0d61bebe287e0df0254c175eb2f183d697aa)

- - - - -
52304776 by roland at 2018-10-12T23:31:07-04:00
Compiler panic on invalid syntax (unterminated pragma)

Summary: After a parse error in OPTIONS_GHC issue an error message instead of a compiler panic.

Test Plan: make test TEST=T15053

Reviewers: Phyx, thomie, bgamari, monoidal, osa1

Reviewed By: Phyx, monoidal, osa1

Subscribers: tdammers, osa1, rwbarton, carter

GHC Trac Issues: #15053

Differential Revision: https://phabricator.haskell.org/D5093

(cherry picked from commit df363a646b66f4dd13d63ec70f18e427cabc8878)

- - - - -
10e3125d by Ömer Sinan Ağacan at 2018-10-12T23:32:22-04:00
Fix slop zeroing for AP_STACK eager blackholes in debug build

As #15571 reports, eager blackholing breaks sanity checks as we can't
zero the payload when eagerly blackholing (because we'll be using the
payload after blackholing), but by the time we blackhole a previously
eagerly blackholed object (in `threadPaused()`) we don't have the
correct size information for the object (because the object's type
becomes BLACKHOLE when we eagerly blackhole it) so can't properly zero
the slop.

This problem can be solved for AP_STACK eager blackholing (which unlike
eager blackholing in general, is not optional) by zeroing the payload
after entering the stack. This patch implements this idea.

Fixes #15571.

Test Plan:
Previously concprog001 when compiled and run with sanity checks

    ghc-stage2 Mult.hs -debug -rtsopts
    ./Mult +RTS -DS

was failing with

    Mult: internal error: checkClosure: stack frame
        (GHC version 8.7.20180821 for x86_64_unknown_linux)
        Please report this as a GHC bug:  http://www.haskell.org/ghc/reportabug

thic patch fixes this panic. The test still panics, but it runs for a while
before panicking (instead of directly panicking as before), and the new problem
seems unrelated:

    Mult: internal error: ASSERTION FAILED: file rts/sm/Sanity.c, line 296
        (GHC version 8.7.20180919 for x86_64_unknown_linux)
        Please report this as a GHC bug:  http://www.haskell.org/ghc/reportabug

The new problem will be fixed in another diff.

I also tried slow validate (which requires D5164): this does not introduce any
new failures.

Reviewers: simonmar, bgamari, erikd

Reviewed By: simonmar

Subscribers: rwbarton, carter

GHC Trac Issues: #15571

Differential Revision: https://phabricator.haskell.org/D5165

(cherry picked from commit 66c17293648fd03a04aabfd807b3c8336e8f843a)

- - - - -
4ab2f347 by Vladislav Zavialov at 2018-10-12T23:32:49-04:00
Add -Wstar-is-type to the User's Guide

The -Wstar-is-type flag was added without documentation.
Now it has documentation.

Test Plan: Validate

Reviewers: bgamari

Reviewed By: bgamari

Subscribers: rwbarton, carter

Differential Revision: https://phabricator.haskell.org/D5203

(cherry picked from commit 07083fc44ebf3f0510ae1d71ae5c9c88c87ae1d8)

- - - - -
51c44793 by Alec Theriault at 2018-10-13T00:03:37-04:00
GHCi should not filter instances involving cTuples

Summary: See the new T12005 test case for an example of this.

Test Plan: make TEST=T12005

Reviewers: bgamari, osa1

Reviewed By: osa1

Subscribers: osa1, rwbarton, carter

GHC Trac Issues: #12005

Differential Revision: https://phabricator.haskell.org/D5182

(cherry picked from commit 21efbc7599e39ec93b8b13b7d7b84811226e6f6f)

- - - - -
a04ecd7b by Simon Marlow at 2018-10-13T13:26:18-04:00
Fix for recover with -fexternal-interpreter (#15418)

Summary:
When using -fexternal-interpreter, recover was not treating a Q
compuation that simply registered an error with addErrTc as failing.

Test Plan:
New unit tests:
* T15418 is the repro from in the ticket
* TH_recover_warns is a new test to ensure that we're keeping warnings when
  the body of recover succeeds.

Reviewers: bgamari, RyanGlScott, angerman, goldfire, erikd

Subscribers: rwbarton, carter

GHC Trac Issues: #15418

Differential Revision: https://phabricator.haskell.org/D5185

(cherry picked from commit d00c308633fe7d216d31a1087e00e63532d87d6d)

- - - - -
a22ee705 by Simon Peyton Jones at 2018-10-13T13:26:57-04:00
Do not mark CoVars as dead in the occur-anal

For years we have been marking CoVars as dead, becuase we
don't gather occurrence info from types.  This is obviously
wrong and caused Trac #15695.

See Note [Do not mark CoVars as dead] in OccurAnal.

(cherry picked from commit 02b303eed0170983921877801e57f55d012db301)

- - - - -
b11126fc by Ömer Sinan Ağacan at 2018-10-13T13:30:03-04:00
Fix dataToTag# argument evaluation

See #15696 for more details. We now always enter dataToTag# argument (done in
generated Cmm, in StgCmmExpr). Any high-level optimisations on dataToTag#
applications are done by the simplifier. Looking at tag bits (instead of
reading the info table) for small types is left to another diff.

Incorrect test T14626 is removed. We no longer do this optimisation (see
comment:44, comment:45, comment:60).

Comments and notes about special cases around dataToTag# are removed. We no
longer have any special cases around it in Core.

Other changes related to evaluating primops (seq# and dataToTag#) will be
pursued in follow-up diffs.

Test Plan: Validates with three regression tests

Reviewers: simonpj, simonmar, hvr, bgamari, dfeuer

Reviewed By: simonmar

Subscribers: rwbarton, carter

GHC Trac Issues: #15696

Differential Revision: https://phabricator.haskell.org/D5201

(cherry picked from commit ac977688523e5d77eb6f041f043552410b0c21da)

- - - - -
f7b1ee96 by Ben Gamari at 2018-10-15T22:23:49-04:00
base: Fill in TBAs in changelog

I've added a check in my release script to ensure that this doesn't happen in
the future.

(cherry picked from commit 2605458930f2d79738fab4437f10793448d4232c)

- - - - -
3e050064 by Simon Peyton Jones at 2018-10-17T14:46:22-04:00
Fail fast on pattern synonyms

We were recovering too eagerly from errors in pattern-synonym
type inference, leading to a cascade of confusing follow up errors
(Trac #15685, #15692).

The underlying issue is that a pattern synonym should have a closed,
fixed type, with no unification variables in it.  But it wasn't!

Fixing this made me change the interface to simplifyInfer slightly.
Instead of /emitting/ a residual implication constraint, it
now /returns/ it, so that the caller can decide what to do.

(cherry picked from commit 9ebfa03d9e9cbf79f698b5d4bd39e799e4e9a02c)

- - - - -
334be779 by Ben Gamari at 2018-10-17T14:46:22-04:00
Bump haddock submodule

- - - - -
ba5d0a48 by Richard Eisenberg at 2018-10-17T14:46:22-04:00
Fix #15761 by adding parens

This was just a pretty-printer infelicity. Fixed now.

Test case: printer/T15761

(cherry picked from commit 38c28c1a8bb129141e533866700e7318314f32c1)

- - - - -
578012be by Ben Gamari at 2018-10-17T15:31:36-04:00
circleci: Build with in-tree GMP on Darwin

Fixes #15404.

- - - - -
6f590e9c by Ben Gamari at 2018-10-17T18:39:25-04:00
Bump version to 8.6.2

- - - - -
093bbff2 by Ben Gamari at 2018-10-24T14:14:18-04:00
Bump hsc2hs submodule

- - - - -
2e23e1c7 by Kavon Farvardin at 2018-10-28T13:32:30-04:00
Fix for T14251 on ARM

We now calculate the SSE register padding needed to fix the calling
convention in LLVM in a robust way: grouping them by whether
registers in that class overlap (with the same class overlapping
itself).

My prior patch assumed that no matter the platform, physical
register Fx aliases with Dx, etc, for our calling convention.

This is unfortunately not the case for any platform except x86-64.

Test Plan:
Only know how to test on x86-64, but it should be tested on ARM with:

`make test WAYS=llvm && make test WAYS=optllvm`

Reviewers: bgamari, angerman

Reviewed By: bgamari

Subscribers: rwbarton, carter

GHC Trac Issues: #15780, #14251, #15747

Differential Revision: https://phabricator.haskell.org/D5254

(cherry picked from commit c36a2b596a6ba9d7a0a80df01b3c041720c727ca)

- - - - -
38618f74 by Zejun Wu at 2018-10-28T13:32:38-04:00
Fix rare undefined asm temp end label error in x86

Summary:
Encountered assembly error due to undefined label `.LcaDcU_info_end` for
following code generated by `pprFrameProc`:

```
.Lsat_sa8fp{v}_info_fde_end:
  .long .Lblock{v caDcU}_info_fde_end-.Lblock{v caDcU}_info_fde
.Lblock{v caDcU}_info_fde:
  .long _nbHlD-.Lsection_frame
  .quad block{v caDcU}_info-1
  .quad .Lblock{v caDcU}_info_end-block{v caDcU}_info+1
  .byte 1
```

This diff fixed the error.

Test Plan:
  ./validate

Also the case where we used to have assembly error is now fixed.
Unfortunately, I have limited insight here and cannot get a small enough repro
or test case for this.

Ben says:

> I think I see: Previously we only produced end symbols for the info
> tables of top-level procedures. However, blocks within a procedure may
> also have info tables, we will dutifully generate debug information for
> and consequently we get undefined symbols.

Reviewers: simonmar, scpmw, last_g, bgamari

Reviewed By: bgamari

Subscribers: rwbarton, carter

Differential Revision: https://phabricator.haskell.org/D5246

(cherry picked from commit cf961dcf5ebc26cbd960196ba387736334088303)

- - - - -
b539a99c by Ben Gamari at 2018-10-28T13:32:47-04:00
includes: Allow headers to be built with C++11 compilers

Summary:
Fixes #14784. Note that C++11 is quite conservative; we could likely accept
C++03 as well.

Test Plan:
```
$ cat >hi.c <<EOF
#include <Rts.h>
EOF
$ g++ -std=c++11 hi.c
```

Reviewers: simonmar, hvr

Subscribers: rwbarton, carter

GHC Trac Issues: #14784

Differential Revision: https://phabricator.haskell.org/D5244

(cherry picked from commit d3a1022fabb0ad337003fac774c6929f402ecb8b)

- - - - -
804518f7 by Ningning Xie at 2018-10-28T13:33:14-04:00
Fix `:k` command: add validity checking

Summary:
This patch fixes #15806, where we found that the `:k` command in GHCi
misses a validity checking for the type.

Missing validity checking causes `:k` to accept types that are not validated.
For example, `:k (Maybe (forall a. a -> a))` (incorrectly) returns `*`, while
impredictivity of type instantiation shouldn't be allowed.

Test Plan: ./validate

Reviewers: simonpj, goldfire, bgamari

Reviewed By: bgamari

Subscribers: rwbarton, carter

GHC Trac Issues: #15806

Differential Revision: https://phabricator.haskell.org/D5265

(cherry picked from commit 12cb5cf50b8b35394e2e2d57e1ac693c76f90833)

- - - - -
37d14601 by Fangyi Zhou at 2018-10-28T13:33:23-04:00
Fix integer overflow when encoding doubles (Trac #15271)

Summary:
Ticket #15271 reports a case where 1e1000000000 is incorrectly
converted to 0.0. After some investigation, I discovered the number is
converted to rational correctly, but converting the ratio into a double
introduced an error.

Tracking down to how the conversion is done, I found the rts float
implementation uses `ldexp`, whose signature is
`double ldexp (double x, int exp);`
The callsite passes an `I_` to the second argument, which is
platform-dependent. On machines where `I_` is 64 bits and `int` is 32 bits, we
observe integer overflow behaviour.

Here is a mapping from rational to exponent with observations
1e646457008  -> 2147483645 (result = infinity, positive in int32)
1e646457009  -> 2147483648 (result = 0.0, overflow to negative in int32)
1e1000000000 -> 3321928042 (result = infinity, overflow to positive in int32)
1e1555550000 -> 5167425196 (result = 0.0, overflow to negative in int32)

We fix this issue by comparing STG_INT_MIN/MAX and INT_MIN/MAX and bound the
value appropriately.

Test Plan: New test cases

Reviewers: bgamari, erikd, simonmar

Reviewed By: bgamari

Subscribers: rwbarton, carter

GHC Trac Issues: #15271

Differential Revision: https://phabricator.haskell.org/D5271

(cherry picked from commit 311a63979cfa2c1e81be54b82205e681f6ec4f14)

- - - - -
de9a8feb by Christiaan Baaij at 2018-10-28T13:33:30-04:00
Comment out CONSTANT_FOLDED in GHC.Natural

Summary:
Although these functions were marked as CONSTANT_FOLDED, they did
not have a corresponding builtinRule in PrelRules. The idea was
probably to add them eventually, but this hasn't manifested so
far.

The plan is to eventually add builtin rules for these functions
over Natural, so as a reminder we simply comment out the
CONSTANT_FOLDED  annotation instead of removing it completely.

Reviewers: hvr, bgamari

Reviewed By: bgamari

Subscribers: rwbarton, carter

Differential Revision: https://phabricator.haskell.org/D5267

(cherry picked from commit 3ec6fe8827956cc36b58cdf0bb1f5752eaa2a8ea)

- - - - -
d2cd150e by sheaf at 2018-10-28T13:34:03-04:00
plugins: search for .a files if necessary

Summary:
on windows, plugins are loaded via .a files,
but those paths were not being searched when loading plugins

Test Plan: ./validate

Reviewers: Phyx, bgamari

Reviewed By: Phyx

Subscribers: RyanGlScott, rwbarton, carter

GHC Trac Issues: #15700

Differential Revision: https://phabricator.haskell.org/D5253

(cherry picked from commit 70298db16c3f0ea4adb603ccb2b5e93eb9c7a556)

- - - - -
9f802777 by Ben Gamari at 2018-10-28T17:44:11-04:00
users-guide: Add release notes for 8.6.2

- - - - -
b391cae1 by Ningning Xie at 2018-10-28T19:02:33-04:00
Fix TcType.anyRewritableTyVar

Summary:
This patch fixes #15805, where we found that
`TcType.anyRewritableTyVar` has one wrong case.

Besides the fix, it also:
- removed some unnecessary `ASSERT2(tcIsTcTyVar...)` in `TcType`, as now we have
     `tcIsTcTyVar = isTyVar`.
- fixed some comments

Test Plan: ./validate

Reviewers: goldfire, simonpj, bgamari

Reviewed By: simonpj

Subscribers: rwbarton, carter

GHC Trac Issues: #15805

Differential Revision: https://phabricator.haskell.org/D5263

(cherry picked from commit a7f64c6cbfc5562adff207945576d1c9db2a58d9)

- - - - -
a49f95c2 by Simon Peyton Jones at 2018-10-30T14:58:32-04:00
Report a Wanted error even if there are Given ones

We suppress some Given errors; see Note [Given errors]
in TcErrors.  But we must be careful not to suppress
Wanted errors because of the presence of these Given
errors -- else we might allow compilation to bogusly
proceed

The rubber hits the road in TcRnTypes.insolubleCt,
where we don't want to treat Givens as insoluble,
nor (and this is the new bit) Deriveds that arise
from Givens.  See Note [Given insolubles] in TcRnTypes.

This fixes #15767.

(cherry picked from commit 6b1102e2cfcffb265fd33cf8a99ab5e6b3f14906)

Ben notes:

  I have folded some test output changes in `TEST="T12529 T12921 mc13
  mc14"` into this patch that were not in the original.

- - - - -
d67cbced by Ben Gamari at 2018-10-30T14:58:32-04:00
users-guide: Fix typo

- - - - -
9c4314ec by Ben Gamari at 2018-10-30T14:58:32-04:00
Revert "Fix for T14251 on ARM"

This reverts commit 2e23e1c7de01c92b038e55ce53d11bf9db993dd4.

- - - - -
377fe398 by Ben Gamari at 2018-10-30T14:58:32-04:00
Revert "Multiple fixes / improvements for LLVM backend"

This reverts commit 73273be476a8cc6c13368660b042b3b0614fd928.

Unfortunately we were unable to come to a fix that didn't sacrifice the
ability to bootstrap GHC using the LLVM backend. Reverting for 8.6.2.

- - - - -
2567e8f3 by Ryan Scott at 2018-10-30T14:58:32-04:00
Fix #15815 by parenthesizing the arguments to infix ~

An unfortunate consequence of commit
b9483981d128f55d8dae3f434f49fa6b5b30c779 (`Remove HsEqTy and XEqTy`)
is infix uses of `~` in TH quotes now desugar differently than
before. In particular, we have that:

```haskell
a ~ (Int -> Int)
```

Now desugars to:

```haskell
HsOpTy a (~) (HsOpTy Int (->) Int)
```

Which GHC interprets as being:

```haskell
a ~ Int -> Int
```

Or, equivalently:

```haskell
(a ~ Int) -> Int
```

Which is different than what was intended! This is the cause
of #15815.

All of this has revealed that we likely need to renovate the way we
desugar infix type operators to be more consistent with the treatment
for infix expressions (see
https://ghc.haskell.org/trac/ghc/ticket/15815#comment:5 for more on
this.) Doing so would constitute a breaking change, however, so we
will likely want to wait until another major GHC release to do this.

In the meantime, this patch offers a non-invasive change to the way
that infix uses of `~` are desugared. This makes the program
in #15815 compile again by inserting extra `HsParTy`s around the
arguments to `~` if they are lacking them.

Test Plan: make test TEST=T15815

Reviewers: int-index, goldfire, bgamari

Reviewed By: int-index

Subscribers: int-e, rwbarton, carter

GHC Trac Issues: #15815

Differential Revision: https://phabricator.haskell.org/D5274

(cherry picked from commit b8a797ecc34a309bd78f5a290e3554642a3a478a)

- - - - -
a876edcb by Ben Gamari at 2018-10-30T14:58:32-04:00
users-guide: Note existence of #14251

- - - - -
cfc3ad1f by Ben Gamari at 2018-10-31T12:23:39-04:00
users-guide: Fix version number

- - - - -
7a439e7b by Richard Eisenberg at 2018-11-02T10:59:49-04:00
Fix #15787 by squashing a coercion hole.

In type-incorrect code, we can sometimes let a coercion
hole make it through the zonker. If this coercion hole then
ends up in the environment (e.g., in the type of a data
constructor), then it causes trouble later.

This patch avoids trouble by substituting the coercion hole
for its representative CoVar. Really, any coercion would do,
but the CoVar was very handy.

test case: polykinds/T15787

(cherry picked from commit 4427315a65b25db22e1754d41b43dd4b782b022f)

- - - - -
41f0f6c2 by Richard Eisenberg at 2018-11-02T11:00:36-04:00
Don't lint erroneous programs.

newFamInst lints its types. This is good. But it's not so good
when there have been errors and thus recovery tycons are about.
So we now don't.

Fixes #15796.

Test case: typecheck/should_fail/T15796

(cherry picked from commit 1f72a1c81368e34387aac38c0b1c59521cec58ec)

- - - - -
9448fdce by Ben Gamari at 2018-11-02T11:48:05-04:00
integer-gmp: Fix TBA in changelog

- - - - -
701c872f by Ben Gamari at 2018-11-05T11:47:11-05:00
Set RELEASE=NO

- - - - -
cbde2726 by Ben Gamari at 2018-11-06T10:33:01-05:00
libiserv: Generate cabal file with autoconf

Previously the version number was set by hand. This seems like
unnecessary busywork for what is mostly an internal library.

- - - - -
130b91db by Ben Gamari at 2018-11-07T21:02:19-05:00
distrib/configure: Set RanlibCmd

This fixes #15875.

- - - - -
22cd729a by Ömer Sinan Ağacan at 2018-11-22T14:01:30-05:00
Fix heap corruption during stable name allocation

See #15906 for the problem. To fix we simply call `allocate()` instead of
`ALLOC_PRIM()`. `allocate()` does not trigger GC when the nursery is full,
instead it extends it.

Test Plan:
This validates. memo001 now passes with `-debug` compile parameter. I'll add
another test that runs memo001 with `-debug` once I figure out how to use
stdout files for multiple tests.

Reviewers: simonmar, bgamari, erikd

Reviewed By: simonmar

Subscribers: rwbarton, carter

GHC Trac Issues: #15906

Differential Revision: https://phabricator.haskell.org/D5342

(cherry picked from commit 691aa715cf43bf9d88ee32bca37e471bae35adfb)

- - - - -
14ae4ab6 by Ben Gamari at 2018-11-22T14:01:30-05:00
users guide: We no longer build libraries with -split-objs

We now generally use split-sections instead.

(cherry picked from commit f5fbecc85967218fd8ba6512f10eea2daf2812ac)

- - - - -
c8b24dce by Ben Gamari at 2018-11-22T14:01:30-05:00
rts/M32Alloc: Abort if m32 linker mmap fails

Previously we should just blinding dereference a NULL pointer.

(cherry picked from commit 86f6890e3689f2f75ecca8172eda0338fe3e9769)

- - - - -
e67bebbf by Christiaan Baaij at 2018-11-22T14:01:35-05:00
Load plugins in interactive session

Reviewers: bgamari, tdammers

Reviewed By: tdammers

Subscribers: monoidal, rwbarton, carter

GHC Trac Issues: #15633

Differential Revision: https://phabricator.haskell.org/D5348

(cherry picked from commit 599eaada382d04722219bfc319bde94591be3fb1)

- - - - -
4519d98d by Simon Marlow at 2018-11-22T14:48:15-05:00
Fix a bug in SRT generation (#15892)

Summary:
The logic in `Note [recursive SRTs]` was correct. However, my
implementation of it wasn't: I got the associativity of
`Set.difference` wrong, which led to an extremely subtle and difficult
to find bug.

Fortunately now we have a test case. I was able to cut down the code
to something manageable, and I've added it to the test suite.

Test Plan:
Before (using my stage 1 compiler without the fix):

```
====> T15892(normal) 1 of 1 [0, 0, 0]
cd "T15892.run" &&  "/home/smarlow/ghc/inplace/bin/ghc-stage1" -o T15892
T15892.hs -dcore-lint -dcmm-lint -no-user-package-db -rtsopts
-fno-warn-missed-specialisations -fshow-warning-groups
-fdiagnostics-color=never -fno-diagnostics-show-caret -Werror=compat
-dno-debug-output  -O
cd "T15892.run" && ./T15892  +RTS -G1 -A32k -RTS
Wrong exit code for T15892(normal)(expected 0 , actual 134 )
Stderr ( T15892 ):
T15892: internal error: evacuate: strange closure type 0
    (GHC version 8.7.20181113 for x86_64_unknown_linux)
    Please report this as a GHC bug:  http://www.haskell.org/ghc/reportabug
Aborted (core dumped)
*** unexpected failure for T15892(normal)
=====> T15892(g1) 1 of 1 [0, 1, 0]
cd "T15892.run" &&  "/home/smarlow/ghc/inplace/bin/ghc-stage1" -o T15892
T15892.hs -dcore-lint -dcmm-lint -no-user-package-db -rtsopts
-fno-warn-missed-specialisations -fshow-warning-groups
-fdiagnostics-color=never -fno-diagnostics-show-caret -Werror=compat
-dno-debug-output  -O
cd "T15892.run" && ./T15892 +RTS -G1 -RTS +RTS -G1 -A32k -RTS
Wrong exit code for T15892(g1)(expected 0 , actual 134 )
Stderr ( T15892 ):
T15892: internal error: evacuate: strange closure type 0
    (GHC version 8.7.20181113 for x86_64_unknown_linux)
    Please report this as a GHC bug:  http://www.haskell.org/ghc/reportabug
Aborted (core dumped)
```

After (using my stage 2 compiler with the fix):

```
=====> T15892(normal) 1 of 1 [0, 0, 0]
cd "T15892.run" &&  "/home/smarlow/ghc/inplace/test   spaces/ghc-stage2"
-o T15892 T15892.hs -dcore-lint -dcmm-lint -no-user-package-db -rtsopts
-fno-warn-missed-specialisations -fshow-warning-groups
-fdiagnostics-color=never -fno-diagnostics-show-caret -Werror=compat
-dno-debug-output
cd "T15892.run" && ./T15892  +RTS -G1 -A32k -RTS
=====> T15892(g1) 1 of 1 [0, 0, 0]
cd "T15892.run" &&  "/home/smarlow/ghc/inplace/test   spaces/ghc-stage2"
-o T15892 T15892.hs -dcore-lint -dcmm-lint -no-user-package-db -rtsopts
-fno-warn-missed-specialisations -fshow-warning-groups
-fdiagnostics-color=never -fno-diagnostics-show-caret -Werror=compat
-dno-debug-output
cd "T15892.run" && ./T15892 +RTS -G1 -RTS +RTS -G1 -A32k -RTS
```

Reviewers: bgamari, osa1, erikd

Reviewed By: osa1

Subscribers: rwbarton, carter

GHC Trac Issues: #15892

Differential Revision: https://phabricator.haskell.org/D5334

- - - - -
b6d2d837 by Dario Bertini at 2018-11-22T16:03:11-05:00
circleci: Actually build with in-tree GMP on Darwin

Fixes #15404.

(cherry picked from commit 3584bd4255eb59be043252c9b4ef16bcbd835c9b)

- - - - -
65ced246 by Dario Bertini at 2018-11-22T16:06:09-05:00
rts/MachO: Add a bit more debugging output to getNames

(cherry picked from commit 9e0a23b95c285c4019fd2d36102374ee582f1dcb)

- - - - -
b44caa05 by Dario Bertini at 2018-11-22T16:06:09-05:00
rts/MachO: A bit of refactoring in ocGetNames

Eliminates a bit of repetition.

(cherry picked from commit b2f6f896a0bae0e68ec629bd6817a2cb2533a12c)

- - - - -
11fd7df5 by Dario Bertini at 2018-11-22T16:06:09-05:00
rts/MachO: Iterate through N (all) symbols, not M external symbols

Fixes #15105

(cherry picked from commit 254890855ee04762cc0392da19e0c42fc039a718)

- - - - -
c2c6f498 by Ben Gamari at 2018-11-22T16:59:14-05:00
Revert "libiserv: Generate cabal file with autoconf"

This reverts commit cbde2726f10b8f4c19483bbb755ad42356098c51.

- - - - -
64a50445 by Ben Gamari at 2018-11-22T17:02:45-05:00
base: Mention openFile throwing does-not-exist-errors on FIFOs

As discussed in #15715, the POSIX specification specifies that
attempting to open a FIFO in write-only mode when the FIFO has no
readers will fail with -ENOENT.

[skip ci]

Test Plan: Read it

Reviewers: hvr

Subscribers: rwbarton, carter

GHC Trac Issues: #15715

Differential Revision: https://phabricator.haskell.org/D5295

(cherry picked from commit 4ba3fa31ddfa12b428bd67216a2d4118dc9e8311)

- - - - -
2594ea25 by Richard Eisenberg at 2018-11-22T17:04:06-05:00
Fix #15859 by checking, not assuming, an ArgFlag

We thought that visible dependent quantification was impossible
in terms, but Iceland Jack discovered otherwise in #15859. This fixes an
ASSERT failure that arose.

test case: dependent/should_fail/T15859

(cherry picked from commit 72b82343b79365dc74ffafb345dd33499a7fd394)

(cherry picked from commit 5693ddd071033516a1804420a903cb7e3677682b)

- - - - -
6db7d11e by Alexander Vershilov at 2018-12-06T12:41:22-05:00
Remove explicit recursion in retainer profiling (fixes #14758)

Retainer profiling contained a recursion that under
certain circumstances could lead to the stack overflow
in C code.

The idea of the improvement is to keep an explicit stack for the
object, more precise to reuse existing stack, but allow new type of
objects to be stored there.

There is no reliable reproducer that is not a big program
but in some cases foldr (+) 0 [1..10000000] can work.

Reviewers: bgamari, simonmar, erikd, osa1

Reviewed By: bgamari, osa1

Subscribers: osa1, rwbarton, carter

GHC Trac Issues: #14758

Differential Revision: https://phabricator.haskell.org/D5351

(cherry picked from commit 5f1d949ab9e09b8d95319633854b7959df06eb58)

- - - - -
bf074e3e by Ben Gamari at 2018-12-06T12:43:34-05:00
Bump iserv versions

This fixes #15866, the original fix for which didn't merge cleanly to
the stable branch.

- - - - -
c64918c1 by Tamar Christina at 2018-12-06T12:49:25-05:00
linker: store entire link map and use it.

Summary:
This fixes a corner case in which we have seen the symbol multiple times in
different static libraries, but due to a depencency we end up loading the
symbol from a library other than the first one.

Previously the runtime linker would only track symbols from the first
library and did not store the full link map.  In this case it was unable
to find the address for the symbols in the second library during delay
loading.

This change stores the address of all symbols seen so a full link map
is generated, such that when we make a different decision later than what
was expected we're able to still correctly load the library.

Test Plan: ./validate, new testcase T15894

Reviewers: angerman, bgamari, erikd, simonmar

Reviewed By: bgamari

Subscribers: rwbarton, carter

GHC Trac Issues: #15894

Differential Revision: https://phabricator.haskell.org/D5353

(cherry picked from commit a8b7cef4d45a5003bf7584e06912f0f632116c71)

- - - - -
ed86e3b5 by Ben Gamari at 2018-12-06T16:28:16-05:00
Windows: Use the "big" PE object format on amd64

Test Plan: Do full build on Windows.

Reviewers: AndreasK, Phyx

Reviewed By: AndreasK

Subscribers: rwbarton, erikd, carter

GHC Trac Issues: #15934

Differential Revision: https://phabricator.haskell.org/D5383

(cherry picked from commit 1ef90f990da90036d481c830d8832e21b8f1571b)

- - - - -
d59812ce by Ben Gamari at 2018-12-06T16:57:16-05:00
users guide: Add release notes for 8.6.3

- - - - -
31cd867e by Ben Gamari at 2018-12-06T16:58:34-05:00
Release 8.6.3

- - - - -
ff9ee830 by Ben Gamari at 2018-12-15T15:08:07-05:00
utils/gen-dll: Bump containers upper bound

Fixes #16023.

(cherry picked from commit e709c8f8d45c699840f5bab7c9ff71373a53b8b0)

- - - - -
c6827011 by Ben Gamari at 2018-12-23T20:09:38-05:00
Revert "Windows: Use the "big" PE object format on amd64"

This ended up breaking GHCi due to alignment issues. See #16071.

This reverts commit ed86e3b531322f74d2c2d00d7ff8662b08fabde6.

- - - - -
b6237131 by Ben Gamari at 2018-12-27T01:11:20-05:00
Grab CI configuration from master

This is awfully ugly but is nevertheless significantly less error-prone
than cherry-picking all of the relevant commits manually.

- - - - -
27019e9f by Ben Gamari at 2018-12-27T10:26:43-05:00
gitlab-ci: Skip performance tests

These are just too fragile on ghc-8.6 which lacks #12758.

- - - - -
8b043e88 by Ben Gamari at 2018-12-29T16:35:09-05:00
testsuite: Skip ffi018_ghci when unregisterised

As noted in #16085 this test is fragile in unregisterised compilers.

(cherry picked from commit 7bfc1e81377d1e37069cf52bd090530124dcd871)

- - - - -
b348b173 by Ben Gamari at 2018-12-29T17:40:01-05:00
gitlab-ci: Allow integer-simple and unregisterised builds to fail

- - - - -
1acf0ceb by Ben Gamari at 2018-12-30T10:20:13-05:00
testsuite: Mark heapprof001 as broken in prof_hc_hb way on i386

As documented in #15382, this is known to fail in prof_hc_hb on i386.
Concerningly, I have also seen this test non-deterministically fail in
prof_hc_hb on amd64. We should really investigate this.

(cherry picked from commit 8fd3f9a67f9c7b447a5bfcb3aefd8986794918ce)

- - - - -
ee6cf4b3 by Ben Gamari at 2018-12-30T10:20:13-05:00
testsuite: Mark objcpp-hi and T13366 as broken on Darwin due to #16083

(cherry picked from commit 1c0c5e844226f3d77af31d97b21ffb8b14b55740)

- - - - -
08cfa615 by Simon Marlow at 2019-01-07T12:18:09-05:00
Fix recompilation bug with default class methods (#15970)

If a module uses a class, then it can instantiate the class and
thereby use its default methods, so we must include the default
methods when calculating the fingerprint for the class.

Test Plan:
New unit test: driver/T15970

Before:

```
=====> T15970(normal) 1 of 1 [0, 0, 0]
cd "T15970.run" && $MAKE -s --no-print-directory T15970
Wrong exit code for T15970()(expected 0 , actual 2 )
Stdout ( T15970 ):
Makefile:13: recipe for target 'T15970' failed
Stderr ( T15970 ):
C.o:function Main_zdfTypeClassMyDataType1_info: error: undefined
reference to 'A_toTypedData2_closure'
C.o:function Main_main1_info: error: undefined reference to
'A_toTypedData2_closure'
C.o(.data+0x298): error: undefined reference to 'A_toTypedData2_closure'
C.o(.data+0x480): error: undefined reference to 'A_toTypedData2_closure'
collect2: error: ld returned 1 exit status
`gcc' failed in phase `Linker'. (Exit code: 1)
```

After: test passes.

Reviewers: bgamari, simonpj, erikd, watashi, afarmer

Subscribers: rwbarton, carter

GHC Trac Issues: #15970

Differential Revision: https://phabricator.haskell.org/D5394

(cherry picked from commit 288f681e06accbae690c46eb8a6e997fa9e5f56a)

- - - - -
a7fdfd95 by Ben Gamari at 2019-01-10T23:58:53-05:00
Release notes for 8.6.4

- - - - -
3ad6c60e by Ben Gamari at 2019-01-15T23:21:39-05:00
gitlab: Collect artifacts on Windows

- - - - -
c25a9d8e by Peter Trommler at 2019-01-17T13:38:21-05:00
PPC NCG: Implement simple 64-Bit compare on 32-bit

- - - - -
ff47e60a by Simon Peyton Jones at 2019-01-28T18:07:36-05:00
Fix bogus worker for newtypes

The "worker" for a newtype is actually a function
with a small (compulsory) unfolding, namely a cast.

But the construction of this function was plain wrong
for newtype /instances/; it cast the arguemnt to the
family type rather than the representation type.

This never actually bit us because, in the case of a
family instance, we immediately cast the result to
the family type.  So we get
   \x. (x |> co1) |> co2

where the compositio of co1 and co2 is ill-kinded.
However the optimiser (even the simple optimiser)
just collapsed those casts, ignoring the mis-match
in the middle, so we never saw the problem.

Trac #16191 is indeed a dup of #16141; but the resaon
these tickets produce Lint errors is not the unnecessary
forcing; it's because of the ill-typed casts.

This patch fixes the ill-typed casts, properly.  I can't
see a way to trigger an actual failure prior to this
patch, but it's still wrong wrong wrong to have ill-typed
casts, so better to get rid of them.

(cherry picked from commit a5373c1fe172dee31e07bcb7c7f6caff1035e6ba)

- - - - -
7ec385f4 by Ben Gamari at 2019-01-28T18:07:38-05:00
itimer: Don't free condvar until we know ticker is stopped

When we are shutting down the pthread ticker we signal the start_cond condition
variable to ensure that the ticker thread wakes up and exits in a reasonable
amount of time. Previously, when the ticker thread would shut down it was
responsible for freeing the start_cond condition variable. However, this would
lead to a race wherein the ticker would free start_cond, then the main thread
would try to signal it in an effort to wake the ticker (#16150).

Avoid this by moving the mutex destruction to the main thread.

(cherry picked from commit 7b12b3f0240321ac1ee43f14eb9c07e015022eeb)

- - - - -
4f180640 by Ben Gamari at 2019-01-28T18:07:38-05:00
rts: Use always-available locking operations in pthread Itimer implementation

Previously we ACQUIRE_LOCK and RELEASE_LOCK but these compile to a noop in the
non-threaded RTS, as noted in #16150. Use OS_ACQUIRE_LOCK and OS_RELEASE_LOCK
instead.

(cherry picked from commit ce11f6f25c1160262830d9670c4eaaebac37cbaf)

- - - - -
ee6e4fcc by Ömer Sinan Ağacan at 2019-01-28T18:07:38-05:00
Fix a MSG_BLACKHOLE sanity check, add some comments

Reviewers: simonmar, bgamari, erikd

Reviewed By: simonmar

Subscribers: rwbarton, carter

GHC Trac Issues: #15508

Differential Revision: https://phabricator.haskell.org/D5178

(cherry picked from commit d90946cea1357d3e99805c27dab1e811785a4088)

- - - - -
4f712fb3 by Ömer Sinan Ağacan at 2019-01-28T18:07:38-05:00
Implement a sanity check for CCS fields in profiling builds

This helped me debug one of the bugs in #15508. I'm not sure if this is
a good idea, but it worked for me, so wanted to submit this as a MR.

(cherry picked from commit 82d1a88dec216d761b17252ede760da5c566007f)

- - - - -
cf5b5a74 by Ömer Sinan Ağacan at 2019-01-28T18:07:38-05:00
Fix raiseAsync() UNDERFLOW_FRAME handling in profiling runtime

UNDERFLOW_FRAMEs don't have profiling headers so we have to use the
AP_STACK's function's CCS as the new frame's CCS.

Fixes one of the many bugs caught by concprog001 (#15508).

(cherry picked from commit 74cd4ec5d2f9321aad5db3285cb60d78f2562996)

- - - - -
14001294 by Ömer Sinan Ağacan at 2019-01-28T18:07:38-05:00
Fix checkPtrInArena

(See comments)

(cherry picked from commit 448f0e7dd78a8d9404f1aa5e8522cc284360c06d)

- - - - -
1e4f0a9a by Ben Gamari at 2019-02-02T20:16:31-05:00
Bump process submodule to 1.6.4.0

See #16199

- - - - -
9fbcfb97 by Ben Gamari at 2019-02-02T20:16:31-05:00
Bump transformers to 0.5.6.2

See #16199.

- - - - -
18e2de94 by Ben Gamari at 2019-02-09T10:41:41-05:00
testsuite: Mark ghci063 as broken on Darwin

This is the last failing test on Darwin preventing us from disallowing CI
failures. See #16201.

(cherry picked from commit 0b705fadf936eaf48aaca26d2f7c8c9ae9158c66)

- - - - -
8c2dbc16 by Ben Gamari at 2019-02-10T19:56:41-05:00
testsuite: Add test for #16104

- - - - -
5abfd982 by Ben Gamari at 2019-02-10T19:56:41-05:00
GhcPlugins: Fix lookup of TH names

Previously `thNameToGhcName` was calling `lookupOrigNameCache` directly, which
failed to handle the case that the name wasn't already in the name cache. This
happens, for instance, when the name was in scope in a plugin being used during
compilation but not in scope in the module being compiled. In this case we the
interface file containing the name won't be loaded and `lookupOrigNameCache`
fails. This was the cause of #16104.

The solution is simple: use the nicely packaged `lookupOrigIO` instead.

(cherry picked from commit 0d9f105ba423af4f2ca215a18d04d4c8e2c372a8)

- - - - -
0f253b89 by Tamar Christina at 2019-02-10T19:56:41-05:00
Stack: fix name mangling.

(cherry picked from commit fb031b9b046e48ffe0d2864ec76bee3bc8ff5625)

- - - - -
ba11d0aa by Ben Gamari at 2019-02-12T13:17:02-05:00
users-guide: Some more release notes for 8.6.4

- - - - -
a481b199 by Ömer Sinan Ağacan at 2019-02-20T13:19:05-05:00
Fix two bugs in stg_ap_0_fast in profiling runtime

This includes two bug fixes in profiling version of stg_ap_0_fast:

- PAPs allocated by stg_ap_0_fast are now correctly tagged. This
  invariant is checked in Sanity.c:checkPAP.

  (This was originally implemented in 2693eb11f5, later reverted with
  ab55b4ddb7 because it revealed the bug below, but it wasn't clear at
  the time whether the bug was the one below or something in the commit)

- The local variable `untaggedfun` is now marked as a pointer so it
  survives GC.

With this we finally fix all known bugs caught in #15508. `concprog001`
now works reliably with prof+threaded and prof runtimes (with and
without -debug).

(cherry picked from commit 908b4b8659713f0b7a1704ce33c7fa30e3e0ffc3)

- - - - -
bdc9680c by Herbert Valerio Riedel at 2019-02-20T14:46:47-05:00
Fix regression incorrectly advertising TH support

`--supported-languages` must only advertise language extensions
which are supported by the compiler in order for tooling such
as Cabal relying on this signalling not to behave incorrectly.

Fixes #16331

(cherry picked from commit db4372cda7f6c87e7ad26efe3fca4b3f7f527a48)

- - - - -
e1f52f38 by Ben Gamari at 2019-03-02T15:30:07-05:00
gitlab-ci: Pull docker images from ghc/ci-images registry

(cherry picked from commit b90695cdaaa0995c1b7a26289c63be9f9e9cfe3e)

- - - - -
b09f057a by Ben Gamari at 2019-03-02T15:30:11-05:00
gitlab-ci: Produce DWARF-enabled binary distribution

(cherry picked from commit d298cb9cf722126316c9697c20a8e0048498efb9)

- - - - -
b6f949ff by Ben Gamari at 2019-03-02T15:32:30-05:00
gitlab-ci: Drop CircleCI jobs

- - - - -
aac18e9a by Ben Gamari at 2019-03-04T15:48:49-05:00
Bump to 8.6.4

- - - - -
1d5b97c2 by Ben Gamari at 2019-03-05T16:02:06-05:00
Set RELEASE=NO

- - - - -
fd4637c8 by Ben Gamari at 2019-03-19T14:23:21-04:00
gitlab-ci: Don't build Windows in quick flavour

This applies the fix from !516 to the 8.6 branch.

- - - - -
2f196a5c by Ben Gamari at 2019-03-21T15:29:55-04:00
Introduce i386-windows job

- - - - -
1dfc8864 by Matthew Pickering at 2019-03-29T17:03:56-04:00
Don't overwrite the set log_action when using --interactive

-ddump-json didn't work with --interactive as --interactive overwrote
the log_action in terms of defaultLogAction.

Reviewers: bgamari

Subscribers: rwbarton, thomie, carter

GHC Trac Issues: #14078

Differential Revision: https://phabricator.haskell.org/D4533

(cherry picked from commit 10faf44d97095b2f8516b6d449d266f6889dcd70)

- - - - -
97c1ef86 by Edward Z. Yang at 2019-03-29T17:34:49-04:00
Fix #16219: TemplateHaskell causes indefinite package build error

It should work to write an indefinite package using TemplateHaskell,
so long as all of the actual TH code lives outside of the package.
However, cleverness we had to build TH code even when building
with -fno-code meant that we attempted to build object code for
modules in an indefinite package, even when the signatures were
not instantiated.  This patch disables said logic in the event
that an indefinite package is being typechecked.

Signed-off-by: Edward Z. Yang <ezyang at fb.com>

Test Plan: validate

Reviewers: simonpj, bgamari

Reviewed By: bgamari

Subscribers: rwbarton, carter

GHC Trac Issues: #16219

Differential Revision: https://phabricator.haskell.org/D5475

(cherry picked from commit d6d735c1114082b9e9cc1ba7da87c49f52891320)

- - - - -
e04e3d81 by Ben Gamari at 2019-04-04T12:35:47-04:00
gitlab-ci: Build hyperlinked sources for releases

Fixes #16445.

(cherry picked from commit a32ac2f4d963b657c0a53359b492c593e82304b1)

- - - - -
9cf1f91b by klebinger.andreas at gmx.at at 2019-04-04T12:35:47-04:00
Restore Xmm registers properly in StgCRun.c

This fixes #16514: Xmm6-15 was restored based off rax instead of rsp.
The code was introduced in the fix for #14619.

(cherry picked from commit 9b131500371a07626e33edc56700c12322364560)

- - - - -
d2a284ab by Ben Gamari at 2019-04-04T12:35:47-04:00
configure: Always use AC_LINK_ELSEIF when testing against assembler

This fixes #16440, where the build system incorrectly concluded that the
`.subsections_via_symbols` assembler directive was supported on a Linux
system. This was caused by the fact that gcc was invoked with `-flto`;
when so-configured gcc does not call the assembler but rather simply
serialises its AST for compilation during the final link.

This is described in Note [autoconf assembler checks and -flto].

(cherry picked from commit 7b090b53fea065d2cfd967ea919426af9ba8d737)

- - - - -
7d3040ac by Ben Gamari at 2019-04-06T12:32:53-04:00
Add release notes for 8.6.5

- - - - -
f6cd3ae8 by Ben Gamari at 2019-04-06T12:35:41-04:00
users-guide: Add missing libraries to release notes library list

- - - - -
d6c93748 by Ben Gamari at 2019-04-07T15:35:51-04:00
users-guide: Fix version number reference

- - - - -
b9001408 by Ben Gamari at 2019-04-07T15:39:32-04:00
users-guide: Mention fix to #16514

- - - - -
4c7d3228 by Ben Gamari at 2019-04-08T13:47:04-04:00
Move 8.6.5-notes.rst to docs/users_guide

- - - - -
f0592c22 by Ben Gamari at 2019-04-19T09:45:03-04:00
Do not build i386 Windows with profiled libraries

Due to #15934

- - - - -
71abf35a by Ben Gamari at 2019-04-19T09:47:48-04:00
gitlab-ci: Add centos7 release job

- - - - -
1df8c217 by Takenobu Tani at 2019-04-19T10:22:27-04:00
gitlab-ci: Enable -haddock while building ghc library

Fixing #16415. This is a variant of @takenobu-hs's !769.

- - - - -
e86d5a21 by Ben Gamari at 2019-04-19T17:04:47-04:00
gitlab-ci: Disable Sphinx PDF output on Debian 8

- - - - -
bc75b94f by Ben Gamari at 2019-04-21T10:27:23-04:00
gitlab-ci: Fix YAML syntax

- - - - -
92b6a023 by Ben Gamari at 2019-04-22T21:46:46-04:00
Release 8.6.5

- - - - -
b1e4243a by Ben Gamari at 2020-11-10T11:23:40-05:00
gitlab-ci: Bump Docker images

- - - - -


30 changed files:

- .circleci/config.yml
- + .circleci/images/aarch64-linux-deb9/Dockerfile
- + .circleci/images/i386-linux-deb8/Dockerfile
- + .circleci/images/i386-linux-deb9/Dockerfile
- .circleci/images/i386-linux/Dockerfile
- + .circleci/images/linters/Dockerfile
- + .circleci/images/powerpc64le-linux-deb9-cross/Dockerfile
- + .circleci/images/update-image
- .circleci/images/x86_64-freebsd/Dockerfile
- + .circleci/images/x86_64-linux-centos7/Dockerfile
- + .circleci/images/x86_64-linux-deb8/Dockerfile
- + .circleci/images/x86_64-linux-deb9/Dockerfile
- .circleci/images/x86_64-linux-fedora/Dockerfile
- + .circleci/images/x86_64-linux-fedora27/Dockerfile
- .circleci/images/x86_64-linux/Dockerfile
- .circleci/prepare-system.sh
- + .circleci/push-test-metrics.sh
- + .gitlab-ci.yml
- + .gitlab/circle-ci-job.sh
- + .gitlab/darwin-init.sh
- + .gitlab/fix-submodules.py
- + .gitlab/linters/check-cpp.py
- + .gitlab/linters/check-makefiles.py
- + .gitlab/linters/linter.py
- + .gitlab/win32-init.sh
- aclocal.m4
- compiler/basicTypes/BasicTypes.hs
- compiler/basicTypes/DataCon.hs
- compiler/basicTypes/Demand.hs
- compiler/basicTypes/MkId.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/4f35f54516e35f7a56b67244a15a9f094efae1a9...b1e4243ad3783b46e2f56be53f2303de2787ce3a

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/4f35f54516e35f7a56b67244a15a9f094efae1a9...b1e4243ad3783b46e2f56be53f2303de2787ce3a
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/20201110/344c8bf6/attachment-0001.html>


More information about the ghc-commits mailing list