[Git][ghc/ghc][wip/az/exactprint] 83 commits: .gitignore *.hiedb files
Alan Zimmerman
gitlab at gitlab.haskell.org
Thu Sep 24 21:15:01 UTC 2020
Alan Zimmerman pushed to branch wip/az/exactprint at Glasgow Haskell Compiler / GHC
Commits:
6abe4a1c by Sebastian Graf at 2020-09-10T17:02:00+02:00
.gitignore *.hiedb files
- - - - -
3777be14 by Sebastian Graf at 2020-09-10T17:03:12+02:00
PmCheck: Handle ⊥ and strict fields correctly (#18341)
In #18341, we discovered an incorrect digression from Lower Your Guards.
This MR changes what's necessary to support properly fixing #18341.
In particular, bottomness constraints are now properly tracked in the
oracle/inhabitation testing, as an additional field
`vi_bot :: Maybe Bool` in `VarInfo`. That in turn allows us to
model newtypes as advertised in the Appendix of LYG and fix #17725.
Proper handling of ⊥ also fixes #17977 (once again) and fixes #18670.
For some reason I couldn't follow, this also fixes #18273.
I also added a couple of regression tests that were missing. Most of
them were already fixed before.
In summary, this patch fixes #18341, #17725, #18273, #17977 and #18670.
Metric Decrease:
T12227
- - - - -
1bd28931 by David Himmelstrup at 2020-09-11T09:59:43-04:00
Define TICKY_TICKY when compiling cmm RTS files.
- - - - -
15e67801 by David Himmelstrup at 2020-09-11T09:59:43-04:00
Fix typos in TICKY_TICKY symbol names.
- - - - -
8a5a91cb by David Himmelstrup at 2020-09-11T09:59:43-04:00
Enable TICKY_TICKY for debug builds when building with makefiles.
- - - - -
fc965c09 by Sandy Maguire at 2020-09-12T00:31:36-04:00
Add clamp function to Data.Ord
- - - - -
fb6e29e8 by Sandy Maguire at 2020-09-12T00:31:37-04:00
Add tests
- - - - -
2a942285 by Sebastian Graf at 2020-09-12T00:32:13-04:00
PmCheck: Disattach COMPLETE pragma lookup from TyCons
By not attaching COMPLETE pragmas with a particular TyCon and instead
assume that every COMPLETE pragma is applicable everywhere, we can
drastically simplify the logic that tries to initialise available
COMPLETE sets of a variable during the pattern-match checking process,
as well as fixing a few bugs.
Of course, we have to make sure not to report any of the
ill-typed/unrelated COMPLETE sets, which came up in a few regression
tests.
In doing so, we fix #17207, #18277 and #14422.
There was a metric decrease in #18478 by ~20%.
Metric Decrease:
T18478
- - - - -
389a6683 by Ben Gamari at 2020-09-12T00:32:49-04:00
hadrian: Pass input file to makeindex
Strangely I find that on Alpine (and apparently only on Alpine) the
latex makeindex command expects to be given a filename, lest it reads
from stdin.
- - - - -
853d121a by Ryan Scott at 2020-09-12T00:33:25-04:00
Don't quote argument to Hadrian's test-env flag (#18656)
Doing so causes the name of the test environment to gain an extra
set of double quotes, which changes the name entirely.
Fixes #18656.
- - - - -
8440b5fa by Krzysztof Gogolewski at 2020-09-12T00:33:25-04:00
Make sure we can read past perf notes
See #18656.
- - - - -
2157be52 by theobat at 2020-09-12T21:27:04-04:00
Avoid iterating twice in `zipTyEnv` (#18535)
zipToUFM is a new function to replace `listToUFM (zipEqual ks vs)`.
An explicit recursion is preferred due to the sensible nature of fusion.
T12227 -6.0%
T12545 -12.3%
T5030 -9.0%
T9872a -1.6%
T9872b -1.6%
T9872c -2.0%
-------------------------
Metric Decrease:
T12227
T12545
T5030
T9872a
T9872b
T9872c
-------------------------
- - - - -
69ea2fee by Sebastian Graf at 2020-09-12T21:27:40-04:00
Make `tcCheckSatisfiability` incremental (#18645)
By taking and returning an `InertSet`.
Every new `TcS` session can then pick up where a prior session left with
`setTcSInerts`.
Since we don't want to unflatten the Givens (and because it leads to
infinite loops, see !3971), we introduced a new variant of `runTcS`,
`runTcSInerts`, that takes and returns the `InertSet` and makes
sure not to unflatten the Givens after running the `TcS` action.
Fixes #18645 and #17836.
Metric Decrease:
T17977
T18478
- - - - -
a77e48d2 by Sebastian Graf at 2020-09-12T21:27:40-04:00
Extract definition of DsM into GHC.HsToCore.Types
`DsM` was previously defined in `GHC.Tc.Types`, along with `TcM`. But
`GHC.Tc.Types` is in the set of transitive dependencies of `GHC.Parser`,
a set which we aim to minimise. Test case `CountParserDeps` checks for
that.
Having `DsM` in that set means the parser also depends on the innards of
the pattern-match checker in `GHC.HsToCore.PmCheck.Types`, which is the
reason we have that module in the first place.
In the previous commit, we represented the `TyState` by an `InertSet`,
but that pulls the constraint solver as well as 250 more modules into
the set of dependencies, triggering failure of `CountParserDeps`.
Clearly, we want to evolve the pattern-match checker (and the desugarer)
without being concerned by this test, so this patch includes a small
refactor that puts `DsM` into its own module.
- - - - -
fd5d622a by Sebastian Graf at 2020-09-12T21:27:40-04:00
Hackily decouple the parser from the desugarer
In a hopefully temporary hack, I re-used the idea from !1957 of using a
nullary type family to break the dependency from GHC.Driver.Hooks on the
definition of DsM ("Abstract Data").
This in turn broke the last dependency from the parser to the desugarer.
More details in `Note [The Decoupling Abstract Data Hack]`.
In the future, we hope to undo this hack again in favour of breaking the
dependency from the parser to DynFlags altogether.
- - - - -
35a7b7ec by Adam Sandberg Eriksson at 2020-09-14T17:46:16-04:00
docs: -B rts option sounds the bell on every GC (#18351)
- - - - -
5ae8212c by Wander Hillen at 2020-09-14T17:46:54-04:00
Populate gitlab cache after building
- - - - -
a5ffb39a by Wander Hillen at 2020-09-14T17:46:54-04:00
Move ahead cabal cache restoration to before use of cabal
- - - - -
e8b37c21 by Wander Hillen at 2020-09-14T17:46:54-04:00
Do the hadrian rebuild multicore
- - - - -
07762eb5 by Wander Hillen at 2020-09-14T17:46:54-04:00
Also cache other hadrian builds
- - - - -
8610bcbe by DenisFrezzato at 2020-09-15T15:19:08-04:00
Fix rtsopts documentation
- - - - -
c7182a5c by Simon Peyton Jones at 2020-09-15T15:19:44-04:00
Care with implicit-parameter superclasses
Two bugs, #18627 and #18649, had the same cause: we were not
account for the fact that a constaint tuple might hide an implicit
parameter.
The solution is not hard: look for implicit parameters in
superclasses. See Note [Local implicit parameters] in
GHC.Core.Predicate.
Then we use this new function in two places
* The "short-cut solver" in GHC.Tc.Solver.Interact.shortCutSolver
which simply didn't handle implicit parameters properly at all.
This fixes #18627
* The specialiser, which should not specialise on implicit parameters
This fixes #18649
There are some lingering worries (see Note [Local implicit
parameters]) but things are much better.
- - - - -
0f3884b0 by Zubin Duggal at 2020-09-15T15:20:23-04:00
Export enrichHie from GHC.Iface.Ext.Ast
This is useful for `ghcide`
- - - - -
b3143f5a by Sylvain Henry at 2020-09-15T15:21:06-04:00
Enhance metrics output
- - - - -
4283feaa by Ryan Scott at 2020-09-15T15:21:43-04:00
Introduce and use DerivClauseTys (#18662)
This switches `deriv_clause_tys` so that instead of using a list of
`LHsSigType`s to represent the types in a `deriving` clause, it now
uses a sum type. `DctSingle` represents a `deriving` clause with no
enclosing parentheses, while `DctMulti` represents a clause with
enclosing parentheses. This makes pretty-printing easier and avoids
confusion between `HsParTy` and the enclosing parentheses in
`deriving` clauses, which are different semantically.
Fixes #18662.
- - - - -
90229c4b by Ryan Scott at 2020-09-16T04:53:22-04:00
Include -f{write,validate}-ide-info in the User's Guide flag reference
Previously, these were omitted from the flag reference due to a
layout oversight in `docs/users_guide/flags.{rst,py}`.
Fixes #18426.
- - - - -
ce42e187 by Ben Gamari at 2020-09-16T04:53:59-04:00
rts: Fix erroneous usage of vsnprintf
As pointed out in #18685, this should be snprintf not vsnprintf. This
appears to be due to a cut-and-paste error.
Fixes #18658.
- - - - -
b695e7d7 by Sylvain Henry at 2020-09-16T04:54:38-04:00
Rename ghci flag into internal-interpreter
"ghci" as a flag name was confusing because it really enables the
internal-interpreter. Even the ghci library had a "ghci" flag...
- - - - -
8af954d2 by Sylvain Henry at 2020-09-16T04:55:17-04:00
Make ghc-boot reexport modules from ghc-boot-th
Packages don't have to import both ghc-boot and ghc-boot-th. It makes
the dependency graph easier to understand and to refactor.
- - - - -
6baa67f5 by Adam Sandberg Eriksson at 2020-09-16T07:45:47-04:00
docs: correct haddock reference
[skip ci]
- - - - -
7cf09ab0 by Simon Peyton Jones at 2020-09-17T01:27:25-04:00
Do absence analysis on stable unfoldings
Ticket #18638 showed that Very Bad Things happen if we fail
to do absence analysis on stable unfoldings. It's all described
in Note [Absence analysis for stable unfoldings and RULES].
I'm a bit surprised this hasn't bitten us before. Fortunately
the fix is pretty simple.
- - - - -
76d3bcbc by Leif Metcalf at 2020-09-17T01:28:01-04:00
Replace deprecated git --recursive
The --recursive flag of git-clone has been replaced by the
--recurse-submodules flag since git 1.7.4, released in 2011.
- - - - -
da8f4ddd by Richard Eisenberg at 2020-09-17T01:28:38-04:00
Document IfaceTupleTy
- - - - -
3c94c816 by HaskellMouse at 2020-09-17T08:49:51-04:00
Added explicit fixity to (~).
Solves #18252
- - - - -
b612e396 by Cary Robbins at 2020-09-17T08:50:30-04:00
Make the 'IsString (Const a b)' instance polykinded on 'b'
- - - - -
8d0c26c4 by Ben Gamari at 2020-09-17T08:51:08-04:00
rts/win32: Fix missing #include's
These slipped through CI.
- - - - -
76009ec8 by Ben Gamari at 2020-09-17T08:51:08-04:00
Bump Win32 submodule to 2.9.0.0
Also bumps Cabal, directory
- - - - -
147bb598 by Ben Gamari at 2020-09-17T08:51:08-04:00
Bump version to 9.0
Bumps haskeline and haddock submodules.
(cherry picked from commit f218cfc92f7b1a1e01190851972bb9a0e0f3c682)
- - - - -
5c7387f6 by Leif Metcalf at 2020-09-17T08:51:43-04:00
Make Z-encoding comment into a note
- - - - -
c12b3041 by Leif Metcalf at 2020-09-17T08:51:43-04:00
Cosmetic
- - - - -
4f461e1a by Vladislav Zavialov at 2020-09-17T08:52:19-04:00
Parser.y: clarify treatment of @{-# UNPACK #-}
Before this patch, we had this parser production:
ftype : ...
| ftype PREFIX_AT tyarg { ... }
And 'tyarg' is defined as follows:
tyarg : atype { ... }
| unpackedness atype { ... }
So one might get the (false) impression that that parser production is
intended to parse things like:
F @{-# UNPACK #-} X
However, the lexer wouldn't produce PREFIX_AT followed by 'unpackedness',
as the '@' operator followed by '{-' is not considered prefix.
Thus there's no point using 'tyarg' after PREFIX_AT,
and a simple 'atype' will suffice:
ftype : ...
| ftype PREFIX_AT atype { ... }
This change has no user-facing consequences. It just makes the grammar a
bit more clear.
- - - - -
9dec8600 by Benjamin Maurer at 2020-09-17T08:52:56-04:00
Documented '-m' flags for machine specific instruction extensions.
See #18641 'Documenting the Expected Undocumented Flags'
- - - - -
ca48076a by Sylvain Henry at 2020-09-17T20:04:08-04:00
Introduce OutputableP
Some types need a Platform value to be pretty-printed: CLabel, Cmm
types, instructions, etc.
Before this patch they had an Outputable instance and the Platform value
was obtained via sdocWithDynFlags. It meant that the *renderer* of the
SDoc was responsible of passing the appropriate Platform value (e.g. via
the DynFlags given to showSDoc). It put the burden of passing the
Platform value on the renderer while the generator of the SDoc knows the
Platform it is generating the SDoc for and there is no point passing a
different Platform at rendering time.
With this patch, we introduce a new OutputableP class:
class OutputableP a where
pdoc :: Platform -> a -> SDoc
With this class we still have some polymorphism as we have with `ppr`
(i.e. we can use `pdoc` on a variety of types instead of having a
dedicated `pprXXX` function for each XXX type).
One step closer removing `sdocWithDynFlags` (#10143) and supporting
several platforms (#14335).
- - - - -
e45c8544 by Sylvain Henry at 2020-09-17T20:04:08-04:00
Generalize OutputableP
Add a type parameter for the environment required by OutputableP. It
avoids tying Platform with OutputableP.
- - - - -
37aa224a by Sylvain Henry at 2020-09-17T20:04:08-04:00
Add note about OutputableP
- - - - -
7f2785f2 by Sylvain Henry at 2020-09-17T20:04:08-04:00
Remove pprPrec from Outputable (unused)
- - - - -
b689f3db by Sylvain Henry at 2020-09-17T20:04:46-04:00
Bignum: add clamping naturalToWord (fix #18697)
- - - - -
0799b3de by Ben Gamari at 2020-09-18T15:55:50-04:00
rts/nonmoving: Add missing STM write barrier
When updating a TRec for a TVar already part of a transaction we
previously neglected to add the old value to the update remembered set.
I suspect this was the cause of #18587.
- - - - -
c4921349 by Ben Gamari at 2020-09-18T15:56:25-04:00
rts: Refactor foreign export tracking
This avoids calling `libc` in the initializers which are responsible for
registering foreign exports. We believe this should avoid the corruption
observed in #18548.
See Note [Tracking foreign exports] in rts/ForeignExports.c for an
overview of the new scheme.
- - - - -
40dc9106 by Ben Gamari at 2020-09-18T15:56:25-04:00
rts: Refactor unloading of foreign export StablePtrs
Previously we would allocate a linked list cell for each foreign export.
Now we can avoid this by taking advantage of the fact that they are
already broken into groups.
- - - - -
45fa8218 by Simon Jakobi at 2020-09-19T06:57:36-04:00
Deprecate Data.Semigroup.Option
Libraries email: https://mail.haskell.org/pipermail/libraries/2018-April/028724.html
GHC issue: https://gitlab.haskell.org/ghc/ghc/issues/15028
Corresponding PRs for deepseq:
* https://github.com/haskell/deepseq/pull/55
* https://github.com/haskell/deepseq/pull/57
Bumps the deepseq submodule.
- - - - -
2229d570 by Vladislav Zavialov at 2020-09-19T15:47:24-04:00
Require happy >=1.20
- - - - -
a89c2fba by Ben Gamari at 2020-09-19T15:47:24-04:00
ci.sh: Enforce minimum happy/alex versions
Also, always invoke cabal-install to ensure that happy/alex symlinks are
up-to-date.
- - - - -
2f7ef2fb by Ben Gamari at 2020-09-19T15:47:24-04:00
gitlab-ci: Ensure that cabal-install overwrites existing executables
Previously cabal-install wouldn't overwrite toolchain executables if
they already existed (as they likely would due to caching).
- - - - -
ac213d26 by Ryan Scott at 2020-09-19T15:48:01-04:00
Wire in constraint tuples
This wires in the definitions of the constraint tuple classes. The
key changes are in:
* `GHC.Builtin.Types`, where the `mk_ctuple` function is used to
define constraint tuple type constructors, data constructors, and
superclass selector functions, and
* `GHC.Builtin.Uniques`. In addition to wiring in the `Unique`s for
constraint tuple type and data constructors, we now must wire in
the superclass selector functions. Luckily, this proves to be not
that challenging. See the newly added comments.
Historical note: constraint tuples used to be wired-in until about
five years ago, when commit 130e93aab220bdf14d08028771f83df210da340b
turned them into known-key names. This was done as part of a larger
refactor to reduce the number of special cases for constraint tuples,
but the commit message notes that the main reason that constraint
tuples were made known-key (as opposed to boxed/unboxed tuples, which
are wired in) is because it was awkward to wire in the superclass
selectors. This commit solves the problem of wiring in superclass
selectors.
Fixes #18635.
-------------------------
Metric Decrease:
T10421
T12150
T12227
T12234
T12425
T13056
T13253-spj
T18282
T18304
T5321FD
T5321Fun
T5837
T9961
Metric Decrease (test_env='x86_64-linux-deb9-unreg-hadrian'):
T12707
Metric Decrease (test_env='x86_64-darwin'):
T4029
-------------------------
- - - - -
e195dae6 by Wander Hillen at 2020-09-19T15:48:41-04:00
Export singleton function from Data.List
Data.OldList exports a monomorphized singleton function but
it is not re-exported by Data.List. Adding the export to
Data.List causes a conflict with a 14-year old function of the
same name and type by SPJ in GHC.Utils.Misc. We can't just remove
this function because that leads to a problems when building
GHC with a stage0 compiler that does not have singleton in
Data.List yet. We also can't hide the function in GHC.Utils.Misc
since it is not possible to hide a function from a module if the
module does not export the function. To work around this, all
places where the Utils.Misc singleton was used now use a qualified
version like Utils.singleton and in GHC.Utils.Misc we are very
specific about which version we export.
- - - - -
9c1b8ad9 by Sylvain Henry at 2020-09-19T15:49:19-04:00
Bump Stack resolver
- - - - -
d05d13ce by John Ericson at 2020-09-19T15:49:57-04:00
Cinch -fno-warn-name-shadowing down to specific GHCi module
- - - - -
f1accd00 by Sylvain Henry at 2020-09-19T15:49:57-04:00
Add quick-validate Hadrian flavour (quick + -Werror)
- - - - -
8f8d51f1 by Andreas Klebinger at 2020-09-19T15:50:33-04:00
Fix docs who misstated how the RTS treats size suffixes.
They are parsed as multiples of 1024. Not 1000. The docs
used to imply otherwise.
See decodeSize in rts/RtsFlags.c for the logic for this.
- - - - -
2ae0edbd by Andreas Klebinger at 2020-09-19T15:50:33-04:00
Fix a codeblock in ghci.rst
- - - - -
4df3aa95 by Ben Gamari at 2020-09-19T15:51:07-04:00
users guide: Fix various documentation issues
- - - - -
885ecd18 by Ben Gamari at 2020-09-19T15:51:07-04:00
hadrian: Fail on Sphinx syntax errors
Specifically the "Inline literal start-string without end-string"
warning, which typically means that the user neglected to separate
an inline code block from suffix text with a backslash.
- - - - -
b26cd867 by David Feuer at 2020-09-19T15:51:44-04:00
Unpack the MVar in Compact
The `MVar` lock in `Compact` was unnecessarily lazy, creating an extra indirection and wasting two words. Make it strict.
- - - - -
760307cf by Artyom Kuznetsov at 2020-09-19T15:52:21-04:00
Remove GADT self-reference check (#11554, #12081, #12174, fixes #15942)
Reverts 430f5c84dac1eab550110d543831a70516b5cac8
- - - - -
057db94c by Ben Gamari at 2020-09-19T15:52:56-04:00
rts: Drop field initializer on thread_basic_info_data_t
This struct has a number of fields and we only care that the value is
initialized with zeros. This eliminates the warnings noted in #17905.
- - - - -
87e2e2b1 by Vladislav Zavialov at 2020-09-19T23:55:30+03:00
Resolve shift/reduce conflicts with %shift (#17232)
- - - - -
66cba46e by Ben Gamari at 2020-09-20T20:30:57-04:00
testsuite: Unmark T12971 as broken on Windows
It's unclear why, but this no longer seems to fail.
Closes #17945.
- - - - -
816811d4 by Ben Gamari at 2020-09-20T20:30:57-04:00
testsuite: Unmark T5975[ab] as broken on Windows
Sadly it's unclear *why* they have suddenly started working.
Closes #7305.
- - - - -
43a43d39 by Ben Gamari at 2020-09-20T20:30:57-04:00
base/testsuite: Add missing LANGUAGE pragma in ThreadDelay001
Only affected the Windows codepath.
- - - - -
ced8f113 by Ben Gamari at 2020-09-20T20:30:57-04:00
testsuite: Update expected output for outofmem on Windows
The error originates from osCommitMemory rather than getMBlocks.
- - - - -
ea08aead by Ben Gamari at 2020-09-20T20:30:57-04:00
testsuite: Mark some GHCi/Makefile tests as broken on Windows
See #18718.
- - - - -
caf6a5a3 by GHC GitLab CI at 2020-09-20T20:30:57-04:00
testsuite: Fix WinIO error message normalization
This wasn't being applied to stderr.
- - - - -
93ab3e8d by GHC GitLab CI at 2020-09-20T20:30:57-04:00
testsuite: Mark tempfiles as broken on Win32 without WinIO
The old POSIX emulation appears to ignore the user-requested prefix.
- - - - -
9df77fed by GHC GitLab CI at 2020-09-20T20:30:57-04:00
testsuite: Mark TH_spliceE5_prof as broken on Windows
Due to #18721.
- - - - -
1a0f8243 by Ryan Scott at 2020-09-21T16:45:47-04:00
Remove unused ThBrackCtxt and ResSigCtxt
Fixes #18715.
- - - - -
2f222b12 by Ryan Scott at 2020-09-21T16:45:47-04:00
Disallow constraints in KindSigCtxt
This patch cleans up how `GHC.Tc.Validity` classifies `UserTypeCtxt`s
that can only refer to kind-level positions, which is important for
rejecting certain classes of programs. In particular, this patch:
* Introduces a new `TypeOrKindCtxt` data type and
`typeOrKindCtxt :: UserTypeCtxt -> TypeOrKindCtxt` function, which
determines whether a `UserTypeCtxt` can refer to type-level
contexts, kind-level contexts, or both.
* Defines the existing `allConstraintsAllowed` and `vdqAllowed`
functions in terms of `typeOrKindCtxt`, which avoids code
duplication and ensures that they stay in sync in the future.
The net effect of this patch is that it fixes #18714, in which it was
discovered that `allConstraintsAllowed` incorrectly returned `True`
for `KindSigCtxt`. Because `typeOrKindCtxt` now correctly classifies
`KindSigCtxt` as a kind-level context, this bug no longer occurs.
- - - - -
aaa51dcf by Ben Gamari at 2020-09-21T16:46:22-04:00
hadrian: Add extra-deps: happy-1.20 to stack.yaml
GHC now requires happy-1.20, which isn't available in LTS-16.14.
Fixes #18726.
- - - - -
6de40f83 by Simon Peyton Jones at 2020-09-22T05:37:24-04:00
Better eta-expansion (again) and don't specilise DFuns
This patch fixes #18223, which made GHC generate an exponential
amount of code. There are three quite separate changes in here
1. Re-engineer eta-expansion (again). The eta-expander was
generating lots of intermediate stuff, which could be optimised
away, but which choked the simplifier meanwhile. Relatively
easy to kill it off at source.
See Note [The EtaInfo mechanism] in GHC.Core.Opt.Arity.
The main new thing is the use of pushCoArg in getArg_maybe.
2. Stop Specialise specalising DFuns. This is the cause of a huge
(and utterly unnecessary) blowup in program size in #18223.
See Note [Do not specialise DFuns] in GHC.Core.Opt.Specialise.
I also refactored the Specialise monad a bit... it was silly,
because it passed on unchanging values as if they were mutable
state.
3. Do an extra Simplifer run, after SpecConstra and before
late-Specialise. I found (investigating perf/compiler/T16473)
that failing to do this was crippling *both* SpecConstr *and*
Specialise. See Note [Simplify after SpecConstr] in
GHC.Core.Opt.Pipeline.
This change does mean an extra run of the Simplifier, but only
with -O2, and I think that's acceptable.
T16473 allocates *three* times less with this change. (I changed
it to check runtime rather than compile time.)
Some smaller consequences
* I moved pushCoercion, pushCoArg and friends from SimpleOpt
to Arity, because it was needed by the new etaInfoApp.
And pushCoValArg now returns a MCoercion rather than Coercion for
the argument Coercion.
* A minor, incidental improvement to Core pretty-printing
This does fix #18223, (which was otherwise uncompilable. Hooray. But
there is still a big intermediate because there are some very deeply
nested types in that program.
Modest reductions in compile-time allocation on a couple of benchmarks
T12425 -2.0%
T13253 -10.3%
Metric increase with -O2, due to extra simplifier run
T9233 +5.8%
T12227 +1.8%
T15630 +5.0%
There is a spurious apparent increase on heap residency on T9630,
on some architectures at least. I tried it with -G1 and the residency
is essentially unchanged.
Metric Increase
T9233
T12227
T9630
Metric Decrease
T12425
T13253
- - - - -
416bd50e by Simon Peyton Jones at 2020-09-22T05:37:59-04:00
Fix the occurrence analyser
Ticket #18603 demonstrated that the occurrence analyser's
handling of
local RULES for imported Ids
(which I now call IMP-RULES) was inadequate. It led the simplifier
into an infnite loop by failing to label a binder as a loop breaker.
The main change in this commit is to treat IMP-RULES in a simple and
uniform way: as extra rules for the local binder. See
Note [IMP-RULES: local rules for imported functions]
This led to quite a bit of refactoring. The result is still tricky,
but it's much better than before, and better documented I think.
Oh, and it fixes the bug.
- - - - -
6fe8a0c7 by Sebastian Graf at 2020-09-22T05:38:35-04:00
PmCheck - Comments only: Replace /~ by ≁
- - - - -
e9501547 by Sebastian Graf at 2020-09-22T05:38:35-04:00
PmCheck: Rewrite inhabitation test
We used to produce inhabitants of a pattern-match refinement type Nabla
in the checker in at least two different and mostly redundant ways:
1. There was `provideEvidence` (now called
`generateInhabitingPatterns`) which is used by
`GHC.HsToCore.PmCheck` to produce non-exhaustive patterns, which
produces inhabitants of a Nabla as a sub-refinement type where all
match variables are instantiated.
2. There also was `ensure{,All}Inhabited` (now called
`inhabitationTest`) which worked slightly different, but was
whenever new type constraints or negative term constraints were
added. See below why `provideEvidence` and `ensureAllInhabited`
can't be the same function, the main reason being performance.
3. And last but not least there was the `nonVoid` test, which tested
that a given type was inhabited. We did use this for strict fields
and -XEmptyCase in the past.
The overlap of (3) with (2) was always a major pet peeve of mine. The
latter was quite efficient and proven to work for recursive data types,
etc, but could not handle negative constraints well (e.g. we often want
to know if a *refined* type is empty, such as `{ x:[a] | x /= [] }`).
Lower Your Guards suggested that we could get by with just one, by
replacing both functions with `inhabitationTest` in this patch.
That was only possible by implementing the structure of φ constraints
as in the paper, namely the semantics of φ constructor constraints.
This has a number of benefits:
a. Proper handling of unlifted types and strict fields, fixing #18249,
without any code duplication between
`GHC.HsToCore.PmCheck.Oracle.instCon` (was `mkOneConFull`) and
`GHC.HsToCore.PmCheck.checkGrd`.
b. `instCon` can perform the `nonVoid` test (3) simply by emitting
unliftedness constraints for strict fields.
c. `nonVoid` (3) is thus simply expressed by a call to
`inhabitationTest`.
d. Similarly, `ensureAllInhabited` (2), which we called after adding
type info, now can similarly be expressed as the fuel-based
`inhabitationTest`.
See the new `Note [Why inhabitationTest doesn't call generateInhabitingPatterns]`
why we still have tests (1) and (2).
Fixes #18249 and brings nice metric decreases for `T17836` (-76%) and
`T17836b` (-46%), as well as `T18478` (-8%) at the cost of a few very
minor regressions (< +2%), potentially due to the fact that
`generateInhabitingPatterns` does more work to suggest the minimal
COMPLETE set.
Metric Decrease:
T17836
T17836b
- - - - -
d061d49e by Alan Zimmerman at 2020-09-24T22:14:24+01:00
Proof of Concept implementation of in-tree API Annotations
This MR introduces a possible machinery to introduce API Annotations
into the TTG extension points.
It is intended to be a concrete example for discussion.
It still needs to process comments.
----
Work in progress, adding more TTG extensions for annotations.
And fixing ppr round-trip tests by being able to blank out in-tree
annotations, as done with SrcSpans.
This is needed for the case of
class Foo a where
for which current ppr does not print the "where".
Rename AA to AddApiAnn and AA to AddAnn
Add XConPatIn and XConPatOut
Rebase
----
First pass at bringing in LocatedA for API anns in locations
Treatment of ECP in parsing is provisional at this stage, leads to some
horribly stuff in Parser.y and RdrHsSyn.
It is an extensive but not invasive change. I think (AZ).
Locally it reports some parsing tests using less memory.
Add ApiAnns to the HsExpr data structure.
rebase.
Change HsMatchContext and HsStmtContext to use an id, not a GhcPass
parameter.
Add ApiAnns to Hs/Types
Rebase
Rebased 2020-03-25
WIP on in-tree annotations
Includes updating HsModule
Imports
LocateA ImportDecl so we can hang AnnSemi off it
A whole bunch of stuff more
InjectivityAnn and FamEqn now have annotations in them
Add annotations to context srcspan
----
In-tree annotations: LHsDecl and LHsBind LocatedA
----
WIP on in-tree annotations
----
in-tree annotations: LHsType is now LocatedA
----
FunDeps is now also a HS data type
----
WIP. Added LocatedA to Pat, Expr, Decl
And worked some more through Parser.y
----
LStmt now Located
----
Finished working through Parser.y, tests seem ok
failures relate to annotations.
Adding test infrastructure for check-exact
Like check-ppr, but checking for an exact reproduction of the parsed
source file.
Starting to work on actual exact printer
Bring in ApiAnnName
As an alternative for LocatedA, to be used for names only.
Carrying extra name adornments, such as locations of backticks,
parens, etc.
Working on changing ApiAnnName to accurately reflect actual usage
Get rid of AnnApiName in favour of LocatedN
Working on check-exact. Making progress
Working on the ghc-exact bit
Progress, can reproduce the first Test.hs file.
Move API Annotations out of the extensions to annotations
Remove LHsLocalBinds
Fix up after rebasing to bring in XRec
Main thing is to make
type instance XRec (GhcPass p) a = GenLocated (Anno a) a
type family Anno a = b
But this has massive implications.
- - - - -
30 changed files:
- .gitignore
- .gitlab-ci.yml
- .gitlab/ci.sh
- .gitmodules
- README.md
- aclocal.m4
- compiler/GHC.hs
- compiler/GHC/Builtin/Types.hs
- compiler/GHC/Builtin/Types.hs-boot
- compiler/GHC/Builtin/Uniques.hs
- compiler/GHC/Builtin/Utils.hs
- compiler/GHC/Cmm.hs
- compiler/GHC/Cmm/CLabel.hs
- compiler/GHC/Cmm/Dataflow/Label.hs
- compiler/GHC/Cmm/DebugBlock.hs
- compiler/GHC/Cmm/Info/Build.hs
- compiler/GHC/Cmm/LayoutStack.hs
- compiler/GHC/Cmm/Lint.hs
- compiler/GHC/Cmm/Parser.y
- compiler/GHC/Cmm/Pipeline.hs
- compiler/GHC/Cmm/Ppr.hs
- compiler/GHC/Cmm/Ppr/Decl.hs
- compiler/GHC/Cmm/Ppr/Expr.hs
- compiler/GHC/Cmm/ProcPoint.hs
- compiler/GHC/CmmToAsm.hs
- compiler/GHC/CmmToAsm/CFG.hs
- compiler/GHC/CmmToAsm/Dwarf.hs
- compiler/GHC/CmmToAsm/Dwarf/Types.hs
- compiler/GHC/CmmToAsm/PPC/Ppr.hs
- compiler/GHC/CmmToAsm/Ppr.hs
The diff was not included because it is too large.
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/e6ea932fa8e64fdce493ed74886b4e276d723e16...d061d49e15a42f5562eeceb8393fc766aa459a53
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/e6ea932fa8e64fdce493ed74886b4e276d723e16...d061d49e15a42f5562eeceb8393fc766aa459a53
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/20200924/d6e8c952/attachment-0001.html>
More information about the ghc-commits
mailing list