| Commit message (Collapse) | Author | Age | Files | Lines |
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
This patch adds a PromotionFlag field to HsOpTy, which is used
in pretty-printing and when determining whether to emit warnings
with -fwarn-unticked-promoted-constructors.
This allows us to correctly report tick-related warnings for things
like:
type A = Int : '[]
type B = [Int, Bool]
Updates haddock submodule
Fixes #19984
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
How things should work:
* -i is the search path for source files
* -hidir explicitly sets the search path for interface files and the output location for interface files.
* -odir sets the search path and output location for object files.
Before in one shot mode we would look for the interface file in the
search locations given by `-i`, but then set the path to be in the
`hidir`, so in unusual situations the finder could find an interface
file in the `-i` dir but later fail because it tried to read the
interface file from the `-hidir`.
A bug identified by #20569
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
In the past I improved the part of -Wunused-packages which found which
packages were used. Now I improve the part which detects which ones were
specified. The key innovation is to use the explicitUnits field from
UnitState which has the result of resolving the package flags, so we
don't need to mess about with the flag arguments from DynFlags anymore.
The output now always includes the package name and version (and the
flag which exposed it).
```
The following packages were specified via -package or -package-id flags,
but were not needed for compilation:
- bytestring-0.11.2.0 (exposed by flag -package bytestring)
- ghc-9.3 (exposed by flag -package ghc)
- process-1.6.13.2 (exposed by flag -package process)
```
Fixes #21307
|
|
|
|
|
| |
Users are supposed to import GHC.Exts rather than GHC.Prim.
Part of #18749.
|
|
|
|
|
|
|
| |
When pretty printing a HsCmdLam with more than one argument, GHC
panicked because of a missing case. This fixes that.
Closes #21300
|
| |
|
|
|
|
|
|
|
|
|
|
|
| |
- Remove unused functions exprToCoercion_maybe, applyTypeToArg,
typeMonoPrimRep_maybe, runtimeRepMonoPrimRep_maybe.
- Replace orValid with a simpler check
- Use splitAtList in applyTysX
- Remove calls to extra_clean in the testsuite; it does not do anything.
Metric Decrease:
T18223
|
|
|
|
| |
Closes #20640
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
The `ty_co_match` function ignored the implicit RuntimeRep coercions
that occur in a `FunCo`. Even though a comment explained that this
should be fine, #21205 showed that it could result in discarding a
RuntimeRep coercion, and thus discarding an important cast entirely.
With this patch, we first match the kinds in `ty_co_match`.
Fixes #21205
-------------------------
Metric Increase:
T12227
T18223
-------------------------
|
|
|
|
|
|
|
|
| |
Previously, the warnings and errors were given and returned as a tuple
(Messages PsWarnings, Messages PsErrors). Now, it's just PsMessages.
This, together with the HsParsedModule the parser plugin gets and
returns, has been wrapped up as ParsedResult.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Fixes this failure:
=====> 1 of 1 [0, 0, 0]
T13366(normal) 1 of 1 [0, 0, 0] Compile failed (exit code 1) errors were:
<no location info>: error:
user specified .o/.so/.DLL could not be loaded (File not found)
Whilst trying to load: (dynamic) stdc++
Additional directories searched: (none)
*** unexpected failure for T13366(normal)
|
|
|
|
|
|
|
|
|
|
|
| |
Previously, when the parser produced non-fatal errors (i.e. it produced
errors but the 'PState' is 'POk'), compilation would be aborted before
the 'parsedResultAction' of any plugin was invoked. This commit changes
that, so that such that 'parsedResultAction' gets collections of
warnings and errors as argument, and must return them after potentially
modifying them.
Closes #20803
|
|
|
|
| |
Fixes #21306
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
The code
let ;x =1
Captures the semicolon annotation, but did not widen the anchor in the
ValBinds.
Fix that.
Closes #20247
|
|
|
|
| |
Close #21208.
|
|
|
|
| |
Fixes #17830
|
| |
|
|
|
|
|
|
|
|
|
|
|
|
| |
A new pragma, `OPAQUE`, that ensures that every call of a named
function annotated with an `OPAQUE` pragma remains a call of that
named function, not some name-mangled variant.
Implements GHC proposal 0415:
https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0415-opaque-pragma.rst
This commit also updates the haddock submodule to handle the newly
introduced lexer tokens corresponding to the OPAQUE pragma.
|
|
|
|
|
|
|
| |
These dependencies would affect the demand signature depending on
various rules and so on.
Fixes #21271
|
|
|
|
|
|
|
|
| |
This test checks that you are allowed to explicitly supply object files
for dependencies even if you haven't got the shared object for that
library yet.
Fixes #21035
|
|
|
|
|
|
|
|
|
|
|
|
| |
Partial FUN apps like `(->) Bool` aren't detected by `splitFunTy_maybe`.
A silly oversight that is easily fixed by replacing `splitFunTy_maybe` with a
guard in the `splitTyConApp_maybe` case.
But fortunately, Simon nudged me into rewriting the whole `isRecDataCon`
function in a way that makes it much shorter and hence clearer which DataCons
are actually considered as recursive.
Fixes #21265.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
As explained in `Note [Gathering and simplifying constraints for DeriveAnyClass]`
in `GHC.Tc.Deriv.Infer`, `DeriveAnyClass` infers instance contexts by emitting
implication constraints. Previously, these implication constraints were
constructed by hand. This is a terribly trick thing to get right, as it
involves a delicate interplay of skolemisation, metavariable instantiation, and
`TcLevel` bumping. Despite much effort, we discovered in #20719 that the
implementation was subtly incorrect, leading to valid programs being rejected.
While we could scrutinize the code that manually constructs implication
constraints and repair it, there is a better, less error-prone way to do
things. After all, the heart of `DeriveAnyClass` is generating code which
fills in each class method with defaults, e.g., `foo = $gdm_foo`. Typechecking
this sort of code is tantamount to calling `tcSubTypeSigma`, as we much ensure
that the type of `$gdm_foo` is a subtype of (i.e., more polymorphic than) the
type of `foo`. As an added bonus, `tcSubTypeSigma` is a battle-tested function
that handles skolemisation, metvariable instantiation, `TcLevel` bumping, and
all other means of tricky bookkeeping correctly.
With this insight, the solution to the problems uncovered in #20719 is simple:
use `tcSubTypeSigma` to check if `$gdm_foo`'s type is a subtype of `foo`'s
type. As a side effect, `tcSubTypeSigma` will emit exactly the implication
constraint that we were attempting to construct by hand previously. Moreover,
it does so correctly, fixing #20719 as a consequence.
This patch implements the solution thusly:
* The `PredSpec` data type (previously named `PredOrigin`) is now split into
`SimplePredSpec`, which directly stores a `PredType`, and `SubTypePredSpec`,
which stores the actual and expected types in a subtype check.
`SubTypePredSpec` is only used for `DeriveAnyClass`; all other deriving
strategies use `SimplePredSpec`.
* Because `tcSubTypeSigma` manages the finer details of type variable
instantiation and constraint solving under the hood, there is no longer any
need to delicately split apart the method type signatures in
`inferConstraintsAnyclass`. This greatly simplifies the implementation of
`inferConstraintsAnyclass` and obviates the need to store skolems,
metavariables, or given constraints in a `ThetaSpec` (previously named
`ThetaOrigin`). As a bonus, this means that `ThetaSpec` now simply becomes a
synonym for a list of `PredSpec`s, which is conceptually much simpler than it
was before.
* In `simplifyDeriv`, each `SubTypePredSpec` results in a call to
`tcSubTypeSigma`. This is only performed for its side effect of emitting
an implication constraint, which is fed to the rest of the constraint solving
machinery in `simplifyDeriv`. I have updated
`Note [Gathering and simplifying constraints for DeriveAnyClass]` to explain
this in more detail.
To make the changes in `simplifyDeriv` more manageable, I also performed some
auxiliary refactoring:
* Previously, every iteration of `simplifyDeriv` was skolemising the type
variables at the start, simplifying, and then performing a reverse
substitution at the end to un-skolemise the type variables. This is not
necessary, however, since we can just as well skolemise once at the
beginning of the `deriving` pipeline and zonk the `TcTyVar`s after
`simplifyDeriv` is finished. This patch does just that, having been made
possible by prior work in !7613. I have updated `Note [Overlap and deriving]`
in `GHC.Tc.Deriv.Infer` to explain this, and I have also left comments on
the relevant data structures (e.g., `DerivEnv` and `DerivSpec`) to explain
when things might be `TcTyVar`s or `TyVar`s.
* All of the aforementioned cleanup allowed me to remove an ad hoc
deriving-related in `checkImplicationInvariants`, as all of the skolems in
a `tcSubTypeSigma`–produced implication constraint should now be `TcTyVar`
at the time the implication is created.
* Since `simplifyDeriv` now needs a `SkolemInfo` and `UserTypeCtxt`, I have
added `ds_skol_info` and `ds_user_ctxt` fields to `DerivSpec` to store these.
Similarly, I have also added a `denv_skol_info` field to `DerivEnv`, which
ultimately gets used to initialize the `ds_skol_info` in a `DerivSpec`.
Fixes #20719.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Ticket #21110 points out that -Wunused-packages behaves a bit unusually
in GHCi. Now we define the semantics for -Wunused-packages in
interactive mode as follows:
* If you use -Wunused-packages on an initial load then the warning is reported.
* If you explicitly set -Wunused-packages on the command line then the
warning is displayed (until it is disabled)
* If you then subsequently modify the set of available targets by using
:load or :cd (:cd unloads everything) then the warning is (silently)
turned off.
This means that every :r the warning is printed if it's turned on (but you did ask for it).
Fixes #21110
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Names appearing in Haddock docstrings are lexed and renamed like any other names
appearing in the AST. We currently rename names irrespective of the namespace,
so both type and constructor names corresponding to an identifier will appear in
the docstring. Haddock will select a given name as the link destination based on
its own heuristics.
This patch also restricts the limitation of `-haddock` being incompatible with
`Opt_KeepRawTokenStream`.
The export and documenation structure is now computed in GHC and serialised in
.hi files. This can be used by haddock to directly generate doc pages without
reparsing or renaming the source. At the moment the operation of haddock
is not modified, that's left to a future patch.
Updates the haddock submodule with the minimum changes needed.
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
This patch improves code generation for derived Eq instances.
The idea is to use 'dataToTag' to evaluate both arguments.
This allows to 'short-circuit' when tags do not match.
Unfortunately, inner evals are still present when we branch
on tags. This is due to the way 'dataToTag#' primop
evaluates its argument in the code generator. #21207 was
created to explore further optimizations.
Metric Decrease:
LargeRecord
|
|
|
|
|
|
|
|
| |
The pretty printer for regular data types already accounted for these,
and had some duplication with the newtype pretty printer.
Factoring the logic out into a common function and using it for both
newtypes and data declarations is enough to fix the bug.
|
| |
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
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
-------------------------
|
| |
|
| |
|
|
|
|
|
|
|
|
|
| |
This problem was due to a bug in cloneWanted, which was incorrectly
creating a coercion hole to hold an evidence variable.
This bug was introduced by 8bb52d91 and fixed in 81740ce8.
Fixes #21130
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
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)
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
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.
|
|
|
|
|
|
| |
The output of this test changes each time the containers submodule
version updates. It's easier to apply the version normaliser so that
the test checks that there is a version number, but not which one it is.
|
|
|
|
|
|
| |
GHC Proposal #371 requires TypeOperators to use type equality a~b.
This submodule update pulls in the appropriate forward-compatibility
changes in 'libraries/containers' and 'libraries/exceptions'
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
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.
|
| |
|
|
|
|
| |
'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.
|