[Git][ghc/ghc][wip/T17856] 94 commits: Release Notes: Add news from the pattern-match checker [skip ci]
Ben Gamari
gitlab at gitlab.haskell.org
Wed Jun 24 21:22:33 UTC 2020
Ben Gamari pushed to branch wip/T17856 at Glasgow Haskell Compiler / GHC
Commits:
4c7e9689 by Sebastian Graf at 2020-06-11T10:37:38+02:00
Release Notes: Add news from the pattern-match checker [skip ci]
- - - - -
3445b965 by Sylvain Henry at 2020-06-13T02:13:01-04:00
Only test T16190 with the NCG
T16190 is meant to test a NCG feature. It has already caused spurious
failures in other MRs (e.g. !2165) when LLVM is used.
- - - - -
2517a51c by Sylvain Henry at 2020-06-13T02:13:01-04:00
DynFlags refactoring VIII (#17957)
* Remove several uses of `sdocWithDynFlags`, especially in GHC.Llvm.*
* Add LlvmOpts datatype to store Llvm backend options
* Remove Outputable instances (for LlvmVar, LlvmLit, LlvmStatic and
Llvm.MetaExpr) which require LlvmOpts.
* Rename ppMetaExpr into ppMetaAnnotExpr (pprMetaExpr is now used in place of `ppr :: MetaExpr -> SDoc`)
- - - - -
7a02599a by Sylvain Henry at 2020-06-13T02:13:02-04:00
Remove unused code
- - - - -
72d08610 by Sylvain Henry at 2020-06-13T02:13:02-04:00
Refactor homeUnit
* rename thisPackage into homeUnit
* document and refactor several Backpack things
- - - - -
8dc71f55 by Sylvain Henry at 2020-06-13T02:13:02-04:00
Rename unsafeGetUnitInfo into unsafeLookupUnit
- - - - -
f6be6e43 by Sylvain Henry at 2020-06-13T02:13:02-04:00
Add allowVirtualUnits field in PackageState
Instead of always querying DynFlags to know whether we are allowed to
use virtual units (i.e. instantiated on-the-fly, cf Note [About units]
in GHC.Unit), we store it once for all in
`PackageState.allowVirtualUnits`.
This avoids using DynFlags too much (cf #17957) and is preliminary work
for #14335.
- - - - -
e7272d53 by Sylvain Henry at 2020-06-13T02:13:02-04:00
Enhance UnitId use
* use UnitId instead of String to identify wired-in units
* use UnitId instead of Unit in the backend (Unit are only use by
Backpack to produce type-checked interfaces, not real code)
* rename lookup functions for consistency
* documentation
- - - - -
9c5572cd by Sylvain Henry at 2020-06-13T02:13:02-04:00
Remove LinkerUnitId type alias
- - - - -
d345edfe by Sylvain Henry at 2020-06-13T02:13:02-04:00
Refactor WiredMap
* Remove WiredInUnitId and WiredUnitId type aliases
- - - - -
3d171cd6 by Sylvain Henry at 2020-06-13T02:13:03-04:00
Document and refactor `mkUnit` and `mkUnitInfoMap`
- - - - -
d2109b4f by Sylvain Henry at 2020-06-13T02:13:03-04:00
Remove PreloadUnitId type alias
- - - - -
f50c19b8 by Sylvain Henry at 2020-06-13T02:13:03-04:00
Rename listUnitInfoMap into listUnitInfo
There is no Map involved
- - - - -
ed533ec2 by Sylvain Henry at 2020-06-13T02:13:03-04:00
Rename Package into Unit
The terminology changed over time and now package databases contain
"units" (there can be several units compiled from a single Cabal
package: one per-component, one for each option set, one per
instantiation, etc.). We should try to be consistent internally and use
"units": that's what this renaming does. Maybe one day we'll fix the UI
too (e.g. replace -package-id with -unit-id, we already have
-this-unit-id and ghc-pkg has -unit-id...) but it's not done in this
patch.
* rename getPkgFrameworkOpts into getUnitFrameworkOpts
* rename UnitInfoMap into ClosureUnitInfoMap
* rename InstalledPackageIndex into UnitInfoMap
* rename UnusablePackages into UnusableUnits
* rename PackagePrecedenceIndex into UnitPrecedenceMap
* rename PackageDatabase into UnitDatabase
* rename pkgDatabase into unitDatabases
* rename pkgState into unitState
* rename initPackages into initUnits
* rename renamePackage into renameUnitInfo
* rename UnusablePackageReason into UnusableUnitReason
* rename getPackage* into getUnit*
* etc.
- - - - -
202728e5 by Sylvain Henry at 2020-06-13T02:13:03-04:00
Make ClosureUnitInfoMap uses UnitInfoMap
- - - - -
55b4263e by Sylvain Henry at 2020-06-13T02:13:03-04:00
Remove ClosureUnitInfoMap
- - - - -
653d17bd by Sylvain Henry at 2020-06-13T02:13:03-04:00
Rename Package into Unit (2)
* rename PackageState into UnitState
* rename findWiredInPackages into findWiredInUnits
* rename lookupModuleInAll[Packages,Units]
* etc.
- - - - -
ae900605 by Sylvain Henry at 2020-06-13T02:13:03-04:00
Move dump_mod_map into initUnits
- - - - -
598cc1dd by Sylvain Henry at 2020-06-13T02:13:03-04:00
Move wiring of homeUnitInstantiations outside of mkUnitState
- - - - -
437265eb by Sylvain Henry at 2020-06-13T02:13:03-04:00
Avoid timing module map dump in initUnits
- - - - -
9400aa93 by Sylvain Henry at 2020-06-13T02:13:03-04:00
Remove preload parameter of mkUnitState
* Remove preload parameter (unused)
* Don't explicitly return preloaded units: redundant because already
returned as "preloadUnits" field of UnitState
- - - - -
266bc3d9 by Sylvain Henry at 2020-06-13T02:13:03-04:00
DynFlags: refactor unwireUnit
- - - - -
9e715c1b by Sylvain Henry at 2020-06-13T02:13:03-04:00
Document getPreloadUnitsAnd
- - - - -
bd5810dc by Sylvain Henry at 2020-06-13T02:13:03-04:00
DynFlags: remove useless add_package parameter
- - - - -
36e1daf0 by Sylvain Henry at 2020-06-13T02:13:03-04:00
DynFlags: make listVisibleModuleNames take a UnitState
- - - - -
5226da37 by Sylvain Henry at 2020-06-13T02:13:03-04:00
Refactor and document add_package
- - - - -
4b53aac1 by Sylvain Henry at 2020-06-13T02:13:03-04:00
Refactor and document closeUnitDeps
- - - - -
42c054f6 by Sylvain Henry at 2020-06-13T02:13:03-04:00
DynFlags: findWiredInUnits
- - - - -
a444d01b by Sylvain Henry at 2020-06-13T02:13:03-04:00
DynFlags: reportCycles, reportUnusable
- - - - -
8408d521 by Sylvain Henry at 2020-06-13T02:13:03-04:00
DynFlags: merge_databases
- - - - -
fca2d25f by Sylvain Henry at 2020-06-13T02:13:03-04:00
DynFlags: add UnitConfig datatype
Avoid directly querying flags from DynFlags to build the UnitState.
Instead go via UnitConfig so that we could reuse this to make another
UnitState for plugins.
- - - - -
4274688a by Sylvain Henry at 2020-06-13T02:13:03-04:00
Move distrustAll into mkUnitState
- - - - -
28d804e1 by Sylvain Henry at 2020-06-13T02:13:03-04:00
Create helper upd_wired_in_home_instantiations
- - - - -
ac964c83 by Sylvain Henry at 2020-06-13T02:13:03-04:00
Put database cache in UnitConfig
- - - - -
bfd0a78c by Sylvain Henry at 2020-06-13T02:13:03-04:00
Don't return preload units when we set DyNFlags
Preload units can be retrieved in UnitState when needed (i.e. in GHCi)
- - - - -
1fbb4bf5 by Sylvain Henry at 2020-06-13T02:13:03-04:00
NCGConfig: remove useless ncgUnitId field
- - - - -
c10ff7e7 by Sylvain Henry at 2020-06-13T02:13:03-04:00
Doc: fix some comments
- - - - -
456e17f0 by Sylvain Henry at 2020-06-13T02:13:03-04:00
Bump haddock submodule and allow metric decrease
Metric Decrease:
T12150
T12234
T5837
Metric Increase:
T16190
- - - - -
42953902 by Simon Peyton Jones at 2020-06-13T02:13:03-04:00
Trim the demand for recursive product types
Ticket #18304 showed that we need to be very careful
when exploring the demand (esp usage demand) on recursive
product types.
This patch solves the problem by trimming the demand on such types --
in effect, a form of "widening".
See the Note [Trimming a demand to a type] in DmdAnal, which explains
how I did this by piggy-backing on an existing mechansim for trimming
demands becuase of GADTs. The significant payload of this patch is
very small indeed:
* Make GHC.Core.Opt.WorkWrap.Utils.typeShape use RecTcChecker to
avoid looking through recursive types.
But on the way
* I found that ae_rec_tc was entirely inoperative and did nothing.
So I removed it altogether from DmdAnal.
* I moved some code around in DmdAnal and Demand.
(There are no actual changes in dmdFix.)
* I changed the API of DmsAnal.dmdAnalRhsLetDown to return
a StrictSig rather than a decorated Id
* I removed the dead function peelTsFuns from Demand
Performance effects:
Nofib: 0.0% changes. Not surprising, because they don't
use recursive products
Perf tests
T12227:
1% increase in compiler allocation, becuase $cto gets w/w'd.
It did not w/w before because it takes a deeply nested
argument, so the worker gets too many args, so we abandon w/w
altogether (see GHC.Core.Opt.WorkWrap.Utils.isWorkerSmallEnough)
With this patch we trim the demands. That is not strictly
necessary (since these Generic type constructors are like
tuples -- they can't cause a loop) but the net result is that
we now w/w $cto which is fine.
UniqLoop:
16% decrease in /runtime/ allocation. The UniqSupply is a
recursive product, so currently we abandon all strictness on
'churn'. With this patch 'churn' gets useful strictness, and
we w/w it. Hooray
Metric Decrease:
UniqLoop
Metric Increase:
T12227
- - - - -
87d504f4 by Viktor Dukhovni at 2020-06-13T02:13:05-04:00
Add introductory prose for Data.Traversable
- - - - -
9f09b608 by Oleg Grenrus at 2020-06-13T02:13:07-04:00
Fix #12073: Add MonadFix Q instance
- - - - -
220c2d34 by Ben Gamari at 2020-06-13T02:13:07-04:00
testsuite: Increase size of T12150
As noted in #18319, this test was previously very fragile. Increase its
size to make it more likely that its fails with its newly-increased
acceptance threshold.
Metric Increase:
T12150
- - - - -
8bba1c26 by Ben Gamari at 2020-06-13T04:59:06-04:00
gitlab-ci: Always push perf notes
Previously we ci.sh would run with `set -e` implying that we wouldn't
push perf notes if the testsuite were to fail, even if it *only* failed
due to perf notes. This rendered the whole performance testing story
quite fragile as a single regressing commit would cause every successive
commit to fail since a new baseline would not be uploaded.
Fix this by ensuring that we always push performance notes.
- - - - -
7a773f16 by Ben Gamari at 2020-06-13T15:10:55-04:00
gitlab-ci: Eliminate redundant push of CI metrics
- - - - -
a31218f7 by Ryan Scott at 2020-06-13T15:58:37-04:00
Use HsForAllTelescope to avoid inferred, visible foralls
Currently, `HsForAllTy` permits the combination of `ForallVis` and
`Inferred`, but you can't actually typecheck code that uses it
(e.g., `forall {a} ->`). This patch refactors `HsForAllTy` to use a
new `HsForAllTelescope` data type that makes a type-level distinction
between visible and invisible `forall`s such that visible `forall`s
do not track `Specificity`. That part of the patch is actually quite
small; the rest is simply changing consumers of `HsType` to
accommodate this new type.
Fixes #18235. Bumps the `haddock` submodule.
- - - - -
c0e6dee9 by Tamar Christina at 2020-06-14T09:07:44-04:00
winio: Add Atomic Exchange PrimOp and implement Atomic Ptr exchanges.
The initial version was rewritten by Tamar Christina.
It was rewritten in large parts by Andreas Klebinger.
Co-authored-by: Andreas Klebinger <klebinger.andreas at gmx.at>
- - - - -
9a7462fb by Ben Gamari at 2020-06-14T15:35:23-04:00
codeGen: Don't discard live case binders in unsafeEqualityProof logic
Previously CoreToStg would unconditionally discard cases of the form:
case unsafeEqualityProof of wild { _ -> rhs }
and rather replace the whole thing with `rhs`. However, in some cases
(see #18227) the case binder is still live, resulting in unbound
occurrences in `rhs`. Fix this by only discarding the case if the case
binder is dead.
Fixes #18227.
- - - - -
e4137c48 by Ben Gamari at 2020-06-14T15:35:23-04:00
testsuite: Add tests for #18227
T18227A is the original issue which gave rise to the ticket and depends
upon bytestring. T18227B is a minimized reproducer.
- - - - -
8bab9ff1 by Ben Gamari at 2020-06-14T15:35:59-04:00
hadrian: Fix rts include and library paths
Fixes two bugs:
* (?) and (<>) associated in a surprising way
* We neglected to include libdw paths in the rts configure flags
- - - - -
bd761185 by Ben Gamari at 2020-06-14T15:35:59-04:00
hadrian: Drop redundant GHC arguments
Cabal should already be passing this arguments to GHC.
- - - - -
01f7052c by Peter Trommler at 2020-06-14T15:36:38-04:00
FFI: Fix pass small ints in foreign call wrappers
The Haskell calling convention requires integer parameters smaller
than wordsize to be promoted to wordsize (where the upper bits are
don't care). To access such small integer parameter read a word from
the parameter array and then cast that word to the small integer
target type.
Fixes #15933
- - - - -
502647f7 by Krzysztof Gogolewski at 2020-06-14T15:37:14-04:00
Fix "ndecreasingIndentation" in manual (#18116)
- - - - -
9a9cc089 by Simon Jakobi at 2020-06-15T13:10:00-04:00
Use foldl' in unionManyUniqDSets
- - - - -
761dcb84 by Moritz Angermann at 2020-06-15T13:10:36-04:00
Load .lo as well.
Some archives contain so called linker objects, with the affectionate
.lo suffic. For example the musl libc.a will come in that form. We
still want to load those objects, hence we should not discard them and
look for .lo as well. Ultimately we might want to fix this proerly by
looking at the file magic.
- - - - -
cf01477f by Vladislav Zavialov at 2020-06-15T13:11:20-04:00
User's Guide: KnownNat evidence is Natural
This bit of documentation got outdated after commit
1fcede43d2b30f33b7505e25eb6b1f321be0407f
- - - - -
d0dcbfe6 by Jan Hrček at 2020-06-16T20:36:38+02:00
Fix typos and formatting in user guide
- - - - -
56a9e95f by Jan Hrček at 2020-06-16T20:36:38+02:00
Resolve TODO
- - - - -
3e884d14 by Jan Hrček at 2020-06-16T20:36:38+02:00
Rename TcHoleErrors to GHC.Tc.Errors.Hole
- - - - -
d23fc678 by Stefan Schulze Frielinghaus at 2020-06-17T15:31:09-04:00
hadrian: Build with threaded runtime if available
See #16873.
- - - - -
0639dc10 by Sylvain Henry at 2020-06-17T15:31:53-04:00
T16190: only measure bytes_allocated
Just adding `{-# LANGUAGE BangPatterns #-}` makes the two other metrics
fluctuate by 13%.
- - - - -
4cab6897 by Adam Sandberg Ericsson at 2020-06-17T15:32:44-04:00
docs: fix formatting in users guide
- - - - -
eb8115a8 by Sylvain Henry at 2020-06-17T15:33:23-04:00
Move CLabel assertions into smart constructors (#17957)
It avoids using DynFlags in the Outputable instance of Clabel to check
assertions at pretty-printing time.
- - - - -
7faa4509 by Ben Gamari at 2020-06-17T15:43:31-04:00
base: Bump to 4.15.0.0
- - - - -
20616959 by Ben Gamari at 2020-06-17T15:43:31-04:00
configure: Use grep -q instead of --quiet
The latter is apparently not supported by busybox.
- - - - -
40fa237e by Krzysztof Gogolewski at 2020-06-17T16:21:58-04:00
Linear types (#15981)
This is the first step towards implementation of the linear types proposal
(https://github.com/ghc-proposals/ghc-proposals/pull/111).
It features
* A language extension -XLinearTypes
* Syntax for linear functions in the surface language
* Linearity checking in Core Lint, enabled with -dlinear-core-lint
* Core-to-core passes are mostly compatible with linearity
* Fields in a data type can be linear or unrestricted; linear fields
have multiplicity-polymorphic constructors.
If -XLinearTypes is disabled, the GADT syntax defaults to linear fields
The following items are not yet supported:
* a # m -> b syntax (only prefix FUN is supported for now)
* Full multiplicity inference (multiplicities are really only checked)
* Decent linearity error messages
* Linear let, where, and case expressions in the surface language
(each of these currently introduce the unrestricted variant)
* Multiplicity-parametric fields
* Syntax for annotating lambda-bound or let-bound with a multiplicity
* Syntax for non-linear/multiple-field-multiplicity records
* Linear projections for records with a single linear field
* Linear pattern synonyms
* Multiplicity coercions (test LinearPolyType)
A high-level description can be found at
https://ghc.haskell.org/trac/ghc/wiki/LinearTypes/Implementation
Following the link above you will find a description of the changes made to Core.
This commit has been authored by
* Richard Eisenberg
* Krzysztof Gogolewski
* Matthew Pickering
* Arnaud Spiwack
With contributions from:
* Mark Barbone
* Alexander Vershilov
Updates haddock submodule.
- - - - -
6cb84c46 by Krzysztof Gogolewski at 2020-06-17T16:22:03-04:00
Various performance improvements
This implements several general performance improvements to GHC,
to offset the effect of the linear types change.
General optimisations:
- Add a `coreFullView` function which iterates `coreView` on the
head. This avoids making function recursive solely because the
iterate `coreView` themselves. As a consequence, this functions can
be inlined, and trigger case-of-known constructor (_e.g._
`kindRep_maybe`, `isLiftedRuntimeRep`, `isMultiplicityTy`,
`getTyVar_maybe`, `splitAppTy_maybe`, `splitFunType_maybe`,
`tyConAppTyCon_maybe`). The common pattern about all these functions
is that they are almost always used as views, and immediately
consumed by a case expression. This commit also mark them asx `INLINE`.
- In `subst_ty` add a special case for nullary `TyConApp`, which avoid
allocations altogether.
- Use `mkTyConApp` in `subst_ty` for the general `TyConApp`. This
required quite a bit of module shuffling.
case. `myTyConApp` enforces crucial sharing, which was lost during
substitution. See also !2952 .
- Make `subst_ty` stricter.
- In `eqType` (specifically, in `nonDetCmpType`), add a special case,
tested first, for the very common case of nullary `TyConApp`.
`nonDetCmpType` has been made `INLINE` otherwise it is actually a
regression. This is similar to the optimisations in !2952.
Linear-type specific optimisations:
- Use `tyConAppTyCon_maybe` instead of the more complex `eqType` in
the definition of the pattern synonyms `One` and `Many`.
- Break the `hs-boot` cycles between `Multiplicity.hs` and `Type.hs`:
`Multiplicity` now import `Type` normally, rather than from the
`hs-boot`. This way `tyConAppTyCon_maybe` can inline properly in the
`One` and `Many` pattern synonyms.
- Make `updateIdTypeAndMult` strict in its type and multiplicity
- The `scaleIdBy` gets a specialised definition rather than being an
alias to `scaleVarBy`
- `splitFunTy_maybe` is given the type `Type -> Maybe (Mult, Type,
Type)` instead of `Type -> Maybe (Scaled Type, Type)`
- Remove the `MultMul` pattern synonym in favour of a view `isMultMul`
because pattern synonyms appear not to inline well.
- in `eqType`, in a `FunTy`, compare multiplicities last: they are
almost always both `Many`, so it helps failing faster.
- Cache `manyDataConTy` in `mkTyConApp`, to make sure that all the
instances of `TyConApp ManyDataConTy []` are physically the same.
This commit has been authored by
* Richard Eisenberg
* Krzysztof Gogolewski
* Arnaud Spiwack
Metric Decrease:
haddock.base
T12227
T12545
T12990
T1969
T3064
T5030
T9872b
Metric Increase:
haddock.base
haddock.Cabal
haddock.compiler
T12150
T12234
T12425
T12707
T13035
T13056
T15164
T16190
T18304
T1969
T3064
T3294
T5631
T5642
T5837
T6048
T9020
T9233
T9675
T9872a
T9961
WWRec
- - - - -
57db91d8 by Sylvain Henry at 2020-06-17T16:22:03-04:00
Remove integer-simple
integer-simple uses lists of words (`[Word]`) to represent big numbers
instead of ByteArray#:
* it is less efficient than the newer ghc-bignum native backend
* it isn't compatible with the big number representation that is now
shared by all the ghc-bignum backends (based on the one that was
used only in integer-gmp before).
As a consequence, we simply drop integer-simple
- - - - -
9f96bc12 by Sylvain Henry at 2020-06-17T16:22:03-04:00
ghc-bignum library
ghc-bignum is a newer package that aims to replace the legacy
integer-simple and integer-gmp packages.
* it supports several backends. In particular GMP is still supported and
most of the code from integer-gmp has been merged in the "gmp"
backend.
* the pure Haskell "native" backend is new and is much faster than the
previous pure Haskell implementation provided by integer-simple
* new backends are easier to write because they only have to provide a
few well defined functions. All the other code is common to all
backends. In particular they all share the efficient small/big number
distinction previously used only in integer-gmp.
* backends can all be tested against the "native" backend with a simple
Cabal flag. Backends are only allowed to differ in performance, their
results should be the same.
* Add `integer-gmp` compat package: provide some pattern synonyms and
function aliases for those in `ghc-bignum`. It is intended to avoid
breaking packages that depend on `integer-gmp` internals.
Update submodules: text, bytestring
Metric Decrease:
Conversions
ManyAlternatives
ManyConstructors
Naperian
T10359
T10547
T10678
T12150
T12227
T12234
T12425
T13035
T13719
T14936
T1969
T4801
T4830
T5237
T5549
T5837
T8766
T9020
parsing001
space_leak_001
T16190
haddock.base
On ARM and i386, T17499 regresses (+6% > 5%).
On x86_64 unregistered, T13701 sometimes regresses (+2.2% > 2%).
Metric Increase:
T17499
T13701
- - - - -
96aa5787 by Sylvain Henry at 2020-06-17T16:22:03-04:00
Update compiler
Thanks to ghc-bignum, the compiler can be simplified:
* Types and constructors of Integer and Natural can be wired-in. It
means that we don't have to query them from interfaces. It also means
that numeric literals don't have to carry their type with them.
* The same code is used whatever ghc-bignum backend is enabled. In
particular, conversion of bignum literals into final Core expressions
is now much more straightforward. Bignum closure inspection too.
* GHC itself doesn't depend on any integer-* package anymore
* The `integerLibrary` setting is gone.
- - - - -
0f67e344 by Sylvain Henry at 2020-06-17T16:22:03-04:00
Update `base` package
* GHC.Natural isn't implemented in `base` anymore. It is provided by
ghc-bignum in GHC.Num.Natural. It means that we can safely use Natural
primitives in `base` without fearing issues with built-in rewrite
rules (cf #15286)
* `base` doesn't conditionally depend on an integer-* package anymore,
it depends on ghc-bignum
* Some duplicated code in integer-* can now be factored in GHC.Float
* ghc-bignum tries to use a uniform naming convention so most of the
other changes are renaming
- - - - -
aa9e7b71 by Sylvain Henry at 2020-06-17T16:22:03-04:00
Update `make` based build system
* replace integer-* package selection with ghc-bignum backend selection
- - - - -
f817d816 by Sylvain Henry at 2020-06-17T16:22:04-04:00
Update testsuite
* support detection of slow ghc-bignum backend (to replace the detection
of integer-simple use). There are still some test cases that the
native backend doesn't handle efficiently enough.
* remove tests for GMP only functions that have been removed from
ghc-bignum
* fix test results showing dependent packages (e.g. integer-gmp) or
showing suggested instances
* fix test using Integer/Natural API or showing internal names
- - - - -
dceecb09 by Sylvain Henry at 2020-06-17T16:22:04-04:00
Update Hadrian
* support ghc-bignum backend selection in flavours and command-line
* support ghc-bignum "--check" flag (compare results of selected backend
against results of the native one) in flavours and command-line (e.g.
pass --bignum=check-gmp" to check the "gmp" backend)
* remove the hack to workaround #15286
* build GMP only when the gmp backend is used
* remove hacks to workaround `text` package flags about integer-*. We
fix `text` to use ghc-bignum unconditionally in another patch
- - - - -
fa4281d6 by Sylvain Henry at 2020-06-17T16:22:04-04:00
Bump bytestring and text submodules
- - - - -
1a3f6f34 by Adam Sandberg Ericsson at 2020-06-18T23:03:36-04:00
docs: mention -hiedir in docs for -outputdir
[skip ci]
- - - - -
729bcb02 by Sylvain Henry at 2020-06-18T23:04:17-04:00
Hadrian: fix build on Mac OS Catalina (#17798)
- - - - -
95e18292 by Andreas Klebinger at 2020-06-18T23:04:58-04:00
Relax allocation threshold for T12150.
This test performs little work, so the most minor allocation
changes often cause the test to fail.
Increasing the threshold to 2% should help with this.
- - - - -
8ce6c393 by Sebastian Graf at 2020-06-18T23:05:36-04:00
hadrian: Bump pinned cabal.project to an existent index-state
- - - - -
08c1cb0f by Ömer Sinan Ağacan at 2020-06-18T23:06:21-04:00
Fix uninitialized field read in Linker.c
Valgrind report of the bug when running the test `linker_unload`:
==29666== Conditional jump or move depends on uninitialised value(s)
==29666== at 0x369C5B4: setOcInitialStatus (Linker.c:1305)
==29666== by 0x369C6C5: mkOc (Linker.c:1347)
==29666== by 0x36C027A: loadArchive_ (LoadArchive.c:522)
==29666== by 0x36C0600: loadArchive (LoadArchive.c:626)
==29666== by 0x2C144CD: ??? (in /home/omer/haskell/ghc_2/testsuite/tests/rts/linker/linker_unload.run/linker_unload)
==29666==
==29666== Conditional jump or move depends on uninitialised value(s)
==29666== at 0x369C5B4: setOcInitialStatus (Linker.c:1305)
==29666== by 0x369C6C5: mkOc (Linker.c:1347)
==29666== by 0x369C9F6: preloadObjectFile (Linker.c:1507)
==29666== by 0x369CA8D: loadObj_ (Linker.c:1536)
==29666== by 0x369CB17: loadObj (Linker.c:1557)
==29666== by 0x3866BC: main (linker_unload.c:33)
The problem is `mkOc` allocates a new `ObjectCode` and calls
`setOcInitialStatus` without initializing the `status` field.
`setOcInitialStatus` reads the field as first thing:
static void setOcInitialStatus(ObjectCode* oc) {
if (oc->status == OBJECT_DONT_RESOLVE)
return;
if (oc->archiveMemberName == NULL) {
oc->status = OBJECT_NEEDED;
} else {
oc->status = OBJECT_LOADED;
}
}
`setOcInitialStatus` is unsed in two places for two different purposes:
in `mkOc` where we don't have the `status` field initialized yet (`mkOc`
is supposed to initialize it), and `loadOc` where we do have `status`
field initialized and we want to update it. Instead of splitting the
function into two functions which are both called just once I inline the
functions in the use sites and remove it.
Fixes #18342
- - - - -
da18ff99 by Tamar Christina at 2020-06-18T23:07:03-04:00
fix windows bootstrap due to linker changes
- - - - -
2af0ec90 by Sylvain Henry at 2020-06-18T23:07:47-04:00
DynFlags: store default depth in SDocContext (#17957)
It avoids having to use DynFlags to reach for pprUserLength.
- - - - -
d4a0be75 by Sylvain Henry at 2020-06-18T23:08:35-04:00
Move tablesNextToCode field into Platform
tablesNextToCode is a platform setting and doesn't belong into DynFlags
(#17957). Doing this is also a prerequisite to fix #14335 where we deal
with two platforms (target and host) that may have different platform
settings.
- - - - -
809caedf by John Ericson at 2020-06-23T22:47:37-04:00
Switch from HscSource to IsBootInterface for module lookup in GhcMake
We look up modules by their name, and not their contents. There is no
way to separately reference a signature vs regular module; you get what
you get. Only boot files can be referenced indepenently with `import {-#
SOURCE #-}`.
- - - - -
7750bd45 by Sylvain Henry at 2020-06-23T22:48:18-04:00
Cmm: introduce SAVE_REGS/RESTORE_REGS
We don't want to save both Fn and Dn register sets on x86-64 as they are
aliased to the same arch register (XMMn).
Moreover, when SAVE_STGREGS was used in conjunction with `jump foo [*]`
which makes a set of Cmm registers alive so that they cover all arch
registers used to pass parameter, we could have Fn, Dn and XMMn alive at
the same time. It made the LLVM code generator choke (see #17920).
Now `SAVE_REGS/RESTORE_REGS` and `jump foo [*]` use the same set of
registers.
- - - - -
2636794d by Sylvain Henry at 2020-06-23T22:48:18-04:00
CmmToC: don't add extern decl to parsed Cmm data
Previously, if a .cmm file *not in the RTS* contained something like:
```cmm
section "rodata" { msg : bits8[] "Test\n"; }
```
It would get compiled by CmmToC into:
```c
ERW_(msg);
const char msg[] = "Test\012";
```
and fail with:
```
/tmp/ghc32129_0/ghc_4.hc:5:12: error:
error: conflicting types for \u2018msg\u2019
const char msg[] = "Test\012";
^~~
In file included from /tmp/ghc32129_0/ghc_4.hc:3:0: error:
/tmp/ghc32129_0/ghc_4.hc:4:6: error:
note: previous declaration of \u2018msg\u2019 was here
ERW_(msg);
^
/builds/hsyl20/ghc/_build/install/lib/ghc-8.11.0.20200605/lib/../lib/x86_64-linux-ghc-8.11.0.20200605/rts-1.0/include/Stg.h:253:46: error:
note: in definition of macro \u2018ERW_\u2019
#define ERW_(X) extern StgWordArray (X)
^
```
See the rationale for this on https://gitlab.haskell.org/ghc/ghc/-/wikis/commentary/compiler/backends/ppr-c#prototypes
Now we don't generate these extern declarations (ERW_, etc.) for
top-level data. It shouldn't change anything for the RTS (the only place
we use .cmm files) as it is already special cased in
`GHC.Cmm.CLabel.needsCDecl`. And hand-written Cmm can use explicit
extern declarations when needed.
Note that it allows `cgrun069` test to pass with CmmToC (cf #15467).
- - - - -
5f6a0665 by Sylvain Henry at 2020-06-23T22:48:18-04:00
LLVM: refactor and comment register padding code (#17920)
- - - - -
cad62ef1 by Sylvain Henry at 2020-06-23T22:48:18-04:00
Add tests for #17920
Metric Decrease:
T12150
T12234
- - - - -
a2a9006b by Xavier Denis at 2020-06-23T22:48:56-04:00
Fix issue #18262 by zonking constraints after solving
Zonk residual constraints in checkForExistence to reveal user type
errors.
Previously when `:instances` was used with instances that have TypeError
constraints the result would look something like:
instance [safe] s0 => Err 'A -- Defined at ../Bug2.hs:8:10
whereas after zonking, `:instances` now sees the `TypeError` and
properly eliminates the constraint from the results.
- - - - -
181516bc by Simon Peyton Jones at 2020-06-23T22:49:33-04:00
Fix a buglet in Simplify.simplCast
This bug, revealed by #18347, is just a missing update to
sc_hole_ty in simplCast. I'd missed a code path when I
made the recentchanges in
commit 6d49d5be904c0c01788fa7aae1b112d5b4dfaf1c
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date: Thu May 21 12:53:35 2020 +0100
Implement cast worker/wrapper properly
The fix is very easy.
Two other minor changes
* Tidy up in SimpleOpt.simple_opt_expr. In fact I think this is an
outright bug, introduced in the fix to #18112: we were simplifying
the same coercion twice *with the same substitution*, which is just
wrong. It'd be a hard bug to trigger, so I just fixed it; less code
too.
* Better debug printing of ApplyToVal
- - - - -
625a7f54 by Simon Peyton Jones at 2020-06-23T22:50:11-04:00
Two small tweaks to Coercion.simplifyArgsWorker
These tweaks affect the inner loop of simplifyArgsWorker, which
in turn is called from the flattener in Flatten.hs. This is
a key perf bottleneck to T9872{a,b,c,d}.
These two small changes have a modest but useful benefit.
No change in functionality whatsoever.
Relates to #18354
- - - - -
b5768cce by Sylvain Henry at 2020-06-23T22:50:49-04:00
Don't use timesInt2# with GHC < 8.11 (fix #18358)
- - - - -
7ad4085c by Sylvain Henry at 2020-06-23T22:51:27-04:00
Fix invalid printf format
- - - - -
a1f34d37 by Krzysztof Gogolewski at 2020-06-23T22:52:09-04:00
Add missing entry to freeNamesItem (#18369)
- - - - -
2c70a1e3 by Ben Gamari at 2020-06-24T17:22:31-04:00
configure: Work around Raspbian's silly packaging decisions
See #17856.
- - - - -
30 changed files:
- .gitlab/ci.sh
- .gitmodules
- aclocal.m4
- compiler/GHC.hs
- compiler/GHC/Builtin/Names.hs
- compiler/GHC/Builtin/Names/TH.hs
- compiler/GHC/Builtin/PrimOps.hs
- compiler/GHC/Builtin/Types.hs
- compiler/GHC/Builtin/Types.hs-boot
- compiler/GHC/Builtin/Types/Prim.hs
- compiler/GHC/Builtin/primops.txt.pp
- compiler/GHC/ByteCode/Asm.hs
- compiler/GHC/ByteCode/InfoTable.hs
- compiler/GHC/ByteCode/Linker.hs
- compiler/GHC/Cmm/CLabel.hs
- compiler/GHC/Cmm/CallConv.hs
- compiler/GHC/Cmm/Info.hs
- compiler/GHC/Cmm/LayoutStack.hs
- compiler/GHC/Cmm/MachOp.hs
- compiler/GHC/Cmm/Parser.y
- compiler/GHC/Cmm/Pipeline.hs
- compiler/GHC/Cmm/ProcPoint.hs
- compiler/GHC/CmmToAsm/CPrim.hs
- compiler/GHC/CmmToAsm/Config.hs
- compiler/GHC/CmmToAsm/Monad.hs
- compiler/GHC/CmmToAsm/PPC/CodeGen.hs
- compiler/GHC/CmmToAsm/SPARC/CodeGen.hs
- compiler/GHC/CmmToAsm/X86/CodeGen.hs
- compiler/GHC/CmmToAsm/X86/Instr.hs
- compiler/GHC/CmmToAsm/X86/Ppr.hs
The diff was not included because it is too large.
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/57d074073c8e77dab3fbf2f3411bbb9cbf2733bf...2c70a1e3f98a06321b066613eb8dccfd7ac420c7
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/57d074073c8e77dab3fbf2f3411bbb9cbf2733bf...2c70a1e3f98a06321b066613eb8dccfd7ac420c7
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/20200624/9575d8b7/attachment-0001.html>
More information about the ghc-commits
mailing list