| Commit message (Collapse) | Author | Age | Files | Lines |
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
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.
|
| |
|
|
|
|
|
|
|
| |
Previously the default definition was used, which involved allocating
intermediate Natural values.
Fixes #21173.
|
|
|
|
| |
'no_instance_msg' and 'no_deduce_msg' were omitting the first wanted.
|
| |
|
|
|
|
|
| |
And adds a check to make sure we are not accidently settings
BIN_DIST_PREP_TAR_COMP when using hadrian.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
This is the first step in converting all the CI configs to use hadrian
rather than make. (#21129)
The metrics increase due to hadrian using --hyperlinked-source for
haddock builds. (See #21156)
-------------------------
Metric Increase:
haddock.Cabal
haddock.base
haddock.compiler
-------------------------
|
|
|
|
|
| |
This can be useful to build a `perf+assertions` build or even better
`default+no_profiled_libs+omit_pragmas+assertions`.
|
|
|
|
|
| |
Fix #21023 by always generalising top-level binding; change
the documentation of -XMonoLocalBinds to match.
|
|
|
|
| |
It was hanging and timing out on OpenBSD before.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
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
|
|
|
|
|
|
|
|
| |
CLC proposal: https://github.com/haskell/core-libraries-committee/issues/33
The instances had `fail` implemented in terms of `error`, whereas the
idea of the `MonadFail` class is that the `fail` method should be
implemented in terms of the monad itself.
|
| |
|
|
|
|
|
| |
Most (all) of the exports are re-exported from
the preferable Data.Bits.
|
|
|
|
|
|
|
|
|
| |
We no longer require LiberalTypeSynonyms to use 'forall' or an unboxed
tuple in a synonym.
I also removed that kind checking before expanding synonyms "could be changed".
This was true when type synonyms were thought of macros, but with
the extensions such as SAKS or matchability I don't see it changing.
|
|
|
|
| |
Fixes #21154
|
|
|
|
| |
Fixes #20100
|
|
|
|
|
|
| |
[skip ci]
Fixes #15429
|
|
|
|
|
|
| |
For example, running the `slow-validate` flavour would incorrectly run
the T16135 test which would fail with an assertion error, despite the
fact that is should be skipped when we have a debug compiler.
|
|
|
|
| |
Taken froù!3658
|
| |
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
The default instance leads to an infinite loop.
bisequenceA is defined in terms of bisquence which is defined in terms
of bitraverse.
```
bitraverse f g
= (defn of bitraverse)
bisequenceA . bimap f g
= (defn of bisequenceA)
bitraverse id id . bimap f g
= (defn of bitraverse)
...
```
Any instances defined without an explicitly implementation are currently
broken, therefore removing it will alert users to an issue in their
code.
CLC issue: https://github.com/haskell/core-libraries-committee/issues/47
Fixes #20329 #18901
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
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.
|
|
|
|
|
| |
It seems like a commented out section of code was accidentally included
in the docstring for a field.
|
| |
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
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
|
|
|
|
|
|
|
|
| |
Remove these smart constructors for these reasons:
* mkLocalClosureTableLabel : Does the same as the non-local variant.
* mkLocalClosureLabel : Does the same as the non-local variant.
* mkLocalInfoTableLabel : Decide if we make a local label based on the name
and just use mkInfoTableLabel everywhere.
|
|
|
|
|
|
|
| |
If a setting is missing from the configuration file it's likely the user
needs to reconfigure.
Fixes #20476
|
|
|
|
|
| |
This does not fix all hlint issues as the criticised index and
length expressions seem to be fine in context.
|
|
|
|
| |
fix #18963
|
| |
|
| |
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
This patch adds a check to Core Lint, checkCanEtaExpand,
which ensures that primops and other wired-in functions with
no binding such as unsafeCoerce#, oneShot, rightSection...
can always be eta-expanded, by checking that the remaining
argument types have a fixed RuntimeRep.
Two subtleties came up:
- the notion of arity in Core looks through newtypes, so we may
need to unwrap newtypes in this check,
- we want to avoid calling hasNoBinding on something whose unfolding
we are in the process of linting, as this would cause a loop;
to avoid this we add some information to the Core Lint environment
that holds this information.
Fixes #20480
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
The code in tcAnonWildCardOcc assumed that it could never encounter
anonymous wildcards in illegal positions, because the renamer would
have ruled them out. However, it's possible to sneak past the checks
in the renamer by using Template Haskell. It isn't possible to simply
pass on additional information when renaming Template Haskell
brackets, because we don't know in advance in what context the bracket
will be spliced in (see test case T15433b). So we accept that we might
encounter these bogus wildcards in the typechecker and throw the
appropriate error.
This patch also migrates the error messages for illegal wildcards in
types to use the diagnostic infrastructure.
Fixes #15433
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Essentially we apply the identity:
> lookupNameEnv n (plusNameEnv_C (++) rb1 rb2)
> = lookupNameEnv n rb1 ++ lookupNameEnv n rb2
The latter being more efficient as we don't construct an intermediate
map.
This is now quite important as each time we try and apply rules we need
to combine the current EPS RuleBase with the HPT and ModGuts rule bases.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
As the prescient (now deleted) note warns in simplifyPgmIO we have to be a bit careful
about when we gather rules from the EPS so that we get the rules for
imported bindings.
```
-- Get any new rules, and extend the rule base
-- See Note [Overall plumbing for rules] in GHC.Core.Rules
-- We need to do this regularly, because simplification can
-- poke on IdInfo thunks, which in turn brings in new rules
-- behind the scenes. Otherwise there's a danger we'll simply
-- miss the rules for Ids hidden inside imported inlinings
```
Given the previous commit, the loading of unfoldings is now even more
delayed so we need to be more careful to read the EPS rule base closer to the point
where we decide to try rules.
Without this fix GHC performance regressed by a noticeably amount
because the `zip` rule was not brought into scope eagerly enough which
led to a further series of unfortunate events in the simplifer which
tipped `substTyWithCoVars` over the edge of the size threshold, stopped
it being inlined and increased allocations by 10% in some cases.
Furthermore, this change is noticeably in the testsuite as it changes
T19790 so that the `length` rules from GHC.List fires earlier.
-------------------------
Metric Increase:
T9961
-------------------------
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
The old logic was unecessarily strict in loading unfoldings because when
reading the unfolding we would case on the result of attempting to load
the template before commiting to which type of unfolding we were
producing. Hence trying to inspect any of the information about an
unfolding would force the template to be loaded.
This also removes a potentially hard to discover bug where if the
template failed to be typechecked for some reason then we would just not
return an unfolding. Instead we now panic so these bad situations which
should never arise can be identified.
|
|
|
|
|
|
| |
Now it takes a better account of precise vs. imprecise exception semantics.
Fixes #19854.
|
|
|
|
| |
This is used by the JS backend for serialization.
|