[Git][ghc/ghc][wip/stack_cloning] 33 commits: Fix `instance Bounded a => Bounded (Down a)` (#18716)

Ben Gamari gitlab at gitlab.haskell.org
Sat Oct 31 18:09:41 UTC 2020



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


Commits:
9ad51bc9 by David Beacham at 2020-10-27T13:59:35-04:00
Fix `instance Bounded a => Bounded (Down a)` (#18716)

* Flip `minBound` and `maxBound` to respect the change in ordering
* Remove awkward `Enum` (and hence `Integral`) instances for
  `Data.Ord.Down`
* Update changelog

- - - - -
eedec53d by Vladislav Zavialov at 2020-10-27T14:00:11-04:00
Version bump: base-4.16 (#18712)

Also bumps upper bounds on base in boot libraries (incl. submodules).

- - - - -
412018c1 by Tamar Christina at 2020-10-27T14:00:49-04:00
winio: simplify logic remove optimization step.

- - - - -
4950dd07 by Ben Gamari at 2020-10-27T14:01:24-04:00
hadrian: Suppress xelatex output unless it fails

As noted in #18835, xelatex produces an absurd amount of output, nearly
all of which is meaningless. Silence this.

Fixes #18835.

- - - - -
f3d8ab2e by Ben Gamari at 2020-10-27T14:02:00-04:00
build system: Clean mingw tarballs

Tamar noticed in !4293 that the build systems fail to clean up the mingw
tarballs directory (`ghc-tarballs`). Fix this in both the make build
system and Hadrian.

- - - - -
0b3d23af by Simon Peyton Jones at 2020-10-27T14:02:34-04:00
Fix two constraint solving problems

This patch fixes two problems in the constraint solver.

* An actual bug #18555: we were floating out a constraint to eagerly,
  and that was ultimately fatal.  It's explained in
  Note [Do not float blocked constraints] in GHC.Core.Constraint.

  This is all very delicate, but it's all going to become irrelevant
  when we stop floating constraints (#17656).

* A major performance infelicity in the flattener.  When flattening
  (ty |> co) we *never* generated Refl, even when there was nothing
  at all to do.  Result: we would gratuitously rewrite the constraint
  to exactly the same thing, wasting work.  Described in #18413, and
  came up again in #18855.

  Solution: exploit the special case by calling the new function
  castCoercionKind1.  See Note [castCoercionKind1] in
  GHC.Core.Coercion

- - - - -
f76c5a08 by Sergei Trofimovich at 2020-10-27T14:03:14-04:00
ghc.mk: amend 'make sdist'

Noticed 'make sdist' failure seen as:

```
"rm" -rf sdistprep/ghc/ghc-9.1.0.20201020/hadrian/_build/ (SRC_DIST_GHC_DIR)/hadrian/dist-newstyle/
/bin/sh: -c: line 0: syntax error near unexpected token `('
```

commit 9657f6f34
("sdist: Include hadrian sources in source distribution")
added a new cleanup path without a variable expantion.

The change adds variable reference. While at it move directory
cleanup to a separate statement.

Amends #18794

Signed-off-by: Sergei Trofimovich <slyfox at gentoo.org>

- - - - -
78b52c88 by David Eichmann at 2020-10-27T14:03:51-04:00
Use config.run_ways for multi_compile_and_run tests

- - - - -
e3fdd419 by Alan Zimmerman at 2020-10-27T14:04:26-04:00
Api Annotations: Introduce AnnPercent for HsExplicitMult

For the case

  foo :: a %p -> b

The location of the '%' is captured, separate from the 'p'

- - - - -
d2a25f42 by Ben Gamari at 2020-10-27T14:05:02-04:00
gitlab-ci: Bump ci-images

Bumps bootstrap compiler to 8.10.1.

- - - - -
28f98b01 by Sebastian Graf at 2020-10-27T14:05:37-04:00
DmdAnal: Kill `is_thunk` case in `splitFV`

The `splitFV` function implements the highly dubious hack
described in `Note [Lazy und unleashable free variables]` in
GHC.Core.Opt.DmdAnal. It arranges it so that demand signatures only
carry strictness info on free variables. Usage info is released through
other means, see the Note. It's purely for analysis performance reasons.

It turns out that `splitFV` has a quite involved case for thunks that
produces slightly different usage signatures and it's not clear why we
need it: `splitFV` is only relevant in the LetDown case and the only
time we call it on thunks is for top-level or local recursive thunks.

Since usage signatures of top-level thunks can only reference other
top-level bindings and we completely discard demand info we have on
top-level things (see the lack of `setIdDemandInfo` in
`dmdAnalTopBind`), the `is_thunk` case is completely irrelevant here.

For local, recursive thunks, the added benefit of the `is_thunk` test
is marginal: We get used-multiple-times in some cases where previously
we had used-once if a recursive thunk has multiple call sites. It's
very unlikely and not a case to optimise for.

So we kill the `is_thunk` case and inline `splitFV` at its call site,
exposing `isWeakDmd` from `GHC.Types.Demand` instead.

The NoFib summary supports this decision:

```
            Min           0.0%     -0.0%
            Max           0.0%     +0.0%
 Geometric Mean          -0.0%     -0.0%
```

- - - - -
60322f93 by Ben Gamari at 2020-10-28T21:11:39-04:00
hadrian: Don't quote metric baseline argument

Previously this was quoted inappropriately.
- - - - -
c85eb372 by Alan Zimmerman at 2020-10-28T21:12:15-04:00
API Annotations: put constructors in alphabetical order

- - - - -
795908dc by John Ericson at 2020-10-29T03:53:14-04:00
Widen acceptance threshold for T10421a

Progress towards #18842. As @sgraf812 points out, widening the window is
dangerous until the exponential described in #17658 is fixed. But this
test has caused enough misery and is low stakes enough that we and
@bgamari think it's worth it in this one case for the time being.

- - - - -
0e9f6def by Sylvain Henry at 2020-10-29T03:53:52-04:00
Split GHC.Driver.Types

I was working on making DynFlags stateless (#17957), especially by
storing loaded plugins into HscEnv instead of DynFlags. It turned out to
be complicated because HscEnv is in GHC.Driver.Types but LoadedPlugin
isn't: it is in GHC.Driver.Plugins which depends on GHC.Driver.Types. I
didn't feel like introducing yet another hs-boot file to break the loop.

Additionally I remember that while we introduced the module hierarchy
(#13009) we talked about splitting GHC.Driver.Types because it contained
various unrelated types and functions, but we never executed. I didn't
feel like making GHC.Driver.Types bigger with more unrelated Plugins
related types, so finally I bit the bullet and split GHC.Driver.Types.

As a consequence this patch moves a lot of things. I've tried to put
them into appropriate modules but nothing is set in stone.

Several other things moved to avoid loops.

* Removed Binary instances from GHC.Utils.Binary for random compiler
  things
* Moved Typeable Binary instances into GHC.Utils.Binary.Typeable: they
  import a lot of things that users of GHC.Utils.Binary don't want to
  depend on.
* put everything related to Units/Modules under GHC.Unit:
  GHC.Unit.Finder, GHC.Unit.Module.{ModGuts,ModIface,Deps,etc.}
* Created several modules under GHC.Types: GHC.Types.Fixity, SourceText,
  etc.
* Split GHC.Utils.Error (into GHC.Types.Error)
* Finally removed GHC.Driver.Types

Note that this patch doesn't put loaded plugins into HscEnv. It's left
for another patch.

Bump haddock submodule

- - - - -
22f5d9a9 by Sylvain Henry at 2020-10-29T03:53:52-04:00
GC: Avoid data race (#18717, #17964)

- - - - -
2ef2fac4 by Ryan Scott at 2020-10-29T04:18:52-04:00
Check for large tuples more thoroughly

This fixes #18723 by:

* Moving the existing `GHC.Tc.Gen.HsType.bigConstraintTuple` validity
  check to `GHC.Rename.Utils.checkCTupSize` for consistency with
  `GHC.Rename.Utils.checkTupSize`, and
* Using `check(C)TupSize` when checking tuple _types_, in addition
  to checking names, expressions, and patterns.

Note that I put as many of these checks as possible in the typechecker so
that GHC can properly distinguish between boxed and constraint tuples. The
exception to this rule is checking names, which I perform in the renamer
(in `GHC.Rename.Env`) so that we can rule out `(,, ... ,,)` and
`''(,, ... ,,)` alike in one fell swoop.

While I was in town, I also removed the `HsConstraintTuple` and
`HsBoxedTuple` constructors of `HsTupleSort`, which are functionally
unused. This requires a `haddock` submodule bump.

- - - - -
7f8be3eb by Richard Eisenberg at 2020-10-29T22:08:13-04:00
Remove unnecessary gender from comments/docs

While, say, alternating "he" and "she" in sequential writing
may be nicer than always using "they", reading code/documentation
is almost never sequential. If this small change makes individuals
feel more welcome in GHC's codebase, that's a good thing.

- - - - -
9902d9ec by Viktor Dukhovni at 2020-10-30T05:28:30-04:00
[skip ci] Fix typo in `callocBytes` haddock.

- - - - -
31fcb55f by Ryan Scott at 2020-10-30T18:52:50-04:00
Split HsConDecl{H98,GADT}Details

Haskell98 and GADT constructors both use `HsConDeclDetails`, which includes
`InfixCon`. But `InfixCon` is never used for GADT constructors, which results
in an awkward unrepresentable state. This removes the unrepresentable state by:

* Renaming the existing `HsConDeclDetails` synonym to `HsConDeclH98Details`,
  which emphasizes the fact that it is now only used for Haskell98-style data
  constructors, and
* Creating a new `HsConDeclGADTDetails` data type with `PrefixConGADT` and
  `RecConGADT` constructors that closely resemble `PrefixCon` and `InfixCon`
  in `HsConDeclH98Details`. The key difference is that `HsConDeclGADTDetails`
  lacks any way to represent infix constructors.

The rest of the patch is refactoring to accommodate the new structure of
`HsConDecl{H98,GADT}Details`. Some highlights:

* The `getConArgs` and `hsConDeclArgTys` functions have been removed, as
  there is no way to implement these functions uniformly for all
  `ConDecl`s. For the most part, their previous call sites now
  pattern match on the `ConDecl`s directly and do different things for
  `ConDeclH98`s and `ConDeclGADT`s.

  I did introduce one new function to make the transition easier:
  `getRecConArgs_maybe`, which extracts the arguments from a `RecCon(GADT)`.
  This is still possible since `RecCon(GADT)`s still use the same representation
  in both `HsConDeclH98Details` and `HsConDeclGADTDetails`, and since the
  pattern that `getRecConArgs_maybe` implements is used in several places,
  I thought it worthwhile to factor it out into its own function.
* Previously, the `con_args` fields in `ConDeclH98` and `ConDeclGADT` were
  both of type `HsConDeclDetails`. Now, the former is of type
  `HsConDeclH98Details`, and the latter is of type `HsConDeclGADTDetails`,
  which are distinct types. As a result, I had to rename the `con_args` field
  in `ConDeclGADT` to `con_g_args` to make it typecheck.

  A consequence of all this is that the `con_args` field is now partial, so
  using `con_args` as a top-level field selector is dangerous. (Indeed, Haddock
  was using `con_args` at the top-level, which caused it to crash at runtime
  before I noticed what was wrong!) I decided to add a disclaimer in the 9.2.1
  release notes to advertise this pitfall.

Fixes #18844. Bumps the `haddock` submodule.

- - - - -
57c3db96 by Ryan Scott at 2020-10-31T02:53:55-04:00
Make typechecker equality consider visibility in ForAllTys

Previously, `can_eq_nc'` would equate `ForAllTy`s regardless of their
`ArgFlag`, including `forall i -> i -> Type` and `forall i. i -> Type`! To fix
this, `can_eq_nc'` now uses the `sameVis` function to first check if the
`ArgFlag`s are equal modulo specificity. I have also updated `tcEqType`'s
implementation to match this behavior. For more explanation on the "modulo
specificity" part, see the new `Note [ForAllTy and typechecker equality]`
in `GHC.Tc.Solver.Canonical`.

While I was in town, I fixed some related documentation issues:

* I added `Note [Typechecker equality]` to `GHC.Tc.Utils.TcType` to describe
  what exactly distinguishes `can_eq_nc'` and `tcEqType` (which implement
  typechecker equality) from `eqType` (which implements definitional equality,
  which does not care about the `ArgFlags` of `ForAllTy`s at all).
* The User's Guide had some outdated prose on the specified/inferred
  distinction being different for types and kinds, a holdover from #15079. This
  is no longer the case on today's GHC, so I removed this prose, added some new
  prose to take its place, and added a regression test for the programs in
  #15079.
* The User's Guide had some _more_ outdated prose on inferred type variables
  not being allowed in `default` type signatures for class methods, which is no
  longer true as of the resolution of #18432.
* The related `Note [Deferred Unification]` was being referenced as
  `Note [Deferred unification]` elsewhere, which made it harder to `grep`
  for. I decided to change the name of the Note to `Deferred unification`
  for consistency with the capitalization style used for most other Notes.

Fixes #18863.

- - - - -
a98593f0 by Sylvain Henry at 2020-10-31T02:54:34-04:00
Refactor numeric constant folding rules

Avoid the use of global pattern synonyms.

1) I think it's going to be helpful to implement constant folding for
   other numeric types, especially Natural which doesn't have a wrapping
   behavior. We'll have to refactor these rules even more so we'd better
   make them less cryptic.

2) It should also be slightly faster because global pattern synonyms
   matched operations for every numeric types instead of the current one:
   e.g., ":**:" pattern was matching multiplication for both Int# and
   Word# types. As we will probably want to implement constant folding
   for other numeric types (Int8#, Int16#, etc.), it is more efficient
   to only match primops for a given type as we do now.

- - - - -
730ef38f by Sylvain Henry at 2020-10-31T02:54:34-04:00
Simplify constant-folding (#18032)

See #18032 for the details.

* Use `Lit (LitNumber _ i)` instead of `isLitValue_maybe` which does
  more work but that is not needed for constant-folding
* Don't export `GHC.Types.Literal.isLitValue_maybe`
* Kill `GHC.Types.Literal.isLitValue` which isn't used

- - - - -
d5a53c1a by Ben Gamari at 2020-10-31T02:55:10-04:00
primops.txt.pp: Move ByteArray# primops to separate file

This file will be generated.

- - - - -
b4278a41 by Ben Gamari at 2020-10-31T02:55:10-04:00
primops: Generate ByteArray# index/read/write primops

Previously these were mostly undocumented and was ripe for potential
inconsistencies.

- - - - -
08e6993a by Sylvain Henry at 2020-10-31T02:55:50-04:00
Move loadDecl into IfaceToCore

- - - - -
cb1f755c by Tamar Christina at 2020-10-31T09:26:56-04:00
winio: Fix unused variables warnings

- - - - -
eb368078 by Andrzej Rybczak at 2020-10-31T09:27:34-04:00
Add testcase for #816

- - - - -
154a79fa by Sven Tennie at 2020-10-31T13:54:14-04:00
deriveConstants: Add hie.yaml

- - - - -
8efcab85 by Sven Tennie at 2020-10-31T13:54:20-04:00
base: Generalize newStablePtrPrimMVar

Make it polymorphic in the type of the MVar's value.

- - - - -
648cd4ad by Sven Tennie at 2020-10-31T14:07:00-04:00
Introduce snapshotting of thread's own stack

Introduce `StackSnapshot#` type and the `cloneMyStack#` primop, allowing
the user to reify the state of the calling thread's stack for later
inspection.

The stack snapshot is offline/cold, i.e. it isn't evaluated any further.

For technical details, please see note [Stack Cloning].

- - - - -
35b7999a by Sven Tennie at 2020-10-31T14:07:06-04:00
Introduce cloning of other threads' stacks

Introduce `cloneThreadStack` function, allowing threads to request
snapshots of other threads' stacks.

For technical details, please see note [Stack Cloning].

- - - - -
5e88f509 by Sven Tennie at 2020-10-31T14:07:06-04:00
Introduce printing support for StackSnapshot#'s

This refactors the RTS's existing Printer module to allow printing of
StackSnapshot#'s.

- - - - -


30 changed files:

- .gitlab-ci.yml
- compiler/GHC.hs
- compiler/GHC/Builtin/Names.hs
- compiler/GHC/Builtin/PrimOps.hs
- compiler/GHC/Builtin/Types.hs
- compiler/GHC/Builtin/Types/Prim.hs
- compiler/GHC/Builtin/Utils.hs
- + compiler/GHC/Builtin/bytearray-ops.txt.pp
- compiler/GHC/Builtin/primops.txt.pp
- compiler/GHC/ByteCode/Asm.hs
- compiler/GHC/ByteCode/InfoTable.hs
- compiler/GHC/ByteCode/Linker.hs
- compiler/GHC/Cmm/Pipeline.hs
- compiler/GHC/Core.hs
- compiler/GHC/Core/Coercion.hs
- compiler/GHC/Core/Coercion/Axiom.hs
- − compiler/GHC/Core/ConLike.hs-boot
- compiler/GHC/Core/DataCon.hs
- compiler/GHC/Core/FamInstEnv.hs
- compiler/GHC/Core/Lint.hs
- compiler/GHC/Core/Make.hs
- compiler/GHC/Core/Opt/ConstantFold.hs
- compiler/GHC/Core/Opt/DmdAnal.hs
- compiler/GHC/Core/Opt/FloatIn.hs
- compiler/GHC/Core/Opt/Monad.hs
- compiler/GHC/Core/Opt/Pipeline.hs
- compiler/GHC/Core/Opt/Simplify.hs
- compiler/GHC/Core/Opt/SpecConstr.hs
- compiler/GHC/Core/Opt/Specialise.hs
- compiler/GHC/Core/Opt/WorkWrap.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d1da7d7da23b62719346cf79695664de694cb8b3...5e88f5097f60b24330d4397afcb5aa5d996fbb0a

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d1da7d7da23b62719346cf79695664de694cb8b3...5e88f5097f60b24330d4397afcb5aa5d996fbb0a
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/20201031/549525aa/attachment-0001.html>


More information about the ghc-commits mailing list