| Commit message (Collapse) | Author | Age | Files | Lines |
|
|
|
|
| |
As noted in #18391, foreignInterruptible fails pretty regularly under
GHCi.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
When combining
Inert: [W] C ty1 ty2
Work item: [D] C ty1 ty2
we were simply discarding the Derived one. Not good! We should turn
the inert back into [WD] or keep both. E.g. fundeps work only on
Derived (see isImprovable).
This little patch fixes it. The bug is hard to tickle, but #19315 did so.
The fix is a little messy (see Note [KeepBoth] plus the change in
addDictCt), but I am disinclined to refine it further because it'll
all be swept away when we Kill Deriveds.
|
| |
|
|
|
|
|
|
|
|
|
|
|
|
| |
This adds a new heuristic, controllable via two new flags to
better tune inlining behaviour.
The new flags are -funfolding-case-threshold and
-funfolding-case-scaling which are document both
in the user guide and in
Note [Avoid inlining into deeply nested cases].
Co-authored-by: Andreas Klebinger <klebinger.andreas@gmx.at>
|
| |
|
|
|
|
|
|
|
| |
Commit 65721691ce9c (Improve inference with linear types, !4632)
fixed the bug.
Closes #18736.
|
|
|
|
|
|
|
|
| |
This small patch makes pattern synonyms play nicely with CallStack
constraints, using logic explained in GHC.Tc.Gen.Pat
Note [Call-stack tracing of pattern synonyms]
Fixes #19289
|
|
|
|
|
|
|
|
|
|
| |
The fix for #17958, implemented in MR !2952, introduced a small bug
in GHC.Core.TyCon.expandSynTyCon_maybe, in the case of under-saturated
type synonyms.
This MR fixes the bug, very easy.
Fixes #19279
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Co-authored-by: Rinat Stryungis <rinat.stryungis@serokell.io>
Implement GHC Proposal #387
* Parse char literals 'x' at the type level
* New built-in type families CmpChar, ConsSymbol, UnconsSymbol
* New KnownChar class (cf. KnownSymbol and KnownNat)
* New SomeChar type (cf. SomeSymbol and SomeNat)
* CharTyLit support in template-haskell
Updated submodules: binary, haddock.
Metric Decrease:
T5205
haddock.base
Metric Increase:
Naperian
T13035
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
See T19264 for a tricky corner case when explicitly importing
GHC.Num.BigNat and another module. With -dynamic-too, the FinderCache
contains paths for non-dynamic interfaces so they must be loaded first,
which is usually the case, except for some interfaces loaded in the
backend (e.g. in CorePrep).
So we must run the backend for the non-dynamic way first for
-dynamic-too to work as it is but I broke this invariant in
c85f4928d4dbb2eb2cf906d08bfe7620d6f04ca5 by mistakenly making the
backend run for the dynamic way first.
|
|
|
|
|
|
| |
The motivation is given in Note [tcFamTyPats: zonking the result kind].
Fixes #19250 -- the fix is easy.
|
| |
|
| |
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
* disable idle GC which has a big impact on time measures
* use average measures (before and after event registration)
* use warmup measures (for some reason the first measure of a batch
seems to be often quite different from the others)
* drop the division by monotonic clock time: this clock is impacted by
the load of the runner. We only want to measure the time spent in the
RTS while the mutator is idle so I don't understand why it was used.
|
|
|
|
|
|
|
|
|
|
|
|
| |
This commit also consolidates documentation in the user
manual around UndecidableSuperClasses, UndecidableInstances,
and FlexibleContexts.
Close #19186.
Close #19187.
Test case: typecheck/should_compile/T19186,
typecheck/should_fail/T19187{,a}
|
| |
|
| |
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
The `Applicative` instance is the most important one (for
array/vector/sequence indexing purposes), but it deserves
all the usual ones.
T12545 does silly 1% wibbles both ways, it seems, maybe depending
on architecture.
Metric Increase:
T12545
Metric Decrease:
T12545
|
|
|
|
|
|
| |
With this change, the type/kind of an object as well as it's category
and definition site are added to the output of the :doc command for each
object matching the argument string.
|
|
|
|
|
|
|
|
|
|
| |
It is confusing that it defaults to two different things depending on
whether we are in the profiling way or not.
Use -hc if you have a profiling build
Use -hT if you have a normal build
Fixes #19031
|
|
|
|
|
|
| |
Thery is still, in my view, far too numerous, but I believe this won't
be too hard to improve upon. At the very lease, we can always add more
extension points!
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
----------------
What:
There are two splits.
The first spit is:
- `Language.Haskell.Syntax.Extension`
- `GHC.Hs.Extension`
where the former now just contains helpers like `NoExtCon` and all the
families, and the latter is everything having to do with `GhcPass`.
The second split is:
- `Language.Haskell.Syntax.<mod>`
- `GHC.Hs.<mod>`
Where the former contains all the data definitions, and the few helpers
that don't use `GhcPass`, and the latter contains everything else. The
second modules also reexport the former.
----------------
Why:
See the issue for more details, but in short answer is we're trying to
grasp at the modularity TTG is supposed to offer, after a long time of
mainly just getting the safety benefits of more complete pattern
matching on the AST.
Now, we have an AST datatype which, without `GhcPass` is decently
stripped of GHC-specific concerns. Whereas before, not was it
GHC-specific, it was aware of all the GHC phases despite the
parameterization, with the instances and parametric data structure
side-by-side.
For what it's worth there are also some smaller, imminent benefits:
- The latter change also splits a strongly connected component in two,
since none of the `Language.Haskell.Syntax.*` modules import the older
ones.
- A few TTG violations (Using GhcPass directly in the AST) in `Expr` are
now more explicitly accounted for with new type families to provide the
necessary indirection.
-----------------
Future work:
- I don't see why all the type families should live in
`Language.Haskell.Syntax.Extension`. That seems anti-modular for
little benefit. All the ones used just once can be moved next to the
AST type they serve as an extension point for.
- Decide what to do with the `Outputable` instances. Some of these are
no orphans because they referred to `GhcPass`, and had to be moved. I
think the types could be generalized so they don't refer to `GhcPass`
and therefore can be moved back, but having gotten flak for increasing
the size and complexity types when generalizing before, I did *not*
want to do this.
- We should triage the remaining contents of `GHC.Hs.<mod>`. The
renaming helpers are somewhat odd for needing `GhcPass`. We might
consider if they are a) in fact only needed by one phase b) can be
generalized to be non-GhcPass-specific (e.g. take a callback rather
than GADT-match with `IsPass`) and then they can live in
`Language.Haskell.Syntax.<mod>`.
For more details, see
https://gitlab.haskell.org/ghc/ghc/-/wikis/implementing-trees-that-grow
Bumps Haddock submodule
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
* Implement constant folding rules for Natural (similar to Integer ones)
* Add mkCoreUbxSum helper in GHC.Core.Make
* Remove naturalTo/FromInt
We now only provide `naturalTo/FromWord` as
the semantics is clear (truncate/zero-extend). For Int we have to deal
with negative numbers (throw an exception? convert to Word
beforehand?) so we leave the decision about what to do to the caller.
Moreover, now that we have sized types (Int8#, Int16#, ..., Word8#,
etc.) there is no reason to bless `Int#` more than `Int8#` or `Word8#`
(for example).
* Replaced a few `()` with `(# #)`
|
| |
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
This has two fixes:
1. Take TyVarTvs into account in matchableGivens. This
fixes #19106.
2. Don't allow unifying alpha ~ Maybe alpha. This fixes
#19107.
This patch also removes a redundant Note and redirects
references to a better replacement.
Also some refactoring/improvements around the BindFun
in the pure unifier, which now can take the RHS type
into account.
Close #19106.
Close #19107.
Test case: partial-sigs/should_compile/T19106,
typecheck/should_compile/T19107
|
|
|
|
|
|
| |
Alt, AnnAlt and IfaceAlt were using triples. This patch makes them use
dedicated types so that we can try to make some fields strict (for
example) in the future.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Use `mkConstrTag` to explicitly pass the constructor tag instead of
using `mkConstr` which queries the tag at runtime by querying the index
of the constructor name (a string) in the list of constructor names.
Perf improvement:
T16577(normal) ghc/alloc 11325573876.0 9249786992.0 -18.3% GOOD
Thanks to @sgraf812 for suggesting an additional list fusion fix during
reviews.
Metric Decrease:
T16577
|
| |
|
| |
|
|
|
|
|
|
|
|
| |
This commit fixes 19 tests which were failing due to the use of
`consBag` / `snocBag`, which have been now replaced by `addMessage`.
This means that now GHC would output things in different order but
only for /diagnostics on the same line/, so this is just reflecting
that. The "normal" order of messages is still guaranteed.
|
|
|
|
|
|
|
|
|
| |
This commit paves the way to a richer and more structured representation
of GHC error messages, as per GHC proposal #306. More specifically
'Messages' from 'GHC.Types.Error' now gains an extra type parameter,
that we instantiate to 'ErrDoc' for now. Later, this will allow us to
replace ErrDoc with something more structure (for example messages
coming from the parser, the typechecker etc).
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
As #19142 showed, with -fdefer-type-errors we were allowing
compilation to proceed despite a fatal kind error. This patch
fixes it, as described in the new note in GHC.Tc.Solver,
Note [Wrapping failing kind equalities]
Also fixes #19158
Also when checking
default( ty1, ty2, ... )
only consider a possible default (C ty2) if ty2 is kind-compatible
with C. Previously we could form kind-incompatible constraints, with
who knows what kind of chaos resulting. (Actually, no chaos results,
but that's only by accident. It's plain wrong to form the constraint
(Num Either) for example.) I just happened to notice
this during fixing #19142.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Evidence binders were not collected by
GHC.HsToCore.Arrows.collectStmtBinders, hence bindings for dictionaries
were not taken into account while computing local variables in
statements. As a consequence we had a transformation similar to this:
data Point a where Point :: RealFloat a => a -> Point a
do
p -< ...
returnA -< ... (Point 0)
===> { Type-checking }
do
let $dRealFloat_xyz = GHC.Float.$fRealFloatFloat
p -< ...
returnA -< ... (Point $dRealFloat_xyz 0)
===> { Arrows HsToCore }
first ...
>>> arr (\(p, ()) -> case p of ... ->
let $dRealFloat_xyz = GHC.Float.$fRealFloatFloat
in case .. of () -> ())
>>> \((),()) -> ... (Point $dRealFloat_xyz 0) -- dictionary not in scope
Now evidences are passed in the environment if necessary and we get:
===> { Arrows HsToCore }
first ...
>>> arr (\(p, ()) -> case p of ... ->
let $dRealFloat_xyz = GHC.Float.$fRealFloatFloat
in case .. of () -> $dRealFloat_xyz)
>>> \(ds,()) ->
let $dRealFloat_xyz = ds
in ... (Point $dRealFloat_xyz 0) -- dictionary in scope
Note that collectStmtBinders has been copy-pasted from GHC.Hs.Utils.
This ought to be factorized but Note [Dictionary binders in ConPatOut]
claims that:
Do *not* gather (a) dictionary and (b) dictionary bindings as
binders of a ConPatOut pattern. For most calls it doesn't matter,
because it's pre-typechecker and there are no ConPatOuts. But it
does matter more in the desugarer; for example,
GHC.HsToCore.Utils.mkSelectorBinds uses collectPatBinders. In a
lazy pattern, for example f ~(C x y) = ..., we want to generate
bindings for x,y but not for dictionaries bound by C. (The type
checker ensures they would not be used.)
Desugaring of arrow case expressions needs these bindings (see
GHC.HsToCore.Arrows and arrowcase1), but SPJ (Jan 2007) says it's
safer for it to use its own pat-binder-collector:
Accordingly to the last sentence, this patch doesn't make any attempt at
factorizing both codes.
Fix #18950
|
|
|
|
|
|
|
| |
Instead of producing auxiliary con2tag bindings we now rely on
dataToTag#, eliminating a fair bit of generated code.
Co-Authored-By: Ben Gamari <ben@well-typed.com>
|
| |
|
|
|
|
| |
Missing this caused #19197. Easily fixed.
|
| |
|
|
|
|
|
|
|
|
|
| |
* allow `integerCompare` to inline into `integerLe#`, etc.
* use `naturalSubThrow` to implement Natural's `(-)`
* use `naturalNegate` to implement Natural's `negate`
* implement and use `integerToNaturalThrow` to implement Natural's `fromInteger`
Thanks to @christiaanb for reporting these
|
| |
|
|
|
|
|
|
| |
This reverts commit 7bc3a65b467c4286377b9bded277d5a2f69160b3.
NoSpecConstr is used in the wild (see #19168)
|
|
|
|
|
|
| |
The `expect_broken` of `T14059b` expected outdated output.
But #14059 has long been fixed, so we this commit accepts the new output
and marks the test as unbroken.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Consider `T18960`:
```hs
pattern P :: a -> a
pattern P x = x
{-# COMPLETE P :: () #-}
foo :: ()
foo = case () of
P _ -> ()
```
We know about the match variable of the case match that it is equal to `()`.
After the match on `P`, we still know it's equal to `()` (positive info), but
also that it can't be `P` (negative info). By the `COMPLETE` pragma, we know
that implies that the refinement type of the match variable is empty after the
`P` case.
But in the PmCheck solver, we assumed that "has positive info" means
"is not empty", thus assuming we could omit a costly inhabitation test. Which
is wrong, as we saw above.
A bit of a complication arises because the "has positive info" spared us
from doing a lot of inhabitation tests in `T17836b`. So we keep that
check, but give it a lower priority than the check for dirty variables
that requires us doing an inhabitation test.
Needless to say: This doesn't impact soundness of the checker at all,
it just implements a better trade-off between efficiency and precision.
Fixes #18960.
Metric Decrease:
T17836
|
|
|
|
|
|
| |
This patch delays the detection of missing fields in record creation
after type-checking. This gives us better error messages (see updated
test outputs).
|
| |
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Since !4493 we annotate top-level bindings with demands, which leads to
novel opportunities for thunk splitting absent top-level thunks.
It turns out that thunk splitting wasn't quite equipped for that,
because it re-used top-level, `External` Names for local helper Ids.
That triggered a CoreLint error (#19180), reproducible with `T19180`.
Fixed by adjusting the thunk splitting code to produce `SysLocal` names
for the local bindings.
Fixes #19180.
Metric Decrease:
T12227
T18282
|
|
|
|
|
|
|
|
|
|
|
|
| |
As noted in #19179, conc059 can sometimes fail due to too short of a
delay in the its Haskell threads. Address this by increasing the delay
by an order of magnitude to 5 seconds.
While I'm in town I refactored the test to eliminate a great deal of
unnecessary platform dependence, eliminate use of the deprecated
usleep, and properly handle interruption by signals.
Fixes #19179.
|
| |
|
|
|
|
|
|
|
|
|
|
|
|
| |
Previously lookupSymbol_PEi386 would call lookupSymbol while
holding linker_mutex. Fix this by rather
calling `lookupDependentSymbol`. This is safe
because lookupSymbol_PEi386 unconditionally holds linker_mutex.
Happily, this un-breaks `T12771`, `T13082_good`, and `T14611`, which
were previously marked as broken due to #18718.
Closes #19155.
|
|
|
|
|
|
|
|
|
| |
See Note [Error on unconstrained meta-variables] in TcMType.
Close #17301
Close #17567
Close #17562
Close #15474
|
|
|
|
|
|
|
|
|
|
|
| |
This commit removes the errShortString field from the ErrMsg type,
allowing us to cleanup a lot of dynflag-dependent error functions, and
move them in a more specialised 'GHC.Driver.Errors' closer to the
driver, where they are actually used.
Metric Increase:
T4801
T9961
|