| Commit message (Collapse) | Author | Age | Files | Lines |
|
|
|
|
|
|
|
| |
Justification in #22231. Short form: In a demand like `1C1(C1(L))`
it was too easy to confuse which `1` belongs to which `C`. Now
that should be more obvious.
Fixes #22231
|
|
|
|
|
| |
A small step towards #22185 to avoid partial functions + safe implementation
of `startsWithUnderscore`.
|
| |
|
|
|
|
|
| |
This allows to avoid further partiality, e. g., map head . group is
replaced by map NE.head . NE.group, and there are less panic calls.
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
I was working on fixing an issue where HLS was trying to pass its
DynFlags to HLint, but didn't pass any of the disabled language
extensions, which HLint would then assume are on because of their
default values.
Currently it's not possible to get any of the "No" flags because the
`DynFlags.extensions` field can't really be used since it is [OnOff
Extension] and OnOff is not exported.
So let's export it.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
I finally got tired of the way that IfaceUnfolding reflected
a previous structure of unfoldings, not the current one. This
MR refactors UnfoldingSource and IfaceUnfolding to be simpler
and more consistent.
It's largely just a refactor, but in UnfoldingSource (which moves
to GHC.Types.Basic, since it is now used in IfaceSyn too), I
distinguish between /user-specified/ and /system-generated/ stable
unfoldings.
data UnfoldingSource
= VanillaSrc
| StableUserSrc -- From a user-specified pragma
| StableSystemSrc -- From a system-generated unfolding
| CompulsorySrc
This has a minor effect in CSE (see the use of isisStableUserUnfolding
in GHC.Core.Opt.CSE), which I tripped over when working on
specialisation, but it seems like a Good Thing to know anyway.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
This patch fixes #21286, by not unboxing dictionaries in
worker/wrapper (ever). The main payload is tiny:
* In `GHC.Core.Opt.DmdAnal.finaliseArgBoxities`, do not unbox
dictionaries in `get_dmd`. See Note [Do not unbox class dictionaries]
in that module
* I also found that imported wrappers were being fruitlessly
specialised, so I fixed that too, in canSpecImport.
See Note [Specialising imported functions] point (2).
In doing due diligence in the testsuite I fixed a number of
other things:
* Improve Note [Specialising unfoldings] in GHC.Core.Unfold.Make,
and Note [Inline specialisations] in GHC.Core.Opt.Specialise,
and remove duplication between the two. The new Note describes
how we specialise functions with an INLINABLE pragma.
And simplify the defn of `spec_unf` in `GHC.Core.Opt.Specialise.specCalls`.
* Improve Note [Worker/wrapper for INLINABLE functions] in
GHC.Core.Opt.WorkWrap.
And (critially) make an actual change which is to propagate the
user-written pragma from the original function to the wrapper; see
`mkStrWrapperInlinePrag`.
* Write new Note [Specialising imported functions] in
GHC.Core.Opt.Specialise
All this has a big effect on some compile times. This is
compiler/perf, showing only changes over 1%:
Metrics: compile_time/bytes allocated
-------------------------------------
LargeRecord(normal) -50.2% GOOD
ManyConstructors(normal) +1.0%
MultiLayerModulesTH_OneShot(normal) +2.6%
PmSeriesG(normal) -1.1%
T10547(normal) -1.2%
T11195(normal) -1.2%
T11276(normal) -1.0%
T11303b(normal) -1.6%
T11545(normal) -1.4%
T11822(normal) -1.3%
T12150(optasm) -1.0%
T12234(optasm) -1.2%
T13056(optasm) -9.3% GOOD
T13253(normal) -3.8% GOOD
T15164(normal) -3.6% GOOD
T16190(normal) -2.1%
T16577(normal) -2.8% GOOD
T16875(normal) -1.6%
T17836(normal) +2.2%
T17977b(normal) -1.0%
T18223(normal) -33.3% GOOD
T18282(normal) -3.4% GOOD
T18304(normal) -1.4%
T18698a(normal) -1.4% GOOD
T18698b(normal) -1.3% GOOD
T19695(normal) -2.5% GOOD
T5837(normal) -2.3%
T9630(normal) -33.0% GOOD
WWRec(normal) -9.7% GOOD
hard_hole_fits(normal) -2.1% GOOD
hie002(normal) +1.6%
geo. mean -2.2%
minimum -50.2%
maximum +2.6%
I diligently investigated some of the big drops.
* Caused by not doing w/w for dictionaries:
T13056, T15164, WWRec, T18223
* Caused by not fruitlessly specialising wrappers
LargeRecord, T9630
For runtimes, here is perf/should+_run:
Metrics: runtime/bytes allocated
--------------------------------
T12990(normal) -3.8%
T5205(normal) -1.3%
T9203(normal) -10.7% GOOD
haddock.Cabal(normal) +0.1%
haddock.base(normal) -1.1%
haddock.compiler(normal) -0.3%
lazy-bs-alloc(normal) -0.2%
------------------------------------------
geo. mean -0.3%
minimum -10.7%
maximum +0.1%
I did not investigate exactly what happens in T9203.
Nofib is a wash:
+-------------------------------++--+-----------+-----------+
| || | tsv (rel) | std. err. |
+===============================++==+===========+===========+
| real/anna || | -0.13% | 0.0% |
| real/fem || | +0.13% | 0.0% |
| real/fulsom || | -0.16% | 0.0% |
| real/lift || | -1.55% | 0.0% |
| real/reptile || | -0.11% | 0.0% |
| real/smallpt || | +0.51% | 0.0% |
| spectral/constraints || | +0.20% | 0.0% |
| spectral/dom-lt || | +1.80% | 0.0% |
| spectral/expert || | +0.33% | 0.0% |
+===============================++==+===========+===========+
| geom mean || | | |
+-------------------------------++--+-----------+-----------+
I spent quite some time investigating dom-lt, but it's pretty
complicated. See my note on !7847. Conclusion: it's just a delicate
inlining interaction, and we have plenty of those.
Metric Decrease:
LargeRecord
T13056
T13253
T15164
T16577
T18223
T18282
T18698a
T18698b
T19695
T9630
WWRec
hard_hole_fits
T9203
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
When multiple Given quantified constraints match a Wanted, and there is
a quantified constraint that dominates all others, we now pick it
to solve the Wanted.
See Note [Use only the best matching quantified constraint].
For example:
[G] d1: forall a b. ( Eq a, Num b, C a b ) => D a b
[G] d2: forall a . C a Int => D a Int
[W] {w}: D a Int
When solving the Wanted, we find that both Givens match, but we pick
the second, because it has a weaker precondition, C a Int, compared
to (Eq a, Num Int, C a Int). We thus say that d2 dominates d1;
see Note [When does a quantified instance dominate another?].
This domination test is done purely in terms of superclass expansion,
in the function GHC.Tc.Solver.Interact.impliedBySCs. We don't attempt
to do a full round of constraint solving; this simple check suffices
for now.
Fixes #22216 and #22223
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Below are the noteworthy changes and if given their impact on compiler
allocations for a type heavy module:
* Use the oneShot trick on LintM
* Use a unboxed tuple for the result of LintM: ~6% reduction
* Avoid a thunk for the result of typeKind in lintType: ~5% reduction
* lint_app: Don't allocate the error msg in the hot code path: ~4%
reduction
* lint_app: Eagerly force the in scope set: ~4%
* nonDetCmpType: Try to short cut using reallyUnsafePtrEquality#: ~2%
* lintM: Use a unboxed maybe for the `a` result: ~12%
* lint_app: make go_app tail recursive to avoid allocating the go function
as heap closure: ~7%
* expandSynTyCon_maybe: Use a specialized data type
For a less type heavy module like nofib/spectral/simple compiled with
-O -dcore-lint allocations went down by ~24% and compile time by ~9%.
-------------------------
Metric Decrease:
T1969
-------------------------
|
|
|
|
| |
includes corresponding changes to haddock submodule
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
In #21717 we saw a reportedly unsound strictness signature due to an unsound
definition of plusSubDmd on Calls. This patch contains a description and the fix
to the unsoundness as outlined in `Note [Call SubDemand vs. evaluation Demand]`.
This fix means we also get rid of the special handling of `-fpedantic-bottoms`
in eta-reduction. Thanks to less strict and actually sound strictness results,
we will no longer eta-reduce the problematic cases in the first place, even
without `-fpedantic-bottoms`.
So fixing the unsoundness also makes our eta-reduction code simpler with less
hacks to explain. But there is another, more unfortunate side-effect:
We *unfix* #21085, but fortunately we have a new fix ready:
See `Note [mkCall and plusSubDmd]`.
There's another change:
I decided to make `Note [SubDemand denotes at least one evaluation]` a lot
simpler by using `plusSubDmd` (instead of `lubPlusSubDmd`) even if both argument
demands are lazy. That leads to less precise results, but in turn rids ourselves
from the need for 4 different `OpMode`s and the complication of
`Note [Manual specialisation of lub*Dmd/plus*Dmd]`. The result is simpler code
that is in line with the paper draft on Demand Analysis.
I left the abandoned idea in `Note [Unrealised opportunity in plusDmd]` for
posterity. The fallout in terms of regressions is negligible, as the testsuite
and NoFib shows.
```
Program Allocs Instrs
--------------------------------------------------------------------------------
hidden +0.2% -0.2%
linear -0.0% -0.7%
--------------------------------------------------------------------------------
Min -0.0% -0.7%
Max +0.2% +0.0%
Geometric Mean +0.0% -0.0%
```
Fixes #21717.
|
|
|
|
|
|
|
| |
* Replace 'text . show' and 'ppr' with 'int'.
* Remove Outputable.hs-boot, no longer needed
* Use pprWithCommas
* Factor out instructions in AArch64 codegen
|
|
|
|
|
|
|
|
|
|
|
| |
Part of proposal 475 (https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0475-tuple-syntax.rst)
Moves all tuples to GHC.Tuple.Prim
Updates ghc-prim version (and bumps bounds in dependents)
updates haddock submodule
updates deepseq submodule
updates text submodule
|
|
|
|
|
|
|
|
|
| |
The function GHC.Stg.InferTags.Rewrite.isTagged can be given
the Id of a join point, which might be representation polymorphic.
This would cause the call to isUnliftedType to crash. It's better
to use typeLevity_maybe instead.
Fixes #22212
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Due to an oversight, the initial specification and implementation of
-Woperator-whitespace focused on varsym exclusively and completely
ignored consym.
This meant that expressions such as "x+ y" would produce a warning,
while "x:+ y" would not.
The specification was corrected in ghc-proposals pull request #404,
and this patch updates the implementation accordingly.
Regression test included.
|
|
|
|
|
|
|
| |
Emit a __builtin_unreachable() call after a foreign call marked as
CmmNeverReturns. This is crucial to generate correctly typed code for
wasm; as for other archs, this is also beneficial for the C compiler
optimizations.
|
|
|
|
|
|
|
|
| |
Rather than a list of constructors and a `NewOrData` flag, we define `data DataDefnCons a = NewTypeCon a | DataTypeCons [a]`, which enforces a newtype to have exactly one constructor.
Closes #22070.
Bump haddock submodule.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Before this patch, the varsym lexing rules were defined as follows:
<0> {
@varsym / { precededByClosingToken `alexAndPred` followedByOpeningToken } { varsym_tight_infix }
@varsym / { followedByOpeningToken } { varsym_prefix }
@varsym / { precededByClosingToken } { varsym_suffix }
@varsym { varsym_loose_infix }
}
Unfortunately, this meant that the predicates 'precededByClosingToken' and
'followedByOpeningToken' were recomputed several times before we could figure
out the whitespace context.
With this patch, we check for whitespace context directly in the lexer
action:
<0> {
@varsym { with_op_ws varsym }
}
The checking for opening/closing tokens happens in 'with_op_ws' now,
which is part of the lexer action rather than the lexer predicate.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
In the lexer, predicates have the following type:
{ ... } :: user -- predicate state
-> AlexInput -- input stream before the token
-> Int -- length of the token
-> AlexInput -- input stream after the token
-> Bool -- True <=> accept the token
This is documented in the Alex manual.
There is access to the input stream both before and after the token.
But when the time comes to construct the token, GHC passes only the
initial string buffer to the lexer action. This patch fixes it:
- type Action = PsSpan -> StringBuffer -> Int -> P (PsLocated Token)
+ type Action = PsSpan -> StringBuffer -> Int -> StringBuffer -> P (PsLocated Token)
Now lexer actions have access to the string buffer both before and after
the token, just like the predicates. It's just a matter of passing an
additional function parameter throughout the lexer.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Previously, derived instances of `Functor` (as well as the related classes
`Foldable`, `Traversable`, and `Generic1`) would determine which constraints to
infer by checking for fields that contain the last type variable. The problem
was that this last type variable was taken from `tyConTyVars`. For GADTs, the
type variables in each data constructor are _not_ the same type variables as
in `tyConTyVars`, leading to #22167.
This fixes the issue by instead checking for the last type variable using
`dataConUnivTyVars`. (This is very similar in spirit to the fix for #21185,
which also replaced an errant use of `tyConTyVars` with type variables from
each data constructor.)
Fixes #22167.
|
|
|
|
|
|
|
| |
When compiling Cmm, the ml_hs_file field is used to indicate Cmm
filename when later generating DWARF information. We should pass the
original filename here, otherwise for preprocessed Cmm files, the
filename will be a temporary filename which is confusing.
|
|
|
|
|
|
|
|
|
|
| |
• Delete some dead code, largely under `GHC.Utils`.
• Clean up a few definitions in `GHC.Utils.(Misc, Monad)`.
• Clean up `GHC.Types.SrcLoc`.
• Derive stock `Functor, Foldable, Traversable` for more types.
• Derive more instances for newtypes.
Bump haddock submodule.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
See the examples in #22057 which show we have to traverse deeply into a
pattern to determine whether it contains a splice or not. The original
implementation pointed this out but deemed this very shallow traversal
"too expensive".
Fixes #22057
I also fixed an oversight in !7821 which meant we lost a warning which
was present in 9.2.2.
Fixes #22067
|
|
|
|
| |
fixes #22176
|
| |
|
|
|
|
|
|
|
|
|
|
| |
For an expression like:
case x of y
Con z -> z
If we also retain the tag sig for z we can generate code to immediately return
it rather than calling out to stg_ap_0_fast.
|
| |
|
|
|
|
|
|
|
| |
This fixes various typos and spelling mistakes
in the compiler.
Fixes #21891
|
| |
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
If a module `M` exports two fields `f` (using DuplicateRecordFields), we can
still accept
import M (f)
import M hiding (f)
and treat `f` as referencing both of them. This was accepted in GHC 9.0, but gave
rise to an ambiguity error in GHC 9.2. See #21625.
This patch also documents this behaviour in the user's guide, and updates the
test for #16745 which is now treated differently.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
This MR adds diagnostic codes, assigning unique numeric codes to
error and warnings, e.g.
error: [GHC-53633]
Pattern match is redundant
This is achieved as follows:
- a type family GhcDiagnosticCode that gives the diagnostic code
for each diagnostic constructor,
- a type family ConRecursInto that specifies whether to recur into
an argument of the constructor to obtain a more fine-grained code
(e.g. different error codes for different 'deriving' errors),
- generics machinery to generate the value-level function assigning
each diagnostic its error code; see Note [Diagnostic codes using generics]
in GHC.Types.Error.Codes.
The upshot is that, to add a new diagnostic code, contributors only need
to modify the two type families mentioned above. All logic relating to
diagnostic codes is thus contained to the GHC.Types.Error.Codes module,
with no code duplication.
This MR also refactors error message datatypes a bit, ensuring we can
derive Generic for them, and cleans up the logic around constraint
solver reports by splitting up 'TcSolverReportInfo' into separate
datatypes (see #20772).
Fixes #21684
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
This patch implements GHC proposal 313, "Delimited continuation
primops", by adding native support for delimited continuations to the
GHC RTS.
All things considered, the patch is relatively small. It almost
exclusively consists of changes to the RTS; the compiler itself is
essentially unaffected. The primops come with fairly extensive Haddock
documentation, and an overview of the implementation strategy is given
in the Notes in rts/Continuation.c.
This first stab at the implementation prioritizes simplicity over
performance. Most notably, every continuation is always stored as a
single, contiguous chunk of stack. If one of these chunks is
particularly large, it can result in poor performance, as the current
implementation does not attempt to cleverly squeeze a subset of the
stack frames into the existing stack: it must fit all at once. If this
proves to be a performance issue in practice, a cleverer strategy would
be a worthwhile target for future improvements.
|
|
|
|
|
|
|
|
|
| |
Normally, the unregisterised builds avoid generating 64-bit
CallishMachOp in StgToCmm, so CmmToC doesn't support these. However,
there do exist cases where we'd like to invoke cmmToC for other cmm
inputs which may contain such CallishMachOps, and it's a rather low
effort to add support for these since they only require calling into
existing ghc-prim cbits.
|
|
|
|
|
|
|
| |
By reexporting the entirety of Applicative from GHC.Prelude, we can save
ourselves some `hiding` and importing of `Applicative` in consumers of GHC.Prelude.
This also has the benefit of isolating this type of change to
GHC.Prelude, so that people in the future don't have to think about it.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Changes:
In order to be warning free and compatible, we hide Applicative(..)
from Prelude in a few places and instead import it directly from
Control.Applicative.
Please see the migration guide at
https://github.com/haskell/core-libraries-committee/blob/main/guides/export-lifta2-prelude.md
for more details.
This means that Applicative is now exported in its entirety from
Prelude.
Motivation:
This change is motivated by a few things:
* liftA2 is an often used function, even more so than (<*>) for some
people.
* When implementing Applicative, the compiler will prompt you for either
an implementation of (<*>) or of liftA2, but trying to use the latter
ends with an error, without further imports. This could be confusing
for newbies.
* For teaching, it is often times easier to introduce liftA2 first,
as it is a natural generalisation of fmap.
* This change seems to have been unanimously and enthusiastically
accepted by the CLC members, possibly indicating a lot of love for it.
* This change causes very limited breakage, see the linked issue below
for an investigation on this.
See https://github.com/haskell/core-libraries-committee/issues/50
for the surrounding discussion and more details.
|
|
|
|
|
| |
Use 'text' instead of 'ppr'.
Using 'ppr' on the list "hello" rendered as "h,e,l,l,o".
|
|
|
|
|
|
|
| |
Change calls to renderWithContext with showSDocOneLine; it's more
efficient and explanatory.
Remove polyPatSig (unused)
|
| |
|
| |
|
| |
|
|
|
|
|
|
|
|
|
|
| |
Rather conservatively return Top.
See Note [Untyped demand on case-alternative binders].
I also factored `addCaseBndrDmd` into two separate functions `scrutSubDmd` and
`fieldBndrDmds`.
Fixes #22039.
|
|
|
|
|
|
| |
It turns out Solo is a very recent addition to base, so for older GHC
versions we just defined it inline here the one place we use it in the
compiler.
|
|
|
|
|
|
|
|
|
| |
- Remove mkHeteroCoercionType, sdocImpredicativeTypes, isStateType (unused),
isCoVar_maybe (duplicated by getCoVar_maybe)
- Replace a few occurrences of voidPrimId with (# #).
void# is a deprecated synonym for the unboxed tuple.
- Use showSDoc in :show linker.
This makes it consistent with the other :show commands
|
|
|
|
| |
closes #21931
|
|
|
|
|
| |
This buglet was exposed by #22114, a consequence of my earlier
refactoring of arity for join points.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
This bug was a subtle error in anyInRnEnvR, introduced by
commit d4d3fe6e02c0eb2117dbbc9df72ae394edf50f06
Author: Andreas Klebinger <klebinger.andreas@gmx.at>
Date: Sat Jul 9 01:19:52 2022 +0200
Rule matching: Don't compute the FVs if we don't look at them.
The net result was #22028, where a rewrite rule would wrongly
match on a lambda.
The fix to that function is easy.
|
|
|
|
|
|
|
|
|
|
|
|
| |
The following `TcRnDiagnostic` messages have been introduced:
TcRnIllegalHsigDefaultMethods
TcRnBadGenericMethod
TcRnWarningMinimalDefIncomplete
TcRnDefaultMethodForPragmaLacksBinding
TcRnIgnoreSpecialisePragmaOnDefMethod
TcRnBadMethodErr
TcRnNoExplicitAssocTypeOrDefaultDeclaration
|
|
|
|
|
|
|
|
| |
As the remarkably-simple #22112 showed, we were making a black hole
in the unfolding of a self-recursive binding. Boo!
It's a bit tricky. Documented in GHC.Iface.Tidy,
Note [tidyTopUnfolding: avoiding black holes]
|
|
|
|
|
|
|
| |
The use of Solo here allows us to force the selection into the SCE to obtain
the Subst but without forcing the substitution to be applied. The resulting thunk
is placed into a lazy field which is rarely forced, so forcing it regresses
peformance.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
This fixes a pretty serious space leak as the forced thunk would retain
`Alt b` values which would then contain reference to a lot of old
bindings and other simplifier gunk.
The OtherCon unfolding was not forced on subsequent simplifier runs so
more and more old stuff would be retained until the end of
simplification.
Fixing this has a drastic effect on maximum residency for the mmark
package which goes from
```
45,005,401,056 bytes allocated in the heap
17,227,721,856 bytes copied during GC
818,281,720 bytes maximum residency (33 sample(s))
9,659,144 bytes maximum slop
2245 MiB total memory in use (0 MB lost due to fragmentation)
```
to
```
45,039,453,304 bytes allocated in the heap
13,128,181,400 bytes copied during GC
331,546,608 bytes maximum residency (40 sample(s))
7,471,120 bytes maximum slop
916 MiB total memory in use (0 MB lost due to fragmentation)
```
See #21993 for some more discussion.
|