| Commit message (Collapse) | Author | Age | Files | Lines |
|
|
|
|
|
|
|
|
|
| |
Previously while constructing the jump table index we would
zero-extend the discriminant before subtracting the start of the
jump-table. This goes subtly wrong in the case of a sub-word, signed
discriminant, as described in the included Note. Fix this in both the
PPC and X86 NCGs.
Fixes #21186.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Rewrite the critical notes and fix outdated ones,
use `HsQuote GhcRn` (in `HsBracketTc`) for desugaring regardless of the
bracket being typed or untyped,
remove unused `EpAnn` from `Hs*Bracket GhcRn`,
zonkExpr factor out common brackets code,
ppr_expr factor out common brackets code,
and fix tests,
to finish MR https://gitlab.haskell.org/ghc/ghc/-/merge_requests/4782.
-------------------------
Metric Decrease:
hard_hole_fits
-------------------------
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
An untyped bracket `HsQuote p` can never be constructed with
`p ~ GhcTc`. This is because we don't typecheck `HsQuote` at all.
That's OK, because we also never use `HsQuote GhcTc`.
To enforce this at the type level we make `HsQuote GhcTc` isomorphic
to `NoExtField` and impossible to construct otherwise, by using TTG field
extensions to make all constructors, except for `XQuote` (which takes `NoExtField`),
unconstructable, with `DataConCantHappen`
This is explained more in detail in Note [The life cycle of a TH quotation]
Related discussion: https://gitlab.haskell.org/ghc/ghc/-/merge_requests/4782
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
When desugaring a bracket we want to desugar /renamed/ rather than
/typechecked/ code; So in (HsExpr GhcTc) tree, we must
have a (HsExpr GhcRn) for the quotation itself.
This commit reworks the TTG refactor on typed and untyped brackets by
storing the /renamed/ code in the bracket field extension rather than in
the constructor extension in `HsQuote` (previously called
`HsUntypedBracket`)
See Note [The life cycle of a TH quotation] and https://gitlab.haskell.org/ghc/ghc/-/merge_requests/4782
|
|
|
|
|
|
|
|
|
|
|
| |
Split HsBracket into HsTypedBracket and HsUntypedBracket.
Unfortunately, we still cannot get rid of
instance XXTypedBracket GhcTc = HsTypedBracket GhcRn
despite no longer requiring it for typechecking, but rather because the
TH desugarer works on GhcRn rather than GhcTc (See GHC.HsToCore.Quote)
|
|
|
|
|
|
|
|
|
|
| |
When HsExpr GhcTc, the HsBracket constructor should hold a HsBracket
GhcRn, rather than an HsBracket GhcTc.
We make use of the HsBracket p extension constructor (XBracket
(XXBracket p)) to hold an HsBracket GhcRn when the pass is GhcTc
See !4782 https://gitlab.haskell.org/ghc/ghc/-/merge_requests/4782
|
| |
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Previously, we let `Unboxed` win in `lubBoxity`, which is unsoundly optimistic
in terms ob Boxity analysis. "Unsoundly" in the sense that we sometimes unbox
parameters that we better shouldn't unbox. Examples are #18907 and T19871.absent.
Until now, we thought that this hack pulled its weight becuase it worked around
some shortcomings of the phase separation between Boxity analysis and CPR
analysis. But it is a gross hack which caused regressions itself that needed all
kinds of fixes and workarounds. See for example #20767. It became impossible to
work with in !7599, so I want to remove it.
For example, at the moment, `lubDmd B dmd` will not unbox `dmd`,
but `lubDmd A dmd` will. Given that `B` is supposed to be the bottom element of
the lattice, it's hardly justifiable to get a better demand when `lub`bing with
`A`.
The consequence of letting `Boxed` win in `lubBoxity` is that we *would* regress
#2387, #16040 and parts of #5075 and T19871.sumIO, until Boxity and CPR
are able to communicate better. Fortunately, that is not the case since I could
tweak the other source of optimism in Boxity analysis that is described in
`Note [Unboxed demand on function bodies returning small products]` so that
we *recursively* assume unboxed demands on function bodies returning small
products. See the updated Note.
`Note [Boxity for bottoming functions]` describes why we need bottoming
functions to have signatures that say that they deeply unbox their arguments.
In so doing, I had to tweak `finaliseArgBoxities` so that it will never unbox
recursive data constructors. This is in line with our handling of them in CPR.
I updated `Note [Which types are unboxed?]` to reflect that.
In turn we fix #21119, #20767, #18907, T19871.absent and get a much simpler
implementation (at least to think about). We can also drop the very ad-hoc
definition of `deferAfterPreciseException` and its Note in favor of the
simple, intuitive definition we used to have.
Metric Decrease:
T16875
T18223
T18698a
T18698b
hard_hole_fits
Metric Increase:
LargeRecord
MultiComponentModulesRecomp
T15703
T8095
T9872d
Out of all the regresions, only the one in T9872d doesn't vanish in a perf
build, where the compiler is bootstrapped with -O2 and thus SpecConstr.
Reason for regressions:
* T9872d is due to `ty_co_subst` taking its `LiftingContext` boxed.
That is because the context is passed to a function argument, for
example in `liftCoSubstTyVarBndrUsing`.
* In T15703, LargeRecord and T8095, we get a bit more allocations in
`expand_syn` and `piResultTys`, because a `TCvSubst` isn't unboxed.
In both cases that guards against reboxing in some code paths.
* The same is true for MultiComponentModulesRecomp, where we get less unboxing
in `GHC.Unit.Finder.$wfindInstalledHomeModule`. In a perf build, allocations
actually *improve* by over 4%!
Results on NoFib:
--------------------------------------------------------------------------------
Program Allocs Instrs
--------------------------------------------------------------------------------
awards -0.4% +0.3%
cacheprof -0.3% +2.4%
fft -1.5% -5.1%
fibheaps +1.2% +0.8%
fluid -0.3% -0.1%
ida +0.4% +0.9%
k-nucleotide +0.4% -0.1%
last-piece +10.5% +13.9%
lift -4.4% +3.5%
mandel2 -99.7% -99.8%
mate -0.4% +3.6%
parser -1.0% +0.1%
puzzle -11.6% +6.5%
reverse-complem -3.0% +2.0%
scs -0.5% +0.1%
sphere -0.4% -0.2%
wave4main -8.2% -0.3%
--------------------------------------------------------------------------------
Summary excludes mandel2 because of excessive bias
Min -11.6% -5.1%
Max +10.5% +13.9%
Geometric Mean -0.2% +0.3%
--------------------------------------------------------------------------------
Not bad for a bug fix.
The regression in `last-piece` could become a win if SpecConstr would work on
non-recursive functions. The regression in `fibheaps` is due to
`Note [Reboxed crud for bottoming calls]`, e.g., #21128.
|
|
|
|
|
|
| |
We still don't allow negative overloaded patterns. Earler all negative patterns
were treated as negative overloaded patterns. Now, we expliclty check the
extension field to see if the pattern is actually a negative overloaded pattern
|
|
|
|
|
|
| |
- Use extension suggestion hints instead of suggesting extensions in the
error message body for several FFI errors.
- Adds a test case for `TcRnForeignImportPrimExtNotSet`
|
|
|
|
| |
Converts all uses of 'TcRnUnknownMessage' to proper diagnostics.
|
|
|
|
|
|
|
|
|
|
| |
* Users can define their own (~) type operator
* Haddock can display documentation for the built-in (~)
* New transitional warnings implemented:
-Wtype-equality-out-of-scope
-Wtype-equality-requires-operators
Updates the haddock submodule.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
As `Note [Demand analysis for recursive data constructors]` describes, we now
refrain from unboxing recursive data type arguments, for two reasons:
1. Relating to run/alloc perf: Similar to
`Note [CPR for recursive data constructors]`, it seldomly improves run/alloc
performance if we just unbox a finite number of layers of a potentially huge
data structure.
2. Relating to ghc/alloc perf: Inductive definitions on single-product
recursive data types like the one in T11545 will (diverge, and) have very
deep demand signatures before any other abortion mechanism in Demand
analysis is triggered. That leads to great and unnecessary churn on Demand
analysis when ultimately we will never make use of any nested strictness
information anyway.
Conclusion: Discard nested demand and boxity information on such recursive types
with the help of `Note [Detecting recursive data constructors]`.
I also implemented `GHC.Types.Unique.MemoFun.memoiseUniqueFun` in order to avoid
the overhead of repeated calls to `GHC.Core.Opt.WorkWrap.Utils.isRecDataCon`.
It's nice and simple and guards against some smaller regressions in T9233 and
T16577.
ghc/alloc performance-wise, this patch is a very clear win:
Test Metric value New value Change
---------------------------------------------------------------------------------------
LargeRecord(normal) ghc/alloc 6,141,071,720 6,099,871,216 -0.7%
MultiLayerModulesTH_OneShot(normal) ghc/alloc 2,740,973,040 2,705,146,640 -1.3%
T11545(normal) ghc/alloc 945,475,492 85,768,928 -90.9% GOOD
T13056(optasm) ghc/alloc 370,245,880 326,980,632 -11.7% GOOD
T18304(normal) ghc/alloc 90,933,944 76,998,064 -15.3% GOOD
T9872a(normal) ghc/alloc 1,800,576,840 1,792,348,760 -0.5%
T9872b(normal) ghc/alloc 2,086,492,432 2,073,991,848 -0.6%
T9872c(normal) ghc/alloc 1,750,491,240 1,737,797,832 -0.7%
TcPlugin_RewritePerf(normal) ghc/alloc 2,286,813,400 2,270,957,896 -0.7%
geo. mean -2.9%
No noteworthy change in run/alloc either.
NoFib results show slight wins, too:
--------------------------------------------------------------------------------
Program Allocs Instrs
--------------------------------------------------------------------------------
constraints -1.9% -1.4%
fasta -3.6% -2.7%
reverse-complem -0.3% -0.9%
treejoin -0.0% -0.3%
--------------------------------------------------------------------------------
Min -3.6% -2.7%
Max +0.1% +0.1%
Geometric Mean -0.1% -0.1%
Metric Decrease:
T11545
T13056
T18304
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
As #20837 pointed out, `isLiftedType_maybe` returned `Just False` in
many situations where it should return `Nothing`, because it didn't
take into account type families or type variables.
In this patch, we fix this issue. We rename `isLiftedType_maybe` to
`typeLevity_maybe`, which now returns a `Levity` instead of a boolean.
We now return `Nothing` for types with kinds of the form
`TYPE (F a1 ... an)` for a type family `F`, as well as
`TYPE (BoxedRep l)` where `l` is a type variable.
This fix caused several other problems, as other parts of the compiler
were relying on `isLiftedType_maybe` returning a `Just` value, and were
now panicking after the above fix. There were two main situations in
which panics occurred:
1. Issues involving the let/app invariant. To uphold that invariant,
we need to know whether something is lifted or not. If we get an
answer of `Nothing` from `isLiftedType_maybe`, then we don't know
what to do. As this invariant isn't particularly invariant, we
can change the affected functions to not panic, e.g. by behaving
the same in the `Just False` case and in the `Nothing` case
(meaning: no observable change in behaviour compared to before).
2. Typechecking of data (/newtype) constructor patterns. Some programs
involving patterns with unknown representations were accepted, such
as T20363. Now that we are stricter, this caused further issues,
culminating in Core Lint errors. However, the behaviour was
incorrect the whole time; the incorrectness only being revealed by
this change, not triggered by it.
This patch fixes this by overhauling where the representation
polymorphism involving pattern matching are done. Instead of doing
it in `tcMatches`, we instead ensure that the `matchExpected`
functions such as `matchExpectedFunTys`, `matchActualFunTySigma`,
`matchActualFunTysRho` allow return argument pattern types which
have a fixed RuntimeRep (as defined in Note [Fixed RuntimeRep]).
This ensures that the pattern matching code only ever handles types
with a known runtime representation. One exception was that
patterns with an unknown representation type could sneak in via
`tcConPat`, which points to a missing representation-polymorphism
check, which this patch now adds.
This means that we now reject the program in #20363, at least until
we implement PHASE 2 of FixedRuntimeRep (allowing type families in
RuntimeRep positions). The aforementioned refactoring, in which
checks have been moved to `matchExpected` functions, is a first
step in implementing PHASE 2 for patterns.
Fixes #20837
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
AbsBinds and ABExport both depended on the typechecker, and were thus
removed from the main AST Expr.
CollectPass now has a new function `collectXXHsBindsLR` used for the new
HsBinds extension point
Bumped haddock submodule to work with AST changes.
The removed Notes from Language.Haskell.Syntax.Binds were duplicated
(and not referenced) and the copies in GHC.Hs.Binds are kept (and
referenced there). (See #19252)
|
|
|
|
|
|
|
|
|
|
|
|
| |
Move GHC-specific comments from Language.Haskell.Syntax.Binds to
GHC.Hs.Binds
It looks like the Note was deleted but there were actually two copies of
it. L.H.S.B no longer references it, and GHC.Hs.Binds keeps an updated
copy. (See #19252)
There are other duplicated notes -- they will be fixed in the next
commit
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Issue #21150 shows that worker/wrapper allocated a worker function for a
function with multiple calls that said "called at most once" when the first
argument was absent. That's bad!
This patch makes it so that WW preserves at least one non-one-shot value lambda
(see `Note [Preserving float barriers]`) by passing around `void#` in place of
absent arguments.
Fixes #21150.
Since the fix is pretty similar to `Note [Protecting the last value argument]`,
I put the logic in `mkWorkerArgs`. There I realised (#21204) that
`-ffun-to-thunk` is basically useless with `-ffull-laziness`, so I deprecated
the flag, simplified and split into `needsVoidWorkerArg`/`addVoidWorkerArg`.
SpecConstr is another client of that API.
Fixes #21204.
Metric Decrease:
T14683
|
|
|
|
|
|
|
|
|
|
|
| |
Note [Weak loop breakers] explains why we need to track variables free
in RHS of rules. But we need to do this for /inactive/ rules as well
as active ones, unlike the rhs_fv_env stuff.
So we now have two fields in node Details, one for free vars of
active rules, and one for free vars of all rules.
This was shown up by #20820, which is now fixed.
|
| |
|
|
|
|
| |
This enables GHC to report more parse errors in a single pass.
|
|
|
|
|
| |
Use castFloatToWord32/castDoubleToWord64 in base to perform the
reinterpret cast.
|
|
|
|
|
|
|
| |
case
Otherwise the C compiler may complain "warning: non-void function does
not return a value in all control paths [-Wreturn-type]".
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Our memcpyish primop's type signatures doesn't match the C type
signatures. It's not a problem for typical archs, since their C ABI
permits dropping the result, but it doesn't work for wasm. The
previous logic would cast the memcpyish function pointer to an
incorrect type and perform an indirect call, which results in a
runtime trap on wasm.
The most straightforward fix is: don't emit EFF_ for memcpyish
functions. Since we don't want to include extra headers in .hc to
bring in their prototypes, we can just use the __builtin versions.
|
|
|
|
|
|
| |
Contrary to the legacy comment, the splitting didn't happen and we
ended up with a single StgWord64 literal in the output code! Let's
just do the splitting here.
|
|
|
|
| |
This used to been broken for little-endian targets.
|
| |
|
|
|
|
|
| |
FUN closures don't get tagged when evaluated. So no point in checking their
tags.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
This special logic has been part of GHC ever since template haskell was
introduced in 9af77fa423926fbda946b31e174173d0ec5ebac8.
It's hard to believe in any case that this special logic pays its way at
all. Given
* The list is out-of-date, which has potential to lead to miscompilation
when using "editline", which was removed in 2010 (46aed8a4).
* The performance benefit seems negligable as each load only happens
once anyway and packages specified by package flags are preloaded into
the linker state at the start of compilation.
Therefore we just remove this logic.
Fixes #19791
|
|
|
|
|
|
| |
As the `hlint` executable is only available in the linters image.
Fixes #21146.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Previously, there was an awful hack in `genInst` (now called `genInstBinds`
after this patch) where we had to return a continutation rather than directly
returning the bindings for a derived instance. This was done for staging
purposes, as we had to first infer the instance contexts for derived instances
and then feed these contexts into the continuations to ensure the generated
instance bindings had accurate instance contexts.
`Note [Staging of tcDeriving]` in `GHC.Tc.Deriving` described this confusing
state of affairs.
The root cause of this confusing design was the fact that `genInst` was trying
to generate instance bindings and associated type family instances for derived
instances simultaneously. This really isn't possible, however: as
`Note [Staging of tcDeriving]` explains, one needs to have access to the
associated type family instances before one can properly infer the instance
contexts for derived instances. The use of continuation-returning style was an
attempt to circumvent this dependency, but it did so in an awkward way.
This patch detangles this awkwardness by splitting up `genInst` into two
functions: `genFamInsts` (for associated type family instances) and
`genInstBinds` (for instance bindings). Now, the `tcDeriving` function calls
`genFamInsts` and brings all the family instances into scope before calling
`genInstBinds`. This removes the need for the awkward continuation-returning
style seen in the previous version of `genInst`, making the code easier to
understand.
There are some knock-on changes as well:
1. `hasStockDeriving` now needs to return two separate functions: one that
describes how to generate family instances for a stock-derived instance,
and another that describes how to generate the instance bindings. I factored
out this pattern into a new `StockGenFns` data type.
2. While documenting `StockGenFns`, I realized that there was some
inconsistency regarding which `StockGenFns` functions needed which
arguments. In particular, the function in `GHC.Tc.Deriv.Generics` which
generates `Rep(1)` instances did not take a `SrcSpan` like other `gen_*`
functions did, and it included an extra `[Type]` argument that was entirely
redundant. As a consequence, I refactored the code in
`GHC.Tc.Deriv.Generics` to more closely resemble other `gen_*` functions.
A happy result of all this is that all `StockGenFns` functions now take
exactly the same arguments, which makes everything more uniform.
This is purely a refactoring that should not have any effect on user-observable
behavior. The new design paves the way for an eventual fix for #20719.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
The containers bump reduced the size of the Data.IntMap.Internal.lookup
function so that it no longer experienced W/W. This means that the size
of lookupVarEnv increased over the inlining threshold and it wasn't
inlined into the hot code path in substTyVar.
See containers#821, #21159 and !7638 for some more explanation.
-------------------------
Metric Decrease:
LargeRecord
T12227
T13386
T15703
T18223
T5030
T8095
T9872a
T9872b
T9872c
TcPlugin_RewritePerf
-------------------------
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
When deriving a `Generic1` instance, we need to know what the last type
variable of a data type is. Previously, there were two mechanisms to determine
this information:
* `GenericKind_`, where `Gen1_` stored the last type variable of a data type
constructor (i.e., the `tyConTyVars`).
* `GenericKind_DC`, where `Gen1_DC` stored the last universally quantified
type variable in a data constructor (i.e., the `dataConUnivTyVars`).
These had different use cases, as `GenericKind_` was used for generating
`Rep(1)` instances, while `GenericKind_DC` was used for generating `from(1)`
and `to(1)` implementations. This was already a bit confusing, but things went
from confusing to outright wrong after !6976. This is because after !6976,
the `deriving` machinery stopped using `tyConTyVars` in favor of
`dataConUnivTyVars`. Well, everywhere with the sole exception of
`GenericKind_`, which still continued to use `tyConTyVars`. This lead to
disaster when deriving a `Generic1` instance for a GADT family instance, as
the `tyConTyVars` do not match the `dataConUnivTyVars`. (See #21185.)
The fix is to stop using `GenericKind_` and replace it with `GenericKind_DC`.
For the most part, this proves relatively straightforward. Some highlights:
* The `forgetArgVar` function was deleted entirely, as it no longer proved
necessary after `GenericKind_`'s demise.
* The substitution that maps from the last type variable to `Any` (see
`Note [Generating a correctly typed Rep instance]`) had to be moved from
`tc_mkRepTy` to `tc_mkRepFamInsts`, as `tc_mkRepTy` no longer has access to
the last type variable.
Fixes #21185.
|
|
|
|
|
| |
I've added an explicit mention of the invariants surrounding those. As well as adding
more direct cross references to the Strict Field Invariant.
|
|
|
|
| |
'no_instance_msg' and 'no_deduce_msg' were omitting the first wanted.
|
|
|
|
|
| |
Fix #21023 by always generalising top-level binding; change
the documentation of -XMonoLocalBinds to match.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
This patch does the following two things:
1. Fix the check in Core Lint to properly throw an error when it
comes across Float#/Double# literal patterns. The check
was incorrect before, because it expected the type to be
Float/Double instead of Float#/Double#.
2. Add an error in the parser when the user writes a floating-point
literal pattern such as `case x of { 2.0## -> ... }`.
Fixes #21115
|
| |
|
|
|
|
| |
Fixes #21154
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
This commit alters GenStgAlt from a type synonym to a Record with field
accessors. In pursuit of #21078, this is not a required change but cleans
up several areas for nicer code in the upcoming js-backend, and in GHC
itself.
GenStgAlt: 3-tuple -> record
Stg.Utils: GenStgAlt 3-tuple -> record
Stg.Stats: StgAlt 3-tuple --> record
Stg.InferTags.Rewrite: StgAlt 3-tuple -> record
Stg.FVs: GenStgAlt 3-tuple -> record
Stg.CSE: GenStgAlt 3-tuple -> record
Stg.InferTags: GenStgAlt 3-tuple --> record
Stg.Debug: GenStgAlt 3-tuple --> record
Stg.Lift.Analysis: GenStgAlt 3-tuple --> record
Stg.Lift: GenStgAlt 3-tuple --> record
ByteCode.Instr: GenStgAlt 3-tuple --> record
Stg.Syntax: add GenStgAlt helper functions
Stg.Unarise: GenStgAlt 3-tuple --> record
Stg.BcPrep: GenStgAlt 3-tuple --> record
CoreToStg: GenStgAlt 3-tuple --> record
StgToCmm.Expr: GenStgAlt 3-tuple --> record
StgToCmm.Bind: GenStgAlt 3-tuple --> record
StgToByteCode: GenStgAlt 3-tuple --> record
Stg.Lint: GenStgAlt 3-tuple --> record
Stg.Syntax: strictify GenStgAlt
GenStgAlt: add haddock, some cleanup
fixup: remove calls to pure, single ViewPattern
StgToByteCode: use case over viewpatterns
|
|
|
|
|
|
| |
More details in Note [coreView vs tcView]
Close #21092.
|
|
|
|
| |
Close #20231.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Don't instantiate type variables for :type in
`GHC.Tc.Gen.App.tcInstFun`, to avoid inconsistently instantianting
`r1` but not `r2` in the type
forall {r1} (a :: TYPE r1) {r2} (b :: TYPE r2). ...
This fixes #21088.
This patch also changes the primop pretty-printer to ensure
that we put all the inferred type variables first. For example,
the type of reallyUnsafePtrEquality# is now
forall {l :: Levity} {k :: Levity}
(a :: TYPE (BoxedRep l))
(b :: TYPE (BoxedRep k)).
a -> b -> Int#
This means we avoid running into issue #21088 entirely with
the types of primops. Users can still write a type signature where
the inferred type variables don't come first, however.
This change to primops had a knock-on consequence, revealing that
we were sometimes performing eta reduction on keepAlive#.
This patch updates tryEtaReduce to avoid eta reducing functions
with no binding, bringing it in line with tryEtaReducePrep,
and thus fixing #21090.
|
|
|
|
|
|
|
|
|
| |
After certain simplifier passes we end up with let bound type variables
which are immediately inlined in the next pass. The core diff utility
implemented by -dannot-lint failed to take these into account and
paniced.
Progress towards #20965
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
This patch introduces a new kind of metavariable, by adding the
constructor `ConcreteTv` to `MetaInfo`. A metavariable with
`ConcreteTv` `MetaInfo`, henceforth a concrete metavariable, can only
be unified with a type that is concrete (that is, a type that answers
`True` to `GHC.Core.Type.isConcrete`).
This solves the problem of dangling metavariables in `Concrete#`
constraints: instead of emitting `Concrete# ty`, which contains a
secret existential metavariable, we simply emit a primitive equality
constraint `ty ~# concrete_tv` where `concrete_tv` is a fresh concrete
metavariable.
This means we can avoid all the complexity of canonicalising
`Concrete#` constraints, as we can just re-use the existing machinery
for `~#`.
To finish things up, this patch then removes the `Concrete#` special
predicate, and instead introduces the special predicate `IsRefl#`
which enforces that a coercion is reflexive.
Such a constraint is needed because the canonicaliser is quite happy
to rewrite an equality constraint such as `ty ~# concrete_tv`, but
such a rewriting is not handled by the rest of the compiler currently,
as we need to make use of the resulting coercion, as outlined in the
FixedRuntimeRep plan.
The big upside of this approach (on top of simplifying the code)
is that we can now selectively implement PHASE 2 of FixedRuntimeRep,
by changing individual calls of `hasFixedRuntimeRep_MustBeRefl` to
`hasFixedRuntimeRep` and making use of the obtained coercion.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
This is a one line change. It is a fixup from MR!7325, was pointed out
in review of MR!7442, specifically: https://gitlab.haskell.org/ghc/ghc/-/merge_requests/7442#note_406581
The change removes isNCG check from cgTopBinding. Instead it changes the
type of binBlobThresh in DynFlags from Word to Maybe Word, where a Just
0 or a Nothing indicates an infinite threshold and thus the disable
CmmFileEmbed case in the original check.
This improves the cohesion of the module because more NCG related
Backend stuff is moved into, and checked in, StgToCmm.Config. Note, that
the meaning of a Just 0 or a Nothing in binBlobThresh is indicated in a
comment next to its field in GHC.StgToCmm.Config.
DynFlags: binBlobThresh: Word -> Maybe Word
StgToCmm.Config: binBlobThesh add not ncg check
DynFlags.binBlob: move Just 0 check to dflags init
StgToCmm.binBlob: only check isNCG, Just 0 check to dflags
StgToCmm.Config: strictify binBlobThresh
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
This adds a number of changes to ticky-ticky profiling.
When an executable is profiled with IPE profiling it's now possible to
associate id-related ticky counters to their source location.
This works by emitting the info table address as part of the counter
which can be looked up in the IPE table.
Add a `-ticky-ap-thunk` flag. This flag prevents the use of some standard thunks
which are precompiled into the RTS. This means reduced cache locality
and increased code size. But it allows better attribution of execution
cost to specific source locations instead of simple attributing it to
the standard thunk.
ticky-ticky now uses the `arg` field to emit additional information
about counters in json format. When ticky-ticky is used in combination
with the eventlog eventlog2html can be used to generate a html table
from the eventlog similar to the old text output for ticky-ticky.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
We were not looking through floatable ticks when collecting arguments in
Core Lint, which caused `checkCanEtaExpand` to fail on something like:
```haskell
reallyUnsafePtrEquality
= \ @a ->
(src<loc> reallyUnsafePtrEquality#)
@Lifted @a @Lifted @a
```
We fix this by using `collectArgsTicks tickishFloatable` instead of
`collectArgs`, to be consistent with the behaviour of eta expansion
outlined in Note [Eta expansion and source notes] in GHC.Core.Opt.Arity.
Fixes #21152.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
As noted in #21071 we were missing adding this edge so there were
situations where the .hs file would get compiled before the .hs-boot
file which leads to issues with -j.
I fixed this properly by adding the edge in downsweep so the definition
of nodeDependencies can be simplified to avoid adding this dummy edge
in.
There are plenty of tests which seem to have these redundant boot files
anyway so no new test. #21094 tracks the more general issue of
identifying redundant hs-boot and SOURCE imports.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
In the case when we tell moduleGraphNodes to drop hs-boot files the idea
is to collapse hs-boot files into their hs file nodes. In the old code
* nodeDependencies changed edges from IsBoot to NonBoot
* moduleGraphNodes just dropped boot file nodes
The net result is that any dependencies of the hs-boot files themselves
were dropped. The correct thing to do is
* nodeDependencies changes edges from IsBoot to NonBoot
* moduleGraphNodes merges dependencies of IsBoot and NonBoot nodes.
The result is a properly quotiented dependency graph which contains no
hs-boot files nor hs-boot file edges.
Why this didn't cause endless issues when compiling with boot files, we
will never know.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
These flags were added to help with the high linking cost of the old
split-objs mode. Now we are using split-sections these flags appear to
make no difference to memory usage or time taken to link.
I tested various configurations linking together the ghc library with
-split-sections enabled.
| linker | time (s) |
| ------ | ------ |
| gold | 0.95 |
| ld | 1.6 |
| ld (hash-size = 31, reduce-memory-overheads) | 1.6 |
| ldd | 0.47 |
Fixes #20967
|