[Git][ghc/ghc][wip/T18126] 92 commits: DynFlags: remove use of sdocWithDynFlags from GHC.Stg.* (#17957)
Simon Peyton Jones
gitlab at gitlab.haskell.org
Mon Aug 3 09:20:03 UTC 2020
Simon Peyton Jones pushed to branch wip/T18126 at Glasgow Haskell Compiler / GHC
Commits:
30caeee7 by Sylvain Henry at 2020-07-21T06:39:33-04:00
DynFlags: remove use of sdocWithDynFlags from GHC.Stg.* (#17957)
* add StgPprOpts datatype
* remove Outputable instances for types that need `StgPprOpts` to be
pretty-printed and explicitly call type specific ppr functions
* add default `panicStgPprOpts` for panic messages (when it's not
convenient to thread StgPprOpts or DynFlags down to the ppr function
call)
- - - - -
863c544c by Mark at 2020-07-21T06:39:34-04:00
Fix a typo in existential_quantification.rst
- - - - -
05910be1 by Krzysztof Gogolewski at 2020-07-21T14:47:07-04:00
Add release notes entry for #17816
[skip ci]
- - - - -
a6257192 by Matthew Pickering at 2020-07-21T14:47:19-04:00
Use a newtype `Code` for the return type of typed quotations (Proposal #195)
There are three problems with the current API:
1. It is hard to properly write instances for ``Quote m => m (TExp a)`` as the type is the composition
of two type constructors. Doing so in your program involves making your own newtype and
doing a lot of wrapping/unwrapping.
For example, if I want to create a language which I can either run immediately or
generate code from I could write the following with the new API. ::
class Lang r where
_int :: Int -> r Int
_if :: r Bool -> r a -> r a -> r a
instance Lang Identity where
_int = Identity
_if (Identity b) (Identity t) (Identity f) = Identity (if b then t else f)
instance Quote m => Lang (Code m) where
_int = liftTyped
_if cb ct cf = [|| if $$cb then $$ct else $$cf ||]
2. When doing code generation it is common to want to store code fragments in
a map. When doing typed code generation, these code fragments contain a
type index so it is desirable to store them in one of the parameterised
map data types such as ``DMap`` from ``dependent-map`` or ``MapF`` from
``parameterized-utils``.
::
compiler :: Env -> AST a -> Code Q a
data AST a where ...
data Ident a = ...
type Env = MapF Ident (Code Q)
newtype Code m a = Code (m (TExp a))
In this example, the ``MapF`` maps an ``Ident String`` directly to a ``Code Q String``.
Using one of these map types currently requires creating your own newtype and constantly
wrapping every quotation and unwrapping it when using a splice. Achievable, but
it creates even more syntactic noise than normal metaprogramming.
3. ``m (TExp a)`` is ugly to read and write, understanding ``Code m a`` is
easier. This is a weak reason but one everyone
can surely agree with.
Updates text submodule.
- - - - -
58235d46 by Ben Gamari at 2020-07-21T14:47:28-04:00
users-guide: Fix :rts-flag:`--copying-gc` documentation
It was missing a newline.
- - - - -
19e80b9a by Vladislav Zavialov at 2020-07-21T14:50:01-04:00
Accumulate Haddock comments in P (#17544, #17561, #8944)
Haddock comments are, first and foremost, comments. It's very annoying
to incorporate them into the grammar. We can take advantage of an
important property: adding a Haddock comment does not change the parse
tree in any way other than wrapping some nodes in HsDocTy and the like
(and if it does, that's a bug).
This patch implements the following:
* Accumulate Haddock comments with their locations in the P monad.
This is handled in the lexer.
* After parsing, do a pass over the AST to associate Haddock comments
with AST nodes using location info.
* Report the leftover comments to the user as a warning (-Winvalid-haddock).
- - - - -
4c719460 by David Binder at 2020-07-22T20:17:35-04:00
Fix dead link to haskell prime discussion
- - - - -
f2f817e4 by BinderDavid at 2020-07-22T20:17:35-04:00
Replace broken links to old haskell-prime site by working links to gitlab instance.
[skip ci]
- - - - -
0bf8980e by Daniel Gröber at 2020-07-22T20:18:11-04:00
Remove length field from FastString
- - - - -
1010c33b by Daniel Gröber at 2020-07-22T20:18:11-04:00
Use ShortByteString for FastString
There are multiple reasons we want this:
- Fewer allocations: ByteString has 3 fields, ShortByteString just has one.
- ByteString memory is pinned:
- This can cause fragmentation issues (see for example #13110) but also
- makes using FastStrings in compact regions impossible.
Metric Decrease:
T5837
T12150
T12234
T12425
- - - - -
8336ba78 by Daniel Gröber at 2020-07-22T20:18:11-04:00
Pass specialised utf8DecodeChar# to utf8DecodeLazy# for performance
Currently we're passing a indexWord8OffAddr# type function to
utf8DecodeLazy# which then passes it on to utf8DecodeChar#. By passing one
of utf8DecodeCharAddr# or utf8DecodeCharByteArray# instead we benefit from
the inlining and specialization already done for those.
- - - - -
7484a9a4 by Daniel Gröber at 2020-07-22T20:18:11-04:00
Encoding: Add comment about tricky ForeignPtr lifetime
- - - - -
5536ed28 by Daniel Gröber at 2020-07-22T20:18:11-04:00
Use IO constructor instead of `stToIO . ST`
- - - - -
5b8902e3 by Daniel Gröber at 2020-07-22T20:18:11-04:00
Encoding: Remove redundant use of withForeignPtr
- - - - -
5976a161 by Daniel Gröber at 2020-07-22T20:18:11-04:00
Encoding: Reformat utf8EncodeShortByteString to be more consistent
- - - - -
9ddf1614 by Daniel Gröber at 2020-07-22T20:18:11-04:00
FastString: Reintroduce character count cache
Metric Increase:
ManyConstructors
Metric Decrease:
T4029
- - - - -
e9491668 by Ben Gamari at 2020-07-22T20:18:46-04:00
get-win32-tarballs: Fix detection of missing tarballs
This fixes the error message given by configure when the user
attempts to configure without first download the win32 tarballs.
- - - - -
9f3ff8fd by Andreas Klebinger at 2020-07-22T20:19:22-04:00
Enable BangPatterns, ScopedTypeVariables for ghc and hadrian by default.
This is only for their respective codebases.
- - - - -
0f17b930 by Sylvain Henry at 2020-07-22T20:19:59-04:00
Remove unused "ncg" flag
This flag has been removed in 066b369de2c6f7da03c88206288dca29ab061b31
in 2011.
- - - - -
bab4ec8f by Sylvain Henry at 2020-07-22T20:19:59-04:00
Don't panic if the NCG isn't built (it is always built)
- - - - -
8ea33edb by Sylvain Henry at 2020-07-22T20:19:59-04:00
Remove unused sGhcWithNativeCodeGen
- - - - -
e079bb72 by Sylvain Henry at 2020-07-22T20:19:59-04:00
Correctly test active backend
Previously we used a platform settings to detect if the native code
generator was used. This was wrong. We need to use the
`DynFlags.hscTarget` field instead.
- - - - -
735f9d6b by Sylvain Henry at 2020-07-22T20:19:59-04:00
Replace ghcWithNativeCodeGen with a proper Backend datatype
* Represent backends with a `Backend` datatype in GHC.Driver.Backend
* Don't detect the default backend to use for the target platform at
compile time in Hadrian/make but at runtime. It makes "Settings"
simpler and it is a step toward making GHC multi-target.
* The latter change also fixes hadrian which has not been updated to
take into account that the NCG now supports AIX and PPC64 (cf
df26b95559fd467abc0a3a4151127c95cb5011b9 and
d3c1dda60d0ec07fc7f593bfd83ec9457dfa7984)
* Also we don't treat iOS specifically anymore (cf
cb4878ffd18a3c70f98bdbb413cd3c4d1f054e1f)
- - - - -
f7cc4313 by Sylvain Henry at 2020-07-22T20:19:59-04:00
Replace HscTarget with Backend
They both have the same role and Backend name is more explicit.
Metric Decrease:
T3064
Update Haddock submodule
- - - - -
15ce1804 by Andreas Klebinger at 2020-07-22T20:20:34-04:00
Deprecate -fdmd-tx-dict-sel.
It's behaviour is now unconditionally enabled as
it's slightly beneficial.
There are almost no benchmarks which benefit from
disabling it, so it's not worth the keep this
configurable.
This fixes #18429.
- - - - -
ff1b7710 by Sylvain Henry at 2020-07-22T20:21:11-04:00
Add test for #18064
It has been fixed by 0effc57d48ace6b719a9f4cbeac67c95ad55010b
- - - - -
cfa89149 by Krzysztof Gogolewski at 2020-07-22T20:21:48-04:00
Define type Void# = (# #) (#18441)
There's one backwards compatibility issue: GHC.Prim no longer exports
Void#, we now manually re-export it from GHC.Exts.
- - - - -
02f40b0d by Sebastian Graf at 2020-07-22T20:22:23-04:00
Add regression test for #18478
!3392 backported !2993 to GHC 8.10.2 which most probably is responsible
for fixing #18478, which triggered a pattern match checker performance
regression in GHC 8.10.1 as first observed in #17977.
- - - - -
7f44df1e by Sylvain Henry at 2020-07-22T20:23:00-04:00
Minor refactoring of Unit display
* for consistency, try to always use UnitPprInfo to display units to
users
* remove some uses of `unitPackageIdString` as it doesn't show the
component name and it uses String
- - - - -
dff1cb3d by Moritz Angermann at 2020-07-23T07:55:29-04:00
[linker] Fix out of range relocations.
mmap may return address all over the place. mmap_next will ensure we get
the next free page after the requested address.
This is especially important for linking on aarch64, where the memory model with PIC
admits relocations in the +-4GB range, and as such we can't work with
arbitrary object locations in memory.
Of note: we map the rts into process space, so any mapped objects must
not be ouside of the 4GB from the processes address space.
- - - - -
cdd0ff16 by Tamar Christina at 2020-07-24T18:12:23-04:00
winio: restore console cp on exit
- - - - -
c1f4f81d by Tamar Christina at 2020-07-24T18:13:00-04:00
winio: change memory allocation strategy and fix double free errors.
- - - - -
ba205046 by Simon Peyton Jones at 2020-07-24T18:13:35-04:00
Care with occCheckExpand in kind of occurrences
Issue #18451 showed that we could get an infinite type, through
over-use of occCheckExpand in the kind of an /occurrence/ of a
type variable.
See Note [Occurrence checking: look inside kinds] in GHC.Core.Type
This patch fixes the problem by making occCheckExpand less eager
to expand synonyms in kinds.
It also improves pretty printing of kinds, by *not* suppressing
the kind on a tyvar-binder like
(a :: Const Type b)
where type Const p q = p. Even though the kind of 'a' is Type,
we don't want to suppress the kind ascription. Example: the
error message for polykinds/T18451{a,b}. See GHC.Core.TyCo.Ppr
Note [Suppressing * kinds].
- - - - -
02133353 by Zubin Duggal at 2020-07-25T00:44:30-04:00
Simplify XRec definition
Change `Located X` usage to `XRec pass X`
This increases the scope of the LPat experiment to almost all of GHC.
Introduce UnXRec and MapXRec classes
Fixes #17587 and #18408
Updates haddock submodule
Co-authored-by: Philipp Krüger <philipp.krueger1 at gmail.com>
- - - - -
e443846b by Sylvain Henry at 2020-07-25T00:45:07-04:00
DynFlags: store printer in TraceBinIfaceReading
We don't need to pass the whole DynFlags, just pass the logging
function, if any.
- - - - -
15b2b44f by Sylvain Henry at 2020-07-25T00:45:08-04:00
Rename GHC.Driver.Ways into GHC.Platform.Ways
- - - - -
342a01af by Sylvain Henry at 2020-07-25T00:45:08-04:00
Add GHC.Platform.Profile
- - - - -
6333d739 by Sylvain Henry at 2020-07-25T00:45:08-04:00
Put PlatformConstants into Platform
- - - - -
9dfeca6c by Sylvain Henry at 2020-07-25T00:45:08-04:00
Remove platform constant wrappers
Platform constant wrappers took a DynFlags parameter, hence implicitly
used the target platform constants. We removed them to allow support
for several platforms at once (#14335) and to avoid having to pass
the full DynFlags to every function (#17957).
Metric Decrease:
T4801
- - - - -
73145d57 by Sylvain Henry at 2020-07-25T00:45:08-04:00
Remove dead code in utils/derivConstants
- - - - -
7721b923 by Sylvain Henry at 2020-07-25T00:45:08-04:00
Move GHC.Platform into the compiler
Previously it was in ghc-boot so that ghc-pkg could use it. However it
wasn't necessary because ghc-pkg only uses a subset of it: reading
target arch and OS from the settings file. This is now done via
GHC.Platform.ArchOS (was called PlatformMini before).
- - - - -
459afeb5 by Sylvain Henry at 2020-07-25T00:45:08-04:00
Fix build systems
- - - - -
9e2930c3 by Sylvain Henry at 2020-07-25T00:45:08-04:00
Bump CountParserDeps
- - - - -
6e2db34b by Sylvain Henry at 2020-07-25T00:45:08-04:00
Add accessors to ArchOS
- - - - -
fc0f6fbc by Stefan Schulze Frielinghaus at 2020-07-25T00:45:45-04:00
Require SMP support in order to build a threaded stage1
Fixes 18266
- - - - -
a7c4439a by Matthias Andreas Benkard at 2020-07-26T13:23:24-04:00
Document loadFramework changes. (#18446)
Adds commentary on the rationale for the changes made in merge request
!3689.
- - - - -
da7269a4 by Ben Gamari at 2020-07-26T13:23:59-04:00
rts/win32: Exit with EXIT_HEAPOVERFLOW if memory commit fails
Since switching to the two-step allocator, the `outofmem` test fails via
`osCommitMemory` failing to commit. However, this was previously exiting
with `EXIT_FAILURE`, rather than `EXIT_HEAPOVERFLOW`. I think the latter
is a more reasonable exit code for this case and matches the behavior on
POSIX platforms.
- - - - -
f153a1d0 by Ben Gamari at 2020-07-26T13:23:59-04:00
testsuite: Update win32 output for parseTree
- - - - -
e91672f0 by Ben Gamari at 2020-07-26T13:23:59-04:00
testsuite: Normalise WinIO error message differences
Previously the old Windows IO manager threw different errors than WinIO.
We now canonicalise these to the WinIO errors.
- - - - -
9cbfe086 by Ben Gamari at 2020-07-26T13:23:59-04:00
gitlab-ci: Kill ssh-agent after pushing test metrics
Otherwise the Windows builds hang forever waiting for the process to
terminate.
- - - - -
8236925f by Tamar Christina at 2020-07-26T13:24:35-04:00
winio: remove dead argument to stg_newIOPortzh
- - - - -
ce0a1d67 by Tamar Christina at 2020-07-26T13:25:11-04:00
winio: fix detection of tty terminals
- - - - -
52685cf7 by Tamar Christina at 2020-07-26T13:25:48-04:00
winio: update codeowners
- - - - -
aee45d9e by Vladislav Zavialov at 2020-07-27T07:06:56-04:00
Improve NegativeLiterals (#18022, GHC Proposal #344)
Before this patch, NegativeLiterals used to parse x-1 as x (-1).
This may not be what the user expects, and now it is fixed:
x-1 is parsed as (-) x 1.
We achieve this by the following requirement:
* When lexing a negative literal,
it must not be preceded by a 'closing token'.
This also applies to unboxed literals, e.g. -1#.
See GHC Proposal #229 for the definition of a closing token.
A nice consequence of this change is that -XNegativeLiterals becomes a
subset of -XLexicalNegation. In other words, enabling both of those
extensions has the same effect as enabling -XLexicalNegation alone.
- - - - -
667ab69e by leiftw at 2020-07-27T07:07:32-04:00
fix typo referring to non-existent `-ohidir` flag, should be `-hidir` I think
- - - - -
6ff89c17 by Vladislav Zavialov at 2020-07-27T07:08:07-04:00
Refactor the parser a little
* Create a dedicated production for type operators
* Create a dedicated type for the UNPACK pragma
* Remove an outdated part of Note [Parsing data constructors is hard]
- - - - -
aa054d32 by Ben Gamari at 2020-07-27T20:09:07-04:00
Drop 32-bit Windows support
As noted in #18487, we have reached the end of this road.
- - - - -
6da73bbf by Michalis Pardalos at 2020-07-27T20:09:44-04:00
Add minimal test for #12492
- - - - -
47680cb7 by Michalis Pardalos at 2020-07-27T20:09:44-04:00
Use allocate, not ALLOC_PRIM_P for unpackClosure#
ALLOC_PRIM_P fails for large closures, by directly using allocate
we can handle closures which are larger than the block size.
Fixes #12492
- - - - -
3d345c96 by Simon Peyton Jones at 2020-07-27T20:10:19-04:00
Eta-expand the Simplifier monad
This patch eta-expands the Simplifier's monad, using the method
explained in GHC.Core.Unify Note [The one-shot state monad trick].
It's part of the exta-expansion programme in #18202.
It's a tiny patch, but is worth a 1-2% reduction in bytes-allocated
by the compiler. Here's the list, based on the compiler-performance
tests in perf/compiler:
Reduction in bytes allocated
T10858(normal) -0.7%
T12425(optasm) -1.3%
T13056(optasm) -1.8%
T14683(normal) -1.1%
T15164(normal) -1.3%
T15630(normal) -1.4%
T17516(normal) -2.3%
T18282(normal) -1.6%
T18304(normal) -0.8%
T1969(normal) -0.6%
T4801(normal) -0.8%
T5321FD(normal) -0.7%
T5321Fun(normal) -0.5%
T5642(normal) -0.9%
T6048(optasm) -1.1%
T9020(optasm) -2.7%
T9233(normal) -0.7%
T9675(optasm) -0.5%
T9961(normal) -2.9%
WWRec(normal) -1.2%
Metric Decrease:
T12425
T9020
T9961
- - - - -
57aca6bb by Ben Gamari at 2020-07-27T20:10:54-04:00
gitlab-ci: Ensure that Hadrian jobs don't download artifacts
Previously the Hadrian jobs had the default dependencies, meaning that
they would download artifacts from all jobs of earlier stages. This is
unneccessary.
- - - - -
0a815cea by Ben Gamari at 2020-07-27T20:10:54-04:00
gitlab-ci: Bump bootstrap compiler to 8.8.4
Hopefully this will make the Windows jobs a bit more reliable.
- - - - -
0bd60059 by Simon Peyton Jones at 2020-07-28T02:01:49-04:00
This patch addresses the exponential blow-up in the simplifier.
Specifically:
#13253 exponential inlining
#10421 ditto
#18140 strict constructors
#18282 another nested-function call case
This patch makes one really significant changes: change the way that
mkDupableCont handles StrictArg. The details are explained in
GHC.Core.Opt.Simplify Note [Duplicating StrictArg].
Specific changes
* In mkDupableCont, when making auxiliary bindings for the other arguments
of a call, add extra plumbing so that we don't forget the demand on them.
Otherwise we haev to wait for another round of strictness analysis. But
actually all the info is to hand. This change affects:
- Make the strictness list in ArgInfo be [Demand] instead of [Bool],
and rename it to ai_dmds.
- Add as_dmd to ValArg
- Simplify.makeTrivial takes a Demand
- mkDupableContWithDmds takes a [Demand]
There are a number of other small changes
1. For Ids that are used at most once in each branch of a case, make
the occurrence analyser record the total number of syntactic
occurrences. Previously we recorded just OneBranch or
MultipleBranches.
I thought this was going to be useful, but I ended up barely
using it; see Note [Note [Suppress exponential blowup] in
GHC.Core.Opt.Simplify.Utils
Actual changes:
* See the occ_n_br field of OneOcc.
* postInlineUnconditionally
2. I found a small perf buglet in SetLevels; see the new
function GHC.Core.Opt.SetLevels.hasFreeJoin
3. Remove the sc_cci field of StrictArg. I found I could get
its information from the sc_fun field instead. Less to get
wrong!
4. In ArgInfo, arrange that ai_dmds and ai_discs have a simpler
invariant: they line up with the value arguments beyond ai_args
This allowed a bit of nice refactoring; see isStrictArgInfo,
lazyArgcontext, strictArgContext
There is virtually no difference in nofib. (The runtime numbers
are bogus -- I tried a few manually.)
Program Size Allocs Runtime Elapsed TotalMem
--------------------------------------------------------------------------------
fft +0.0% -2.0% -48.3% -49.4% 0.0%
multiplier +0.0% -2.2% -50.3% -50.9% 0.0%
--------------------------------------------------------------------------------
Min -0.4% -2.2% -59.2% -60.4% 0.0%
Max +0.0% +0.1% +3.3% +4.9% 0.0%
Geometric Mean +0.0% -0.0% -33.2% -34.3% -0.0%
Test T18282 is an existing example of these deeply-nested strict calls.
We get a big decrease in compile time (-85%) because so much less
inlining takes place.
Metric Decrease:
T18282
- - - - -
6ee07b49 by Sylvain Henry at 2020-07-28T02:02:27-04:00
Bignum: add support for negative shifts (fix #18499)
shiftR/shiftL support negative arguments despite Haskell 2010 report
saying otherwise. We explicitly test for negative values which is bad
(it gets in the way of constant folding, etc.). Anyway, for consistency
we fix Bits instancesof Integer/Natural.
- - - - -
f305bbfd by Peter Trommler at 2020-07-28T02:03:02-04:00
config: Fix Haskell platform constructor w/ params
Fixes #18505
- - - - -
318bb17c by Oleg Grenrus at 2020-07-28T20:54:13-04:00
Fix typo in haddock
Spotted by `vilpan` on `#haskell`
- - - - -
39c89862 by Sergei Trofimovich at 2020-07-28T20:54:50-04:00
ghc/mk: don't build gmp packages for BIGNUM_BACKEND=native
Before this change make-based `BIGNUM_BACKEND=native` build was failing as:
```
x86_64-pc-linux-gnu-gcc: error: libraries/ghc-bignum/gmp/objs/*.o: No such file or directory
```
This happens because ghc.mk was pulling in gmp-dependent
ghc-bignum library unconditionally. The change avoid building
ghc-bignum.
Bug: https://gitlab.haskell.org/ghc/ghc/-/issues/18437
Signed-off-by: Sergei Trofimovich <slyfox at gentoo.org>
- - - - -
b9a880fc by Felix Wiemuth at 2020-07-29T15:06:35-04:00
Fix typo
- - - - -
c59064b0 by Brandon Chinn at 2020-07-29T15:07:11-04:00
Add regression test for #16341
- - - - -
a61411ca by Brandon Chinn at 2020-07-29T15:07:11-04:00
Pass dit_rep_tc_args to dsm_stock_gen_fn
- - - - -
a26498da by Brandon Chinn at 2020-07-29T15:07:11-04:00
Pass tc_args to gen_fn
- - - - -
44b11bad by Brandon Chinn at 2020-07-29T15:07:11-04:00
Filter out unreachable constructors when deriving stock instances (#16431)
- - - - -
bbc51916 by Simon Peyton Jones at 2020-07-29T15:07:47-04:00
Kill off sc_mult and as_mult fields
They are readily derivable from other fields, so this is more
efficient, and less error prone.
Fixes #18494
- - - - -
e3db4b4c by Peter Trommler at 2020-07-29T15:08:22-04:00
configure: Fix build system on ARM
- - - - -
96c31ea1 by Sylvain Henry at 2020-07-29T15:09:02-04:00
Fix bug in Natural multiplication (fix #18509)
A bug was lingering in Natural multiplication (inverting two limbs)
despite QuickCheck tests used during the development leading to wrong
results (independently of the selected backend).
- - - - -
e1dc3d7b by Krzysztof Gogolewski at 2020-07-29T15:09:39-04:00
Fix validation errors (#18510)
Test T2632 is a stage1 test that failed because of the Q => Quote change.
The remaining tests did not use quotation and failed when the path
contained a space.
- - - - -
6c68a842 by John Ericson at 2020-07-30T07:11:02-04:00
For `-fkeep-going` do not duplicate dependency edge code
We now compute the deps for `-fkeep-going` the same way that the
original graph calculates them, so the edges are correct. Upsweep really
ought to take the graph rather than a topological sort so we are never
recalculating anything, but at least things are recaluclated
consistently now.
- - - - -
502de556 by cgibbard at 2020-07-30T07:11:02-04:00
Add haddock comment for unfilteredEdges
and move the note about drop_hs_boot_nodes into it.
- - - - -
01c948eb by Ryan Scott at 2020-07-30T07:11:37-04:00
Clean up the inferred type variable restriction
This patch primarily:
* Documents `checkInferredVars` (previously called
`check_inferred_vars`) more carefully. This is the
function which throws an error message if a user quantifies an
inferred type variable in a place where specificity cannot be
observed. See `Note [Unobservably inferred type variables]` in
`GHC.Rename.HsType`.
Note that I now invoke `checkInferredVars` _alongside_
`rnHsSigType`, `rnHsWcSigType`, etc. rather than doing so _inside_
of these functions. This results in slightly more call sites for
`checkInferredVars`, but it makes it much easier to enumerate the
spots where the inferred type variable restriction comes into
effect.
* Removes the inferred type variable restriction for default method
type signatures, per the discussion in #18432. As a result, this
patch fixes #18432.
Along the way, I performed some various cleanup:
* I moved `no_nested_foralls_contexts_err` into `GHC.Rename.Utils`
(under the new name `noNestedForallsContextsErr`), since it now
needs to be invoked from multiple modules. I also added a helper
function `addNoNestedForallsContextsErr` that throws the error
message after producing it, as this is a common idiom.
* In order to ensure that users cannot sneak inferred type variables
into `SPECIALISE instance` pragmas by way of nested `forall`s, I
now invoke `addNoNestedForallsContextsErr` when renaming
`SPECIALISE instance` pragmas, much like when we rename normal
instance declarations. (This probably should have originally been
done as a part of the fix for #18240, but this task was somehow
overlooked.) As a result, this patch fixes #18455 as a side effect.
- - - - -
d47324ce by Ryan Scott at 2020-07-30T07:12:16-04:00
Don't mark closed type family equations as occurrences
Previously, `rnFamInstEqn` would mark the name of the type/data
family used in an equation as an occurrence, regardless of what sort
of family it is. Most of the time, this is the correct thing to do.
The exception is closed type families, whose equations constitute its
definition and therefore should not be marked as occurrences.
Overzealously counting the equations of a closed type family as
occurrences can cause certain warnings to not be emitted, as observed
in #18470. See `Note [Type family equations and occurrences]` in
`GHC.Rename.Module` for the full story.
This fixes #18470 with a little bit of extra-casing in
`rnFamInstEqn`. To accomplish this, I added an extra
`ClosedTyFamInfo` field to the `NonAssocTyFamEqn` constructor of
`AssocTyFamInfo` and refactored the relevant call sites accordingly
so that this information is propagated to `rnFamInstEqn`.
While I was in town, I moved `wrongTyFamName`, which checks that the
name of a closed type family matches the name in an equation for that
family, from the renamer to the typechecker to avoid the need for an
`ASSERT`. As an added bonus, this lets us simplify the details of
`ClosedTyFamInfo` a bit.
- - - - -
ebe2cf45 by Simon Peyton Jones at 2020-07-30T07:12:52-04:00
Remove an incorrect WARN in extendLocalRdrEnv
I noticed this warning going off, and discovered that it's
really fine. This small patch removes the warning, and docments
what is going on.
- - - - -
9f71f697 by Simon Peyton Jones at 2020-07-30T07:13:27-04:00
Add two bangs to improve perf of flattening
This tiny patch improves the compile time of flatten-heavy
programs by 1-2%, by adding two bangs.
Addresses (somewhat) #18502
This reduces allocation by
T9872b -1.1%
T9872d -3.3%
T5321Fun -0.2%
T5631 -0.2%
T5837 +0.1%
T6048 +0.1%
Metric Decrease:
T9872b
T9872d
- - - - -
7c274cd5 by Sylvain Henry at 2020-07-30T22:54:48-04:00
Fix minimal imports dump for boot files (fix #18497)
- - - - -
175cb5b4 by Sylvain Henry at 2020-07-30T22:55:25-04:00
DynFlags: don't use sdocWithDynFlags in datacon ppr
We don't need to use `sdocWithDynFlags` to know whether we should
display linear types for datacon types, we already have
`sdocLinearTypes` field in `SDocContext`. Moreover we want to remove
`sdocWithDynFlags` (#10143, #17957)).
- - - - -
380638a3 by Sylvain Henry at 2020-07-30T22:56:03-04:00
Bignum: fix powMod for gmp backend (#18515)
Also reenable integerPowMod test which had never been reenabled by
mistake.
- - - - -
56a7c193 by Sylvain Henry at 2020-07-31T19:32:09+02:00
Refactor CLabel pretty-printing
Pretty-printing CLabel relies on sdocWithDynFlags that we want to remove
(#10143, #17957). It uses it to query the backend and the platform.
This patch exposes Clabel ppr functions specialised for each backend so
that backend code can directly use them.
- - - - -
3b15dc3c by Sylvain Henry at 2020-07-31T19:32:09+02:00
DynFlags: don't use sdocWithDynFlags in GHC.CmmToAsm.Dwarf.Types
- - - - -
e30fed6c by Vladislav Zavialov at 2020-08-01T04:23:04-04:00
Test case for #17652
The issue was fixed by 19e80b9af252eee760dc047765a9930ef00067ec
- - - - -
22641742 by Ryan Scott at 2020-08-02T16:44:11-04:00
Remove ConDeclGADTPrefixPs
This removes the `ConDeclGADTPrefixPs` per the discussion in #18517.
Most of this patch simply removes code, although the code in the
`rnConDecl` case for `ConDeclGADTPrefixPs` had to be moved around a
bit:
* The nested `forall`s check now lives in the `rnConDecl` case for
`ConDeclGADT`.
* The `LinearTypes`-specific code that used to live in the
`rnConDecl` case for `ConDeclGADTPrefixPs` now lives in
`GHC.Parser.PostProcess.mkGadtDecl`, which is now monadic so that
it can check if `-XLinearTypes` is enabled.
Fixes #18157.
- - - - -
f2d1accf by Leon Schoorl at 2020-08-02T16:44:47-04:00
Fix GHC_STAGE definition generated by make
Fixes #18070
GHC_STAGE is the stage of the compiler we're building, it should be 1,2(,3?).
But make was generating 0 and 1.
Hadrian does this correctly using a similar `+ 1`:
https://gitlab.haskell.org/ghc/ghc/-/blob/eb8115a8c4cbc842b66798480fefc7ab64d31931/hadrian/src/Rules/Generate.hs#L245
- - - - -
db113646 by Simon Peyton Jones at 2020-08-03T10:18:50+01:00
Implement Quick Look impredicativity
This patch implements Quick Look impredicativity (#18126), sticking
very closely to the design in
A quick look at impredicativity, Serrano et al, ICFP 2020
The main change is that a big chunk of GHC.Tc.Gen.Expr has been
extracted to two new modules
GHC.Tc.Gen.App
GHC.Tc.Gen.Head
which deal with typechecking n-ary applications, and the head of
such applications, respectively. Both contain a good deal of
documentation.
Three other loosely-related changes are in this patch:
* I implemented (partly by accident) point (2) of the accepted GHC
proposal "Clean up printing of foralls", namely
https://github.com/ghc-proposals/ghc-proposals/blob/
master/proposals/0179-printing-foralls.rst
In particular, see Note [TcRnExprMode] in GHC.Tc.Module
- :type instantiates /inferred/, but not /specified/, quantifiers
- :type +d instantiates /all/ quantifiers
- :type +v is killed off
* HsRecFld (which the renamer introduces for record field selectors),
is now preserved by the typechecker, rather than being rewritten
back to HsVar. This is more uniform, and turned out to be more
convenient in the new scheme of things.
* The GHCi debugger uses a non-standard unification that allows the
unification variables to unify with polytypes. We used to hack
this by using ImpredicativeTypes, but that doesn't work anymore
so I introduces RuntimeUnkTv. See Note [RuntimeUnkTv] in
GHC.Runtime.Heap.Inspect
WARNING: this patch won't validate on its own. It was too
hard to fully disentangle it from the following patch, on
type errors and kind generalisation.
Changes to tests
* Fixes #9730 (test added)
* Fixes #7026 (test added)
* Fixes most of #8808, except function `g2'` which uses a
section (which doesn't play with QL yet -- see #18126)
Test added
* Fixes #1330. NB Church1.hs subsumes Church2.hs, which is now deleted
* Fixes #17332 (test added)
* Fixes #4295
* This patch makes typecheck/should_run/T7861 fail.
But that turns out to be a pre-existing bug: #18467.
So I have just made T7861 into expect_broken(18467)
- - - - -
24089329 by Simon Peyton Jones at 2020-08-03T10:19:26+01:00
Improve kind generalisation, error messages
This patch does two things:
* It refactors GHC.Tc.Errors a bit. In debugging Quick Look I was
forced to look in detail at error messages, and ended up doing a bit
of refactoring, esp in mkTyVarEqErr'. It's still quite a mess, but
a bit better, I think.
* It makes a significant improvement to the kind checking of type and
class declarations. Specifically, we now ensure that if kind
checking fails with an unsolved constraint, all the skolems are in
scope. That wasn't the case before, which led to some obscure error
messages; and occasional failures with "no skolem info" (eg #16245).
Both of these, and the main Quick Look patch itself, affect a /lot/ of
error messages, as you can see from the number of files changed. I've
checked them all; I think they are as good or better than before.
Smaller things
* I documented the various instances of VarBndr better.
See Note [The VarBndr tyep and its uses] in GHC.Types.Var
* Renamed GHC.Tc.Solver.simpl_top to simplifyTopWanteds
* A bit of refactoring in bindExplicitTKTele, to avoid the
footwork with Either. Simpler now.
* Move promoteTyVar from GHC.Tc.Solver to GHC.Tc.Utils.TcMType
Fixes #16245 (comment 211369), memorialised as
typeecheck/polykinds/T16245a
- - - - -
30 changed files:
- .gitlab-ci.yml
- .gitlab/test-metrics.sh
- CODEOWNERS
- aclocal.m4
- compiler/GHC.hs
- compiler/GHC/Builtin/Names.hs
- compiler/GHC/Builtin/Names/TH.hs
- compiler/GHC/Builtin/Types.hs
- compiler/GHC/Builtin/Types/Prim.hs
- compiler/GHC/Builtin/primops.txt.pp
- compiler/GHC/ByteCode/InfoTable.hs
- compiler/GHC/Cmm/CLabel.hs
- compiler/GHC/Cmm/CallConv.hs
- compiler/GHC/Cmm/Graph.hs
- compiler/GHC/Cmm/Info.hs
- compiler/GHC/Cmm/Info/Build.hs
- compiler/GHC/Cmm/LayoutStack.hs
- compiler/GHC/Cmm/Monad.hs
- compiler/GHC/Cmm/Parser.y
- compiler/GHC/Cmm/Pipeline.hs
- compiler/GHC/Cmm/ProcPoint.hs
- compiler/GHC/Cmm/Switch.hs
- compiler/GHC/Cmm/Switch/Implement.hs
- compiler/GHC/Cmm/Type.hs
- compiler/GHC/Cmm/Utils.hs
- compiler/GHC/CmmToAsm.hs
- compiler/GHC/CmmToAsm/Config.hs
- compiler/GHC/CmmToAsm/Dwarf/Types.hs
- compiler/GHC/CmmToAsm/Monad.hs
- compiler/GHC/CmmToAsm/PIC.hs
The diff was not included because it is too large.
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/29962b14c720698dba888b6d62ad3d80d65eeb29...24089329113711303742306177fa5be64ca85879
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/29962b14c720698dba888b6d62ad3d80d65eeb29...24089329113711303742306177fa5be64ca85879
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/20200803/367db382/attachment-0001.html>
More information about the ghc-commits
mailing list