| Commit message (Collapse) | Author | Age | Files | Lines |
|
|
|
| |
From the notes.ghc.drop list found using weeder in #17713
|
| |
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
This patch improves the way that CSE combines identical
alternatives. See #17901.
I'm still not happy about the duplication between CSE.combineAlts
and GHC.Core.Utils.combineIdenticalAlts; see the Notes with those
functions. But this patch is a step forward.
Metric Decrease:
T12425
T5642
|
|
|
|
|
| |
No change in functionality. Just seems tidier (and signficantly more
efficient) to deal with ticks directly than to call stripTicksTopE.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Ticket #17590 pointed out a bug in the way the linter dealt with
type lets, exposed by the new uniqAway story.
The fix is described in Note [Linting type lets]. I ended up
putting the in-scope Ids in a different env field, le_ids,
rather than (as before) sneaking them into the TCvSubst.
Surprisingly tiresome, but done.
Metric Decrease:
hie002
|
|
|
|
|
|
| |
I wanted to fix the dangling comment in `isDllName` ("This is the cause
of #", #8696 is already mentioned earlier). I took the opportunity to
change the function name to better reflect what it does.
|
|
|
|
|
|
|
|
|
|
|
|
| |
The unsafeCoerce# patch requires that unsafeCoerce# has
a compulsory unfolding that is always available. So we have
to be careful to expose compulsory unfoldings unconditionally
and consistently.
We didn't get this quite right: #17871. This patch fixes
it. No real surprises here.
See Note [Always expose compulsory unfoldings] in GHC.Iface.Tidy
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
* Do not print `join` in ApplictiveStmt, unless ppr-debug
* Print parens around multiple parallel binds
When ApplicativeDo is enabled, the renamer analyses the statements of a
`do` block and in certain cases marks them as needing to be rewritten
using `join`.
For example, if you have:
```
foo = do
a <- e1
b <- e2
doSomething a b
```
it will be desugared into:
```
foo = join (doSomething <$> e1 <*> e2)
```
After renaming but before desugaring the expression is stored
essentially as:
```
foo = do
[will need join] (a <- e1 | b <- e2)
[no return] doSomething a b
```
Before this change, the pretty printer would print a call to `join`,
even though it is not needed at this stage at all. The expression will be
actually rewritten into one using join only at desugaring, at which
point a literal call to join will be inserted.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
After ApplicatveDo strips the last `return` during renaming, the pretty
printer has to restore it. However, if the return was followed by `$`,
the dollar was stripped too and not restored.
For example, the last stamement in:
```
foo = do
x <- ...
...
return $ f x
```
would be printed as:
```
return f x
```
This commit preserved the dolar, so it becomes:
```
return $ f x
```
|
|
|
|
|
|
|
|
| |
Should make `member` queries faster and avoid messing up with missing
`nubSort`.
Metric Increase:
hie002
|
|
|
|
|
|
|
|
| |
* `interpreterDynamic` and `interpreterProfiled` now take `Interp`
parameters instead of DynFlags
* slight refactoring of `ExternalInterp` so that we can read the iserv
configuration (which is pure) without reading an MVar.
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
* extract flags and ways into their own modules (with some renaming)
* remove one SOURCE import of GHC.Driver.Session from GHC.Driver.Phases
* when GHC uses dynamic linking (WayDyn), `interpWays` was only
reporting WayDyn even if the host was profiled (WayProf). Now it
returns both as expected (might fix #16803).
* `mkBuildTag :: [Way] -> String` wasn't reporting a canonical tag for
differently ordered lists. Now we sort and nub the list to fix this.
|
|
|
|
|
|
|
|
| |
* GHC.Iface.Recomp: recompilation avoidance stuff
* GHC.Iface.Make: mkIface*
Moved `writeIfaceFile` into GHC.Iface.Load alongside `readIface` and
renamed it `writeIface` for consistency.
|
| |
|
|
|
|
|
|
|
|
|
| |
- Remove Note [Existentials in shift_con_pat].
The function shift_con_pat has been removed 15 years ago in 23f40f0e9be6d4.
- Remove kcLookupTcTyCon - it's the same as tcLookupTcTyCon
- Remove ASSERT in tyConAppArgN. It's already done by getNth,
and it's the only reason getNth exists.
- Remove unused function nextRole
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
When developing a plugin I had a shadowing problem, where I generated
code
app = \f{v r7B} x{v r7B} -> f{v r7B} x{v r7B}
This is obviously wrong, since the occurrence of `f` to the right of the
arrow refers to the `x` binder (they share a Unique). However, it is
rather confusing when Lint reports
Mismatch in type between binder and occurrence
Var: x{v rB7}
since it is printing the binder, rather than the occurrence.
It is rather easy to read this as claiming there is something wrong with
the `x` occurrence!
We change the report to explicitly print both the binder and the
occurrence variables.
|
|
|
|
|
|
|
|
| |
Aside from making the generated code easier to read when
`-ddump-deriv` is enabled, this makes the error message in `T15073`
substantially simpler (see the updated `T15073` expected stderr).
Fixes #17899.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
If ImpredicativeTypes is not enabled, then `:print <term>` will fail if the
type of <term> has nested `forall`s or `=>`s.
This is because the GHCi debugger's internals will attempt to unify a
metavariable with the type of <term> and then display the result, but if the
type has nested `forall`s or `=>`s, then unification will fail.
As a result, `:print` will bail out and the unhelpful result will be
`<term> = (_t1::t1)` (where `t1` is a metavariable).
Beware: <term> can have nested `forall`s even if its definition doesn't use
RankNTypes! Here is an example from #14828:
class Functor f where
fmap :: (a -> b) -> f a -> f b
Somewhat surprisingly, `:print fmap` considers the type of fmap to have
nested foralls. This is because the GHCi debugger sees the type
`fmap :: forall f. Functor f => forall a b. (a -> b) -> f a -> f b`.
We could envision deeply instantiating this type to get the type
`forall f a b. Functor f => (a -> b) -> f a -> f b`,
but this trick wouldn't work for higher-rank types.
Instead, we adopt a simpler fix: enable `ImpredicativeTypes` when using
`:print` and friends in the GHCi debugger. This is allows metavariables
to unify with types that have nested (or higher-rank) `forall`s/`=>`s,
which makes `:print fmap` display as
`fmap = (_t1::forall a b. Functor f => (a -> b) -> f a -> f b)`, as expected.
Although ImpredicativeTypes is a somewhat unpredictable from a type inference
perspective, there is no danger in using it in the GHCi debugger, since all
of the terms that the GHCi debugger deals with have already been typechecked.
|
|
|
|
|
|
|
| |
* The names in PrelName and THNames are no longer used
since TH merged types and kinds, Typeable is kind-polymorphic,
.net support was removed
* unqualQuasiQuote no longer used since 6f8ff0bbad3b9fa3
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
(#2950)
GHCi is split up into 2 major parts: The user-interface (UI)
and the byte-code interpreter. With `-fexternal-interpreter`
they even run in different processes. Communication between
the UI and the Interpreter (called `iserv`) is done using
messages over a pipe. This is called `Remote GHCI` and
explained in the Note [Remote GHCi] in `compiler/ghci/GHCi.hs`.
To process a `:force` command the UI sends a `Seq` message
to the `iserv` process. Then `iserv` does the effective
evaluation of the value. When during this process a breakpoint
is hit, the `iserv` process has no additional information to
enhance the `Ignoring breakpoint` output with the breakpoint
location.
To be able to print additional breakpoint information,
there are 2 possible implementation choices:
1. Store the needed information in the `iserv` process.
2. Print the `Ignoring breakpoint` from the UI process.
For option 1 we need to store the breakpoint info redundantely
in 2 places and this is bad. Therfore option 2 was implemented
in this MR:
- The user enters a `force` command
- The UI sends a `Seq` message to the `iserv` process.
- If processing of the `Seq` message hits a breakpoint,
the `iserv` process returns control to the UI process.
- The UI looks up the source location of the breakpoint,
and prints the enhanced `Ignoring breakpoint` output.
- The UI sends a `ResumeSeq` message to the `iserv` process,
to continue forcing.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
IfaceIdInfo type is confusing: there's practically no difference between
`NoInfo` and `HasInfo []`. The comments say NoInfo is used when
-fomit-interface-pragmas is enabled, but we don't need to distinguish
`NoInfo` from `HasInfo []` in when reading the interface so the
distinction is not important.
This patch simplifies the type by removing NoInfo. When we have no info
we use an empty list.
With this change we no longer read the info list lazily when reading an
IfaceInfoItem, but when reading an IfaceId the ifIdInfo field is
read lazily, so I doubt this is going to be a problem.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
In #14335 we want to be able to use both the internal interpreter (for
the plugins) and the external interpreter (for TH and GHCi) at the same
time.
This patch performs some preliminary refactoring: the `hsc_interp` field
of HscEnv replaces `hsc_iserv` and is now used to indicate which
interpreter (internal, external) to use to execute TH and GHCi.
Opt_ExternalInterpreter flag and iserv options in DynFlags are now
queried only when we set the session DynFlags. It should help making GHC
multi-target in the future by selecting an interpreter according to the
selected target.
|
|
|
|
|
|
|
|
| |
- Added a few comments in StgPAP
- Added a few comments and assertions in scavenge_small_bitmap and
walk_large_bitmap
- Did tiny refactor in GHC.Data.Bitmap: added some comments, deleted
dead code, used PlatformWordSize type.
|
|
|
|
|
|
|
|
| |
loadInterface replaces the `mi_decls`, `mi_insts`, `mi_fam_insts`,
`mi_rules`, `mi_anns` fields of ModIface with `undefined` before
inserting the interface into the EPS. However, we still want to give
loadInterface plugins access to these fields. Consequently, we want to
pass the unmodified `ModIface` the plugin.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
When GHC is parsing a file generated by a tool, e.g. by the C preprocessor, the
tool may insert #line pragmas to adjust the locations reported to the user.
As the result, the locations recorded in RealSrcLoc are not monotonic. Elements
that appear later in the StringBuffer are not guaranteed to have a higher
line/column number.
In fact, there are no guarantees whatsoever, as #line pragmas can arbitrarily
modify locations. This lack of guarantees makes ideas such as #17544
infeasible.
This patch adds an additional bit of information to every SrcLoc:
newtype BufPos = BufPos { bufPos :: Int }
A BufPos represents the location in the StringBuffer, unaffected by any
pragmas.
Updates haddock submodule.
Metric Increase:
haddock.Cabal
haddock.base
haddock.compiler
MultiLayerModules
Naperian
parsing001
T12150
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Consider
```hs
data T = A | B | C
f :: T -> Int
f A = 1
f x = case x of
A -> 2
B -> 3
C -> 4
```
Clearly, the RHS returning 2 is redundant. But we don't currently see
that, because our approximation to the covered set of the inner case
expression just picks up the positive information from surrounding
pattern matches. It lacks the context sensivity that `x` can't be `A`
anymore!
Therefore, we adopt the conceptually and practically superior approach
of reusing the covered set of a particular GRHS from an outer pattern
match. In this case, we begin checking the `case` expression with the
covered set of `f`s second clause, which encodes the information that
`x` can't be `A` anymore. After this MR, we will successfully warn about
the RHS returning 2 being redundant.
Perhaps surprisingly, this was a great simplification to the code of
both the coverage checker and the desugarer.
Found a redundant case alternative in `unix` submodule, so we have to
bump it with a fix.
Metric Decrease:
T12227
|
|
|
|
| |
Update haddock submodule
|
|
|
|
|
|
| |
* FailablePattern can no longer be created since ab51bee40c82
Therefore, Opt_WarnMissingMonadFailInstances has no effect anymore.
* XWrap is no longer used, it was moved to an extension field
|
|
|
|
|
| |
This reverts commit 8924224ecfa065ebc67b96a90d01cf9d2edd0e77
and fixes #17787.
|
| |
|
|
|
|
|
|
|
|
|
|
|
|
| |
* Remove outdated Note [HsForAllTy tyvar binders] and [Context quantification].
Since the wildcard refactor 1e041b7382, HsForAllTy no longer has an flag
controlling explicity. The field `hsq_implicit` is gone too.
The current situation is covered by Note [HsType binders] which is already
linked from LHsQTyVars.
* Small refactor in CoreLint, extracting common code to a function
* Remove "not so sure about WpFun" in TcEvidence, per Richard's comment
https://gitlab.haskell.org/ghc/ghc/merge_requests/852#note_223226
* Use mkIfThenElse in Foreign/Call, as it does exactly what we need.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Before this patch, GHC relied on Ord SrcSpan to identify source elements, by
using SrcSpan as Map keys:
blackList :: Map SrcSpan () -- compiler/GHC/HsToCore/Coverage.hs
instanceMap :: Map SrcSpan Name -- compiler/GHC/HsToCore/Docs.hs
Firstly, this design is not valid in presence of UnhelpfulSpan, as it
distinguishes between UnhelpfulSpan "X" and UnhelpfulSpan "Y", but those
strings are messages for the user, unfit to serve as identifiers for source
elements.
Secondly, this design made it hard to extend SrcSpan with additional data.
Recall that the definition of SrcSpan is:
data SrcSpan =
RealSrcSpan !RealSrcSpan
| UnhelpfulSpan !FastString
Say we want to extend the RealSrcSpan constructor with additional information:
data SrcSpan =
RealSrcSpan !RealSrcSpan !AdditionalInformation
| UnhelpfulSpan !FastString
getAdditionalInformation :: SrcSpan -> AdditionalInformation
getAdditionalInformation (RealSrcSpan _ a) = a
Now, in order for Map SrcSpan to keep working correctly, we must *ignore* additional
information when comparing SrcSpan values:
instance Ord SrcSpan where
compare (RealSrcSpan r1 _) (RealSrcSpan r2 _) = compare r1 r2
...
However, this would violate an important law:
a == b therefore f a == f b
Ignoring AdditionalInformation in comparisons would mean that with
f=getAdditionalInformation, the law above does not hold.
A more robust design is to avoid Ord SrcSpan altogether, which is what this patch implements.
The mappings are changed to use RealSrcSpan instead:
blackList :: Set RealSrcSpan -- compiler/GHC/HsToCore/Coverage.hs
instanceMap :: Map RealSrcSpan Name -- compiler/GHC/HsToCore/Docs.hs
All SrcSpan comparisons are now done with explicit comparison strategies:
SrcLoc.leftmost_smallest
SrcLoc.leftmost_largest
SrcLoc.rightmost_smallest
These strategies are not subject to the law mentioned above and can easily
discard both the string stored in UnhelpfulSpan and AdditionalInformation.
Updates haddock submodule.
|
|
|
|
| |
submodule updates: nofib, haddock
|
|
|
|
|
|
|
|
|
| |
The invariant which allowed the pervious method of splitting the type of
the body to find the type of the elements didn't work in the new
overloaded quotation world as the type can be something like
`WriterT () m a` rather than `Q a` like before.
Fixes #17839
|
| |
|
| |
|
|
|
|
|
| |
The constructor HsSplicedT occurs only in the GhcTc pass.
This enforces this fact statically via TTG.
|
|
|
|
|
|
|
| |
Switching from `lookupGlobalOccRn_maybe` to `lookupInfoOccRn`
to check whether a `main` function is in scope. Unfortunately
`lookupGlobalOccRn_maybe` complains if there are multiple `main`
functions in scope.
|
| |
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Remove several uses of `sdocWithDynFlags`. The remaining ones are mostly
CodeGen related (e.g. depend on target platform constants) and will be
fixed separately.
Metric Decrease:
T12425
T9961
WWRec
T1969
T14683
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
(Commit message written by Omer, most of the code is written by Simon
and Richard)
See Note [Implementing unsafeCoerce] for how unsafe equality proofs and
the new unsafeCoerce# are implemented.
New notes added:
- [Checking for levity polymorphism] in CoreLint.hs
- [Implementing unsafeCoerce] in base/Unsafe/Coerce.hs
- [Patching magic definitions] in Desugar.hs
- [Wiring in unsafeCoerce#] in Desugar.hs
Only breaking change in this patch is unsafeCoerce# is not exported from
GHC.Exts, instead of GHC.Prim.
Fixes #17443
Fixes #16893
NoFib
-----
--------------------------------------------------------------------------------
Program Size Allocs Instrs Reads Writes
--------------------------------------------------------------------------------
CS -0.1% 0.0% -0.0% -0.0% -0.0%
CSD -0.1% 0.0% -0.0% -0.0% -0.0%
FS -0.1% 0.0% -0.0% -0.0% -0.0%
S -0.1% 0.0% -0.0% -0.0% -0.0%
VS -0.1% 0.0% -0.0% -0.0% -0.0%
VSD -0.1% 0.0% -0.0% -0.0% -0.1%
VSM -0.1% 0.0% -0.0% -0.0% -0.0%
anna -0.0% 0.0% -0.0% -0.0% -0.0%
ansi -0.1% 0.0% -0.0% -0.0% -0.0%
atom -0.1% 0.0% -0.0% -0.0% -0.0%
awards -0.1% 0.0% -0.0% -0.0% -0.0%
banner -0.1% 0.0% -0.0% -0.0% -0.0%
bernouilli -0.1% 0.0% -0.0% -0.0% -0.0%
binary-trees -0.1% 0.0% -0.0% -0.0% -0.0%
boyer -0.1% 0.0% -0.0% -0.0% -0.0%
boyer2 -0.1% 0.0% -0.0% -0.0% -0.0%
bspt -0.1% 0.0% -0.0% -0.0% -0.0%
cacheprof -0.1% 0.0% -0.0% -0.0% -0.0%
calendar -0.1% 0.0% -0.0% -0.0% -0.0%
cichelli -0.1% 0.0% -0.0% -0.0% -0.0%
circsim -0.1% 0.0% -0.0% -0.0% -0.0%
clausify -0.1% 0.0% -0.0% -0.0% -0.0%
comp_lab_zift -0.1% 0.0% -0.0% -0.0% -0.0%
compress -0.1% 0.0% -0.0% -0.0% -0.0%
compress2 -0.1% 0.0% -0.0% -0.0% -0.0%
constraints -0.1% 0.0% -0.0% -0.0% -0.0%
cryptarithm1 -0.1% 0.0% -0.0% -0.0% -0.0%
cryptarithm2 -0.1% 0.0% -0.0% -0.0% -0.0%
cse -0.1% 0.0% -0.0% -0.0% -0.0%
digits-of-e1 -0.1% 0.0% -0.0% -0.0% -0.0%
digits-of-e2 -0.1% 0.0% -0.0% -0.0% -0.0%
dom-lt -0.1% 0.0% -0.0% -0.0% -0.0%
eliza -0.1% 0.0% -0.0% -0.0% -0.0%
event -0.1% 0.0% -0.0% -0.0% -0.0%
exact-reals -0.1% 0.0% -0.0% -0.0% -0.0%
exp3_8 -0.1% 0.0% -0.0% -0.0% -0.0%
expert -0.1% 0.0% -0.0% -0.0% -0.0%
fannkuch-redux -0.1% 0.0% -0.0% -0.0% -0.0%
fasta -0.1% 0.0% -0.5% -0.3% -0.4%
fem -0.1% 0.0% -0.0% -0.0% -0.0%
fft -0.1% 0.0% -0.0% -0.0% -0.0%
fft2 -0.1% 0.0% -0.0% -0.0% -0.0%
fibheaps -0.1% 0.0% -0.0% -0.0% -0.0%
fish -0.1% 0.0% -0.0% -0.0% -0.0%
fluid -0.1% 0.0% -0.0% -0.0% -0.0%
fulsom -0.1% 0.0% +0.0% +0.0% +0.0%
gamteb -0.1% 0.0% -0.0% -0.0% -0.0%
gcd -0.1% 0.0% -0.0% -0.0% -0.0%
gen_regexps -0.1% 0.0% -0.0% -0.0% -0.0%
genfft -0.1% 0.0% -0.0% -0.0% -0.0%
gg -0.1% 0.0% -0.0% -0.0% -0.0%
grep -0.1% 0.0% -0.0% -0.0% -0.0%
hidden -0.1% 0.0% -0.0% -0.0% -0.0%
hpg -0.1% 0.0% -0.0% -0.0% -0.0%
ida -0.1% 0.0% -0.0% -0.0% -0.0%
infer -0.1% 0.0% -0.0% -0.0% -0.0%
integer -0.1% 0.0% -0.0% -0.0% -0.0%
integrate -0.1% 0.0% -0.0% -0.0% -0.0%
k-nucleotide -0.1% 0.0% -0.0% -0.0% -0.0%
kahan -0.1% 0.0% -0.0% -0.0% -0.0%
knights -0.1% 0.0% -0.0% -0.0% -0.0%
lambda -0.1% 0.0% -0.0% -0.0% -0.0%
last-piece -0.1% 0.0% -0.0% -0.0% -0.0%
lcss -0.1% 0.0% -0.0% -0.0% -0.0%
life -0.1% 0.0% -0.0% -0.0% -0.0%
lift -0.1% 0.0% -0.0% -0.0% -0.0%
linear -0.1% 0.0% -0.0% -0.0% -0.0%
listcompr -0.1% 0.0% -0.0% -0.0% -0.0%
listcopy -0.1% 0.0% -0.0% -0.0% -0.0%
maillist -0.1% 0.0% -0.0% -0.0% -0.0%
mandel -0.1% 0.0% -0.0% -0.0% -0.0%
mandel2 -0.1% 0.0% -0.0% -0.0% -0.0%
mate -0.1% 0.0% -0.0% -0.0% -0.0%
minimax -0.1% 0.0% -0.0% -0.0% -0.0%
mkhprog -0.1% 0.0% -0.0% -0.0% -0.0%
multiplier -0.1% 0.0% -0.0% -0.0% -0.0%
n-body -0.1% 0.0% -0.0% -0.0% -0.0%
nucleic2 -0.1% 0.0% -0.0% -0.0% -0.0%
para -0.1% 0.0% -0.0% -0.0% -0.0%
paraffins -0.1% 0.0% -0.0% -0.0% -0.0%
parser -0.1% 0.0% -0.0% -0.0% -0.0%
parstof -0.1% 0.0% -0.0% -0.0% -0.0%
pic -0.1% 0.0% -0.0% -0.0% -0.0%
pidigits -0.1% 0.0% -0.0% -0.0% -0.0%
power -0.1% 0.0% -0.0% -0.0% -0.0%
pretty -0.1% 0.0% -0.1% -0.1% -0.1%
primes -0.1% 0.0% -0.0% -0.0% -0.0%
primetest -0.1% 0.0% -0.0% -0.0% -0.0%
prolog -0.1% 0.0% -0.0% -0.0% -0.0%
puzzle -0.1% 0.0% -0.0% -0.0% -0.0%
queens -0.1% 0.0% -0.0% -0.0% -0.0%
reptile -0.1% 0.0% -0.0% -0.0% -0.0%
reverse-complem -0.1% 0.0% -0.0% -0.0% -0.0%
rewrite -0.1% 0.0% -0.0% -0.0% -0.0%
rfib -0.1% 0.0% -0.0% -0.0% -0.0%
rsa -0.1% 0.0% -0.0% -0.0% -0.0%
scc -0.1% 0.0% -0.1% -0.1% -0.1%
sched -0.1% 0.0% -0.0% -0.0% -0.0%
scs -0.1% 0.0% -0.0% -0.0% -0.0%
simple -0.1% 0.0% -0.0% -0.0% -0.0%
solid -0.1% 0.0% -0.0% -0.0% -0.0%
sorting -0.1% 0.0% -0.0% -0.0% -0.0%
spectral-norm -0.1% 0.0% -0.0% -0.0% -0.0%
sphere -0.1% 0.0% -0.0% -0.0% -0.0%
symalg -0.1% 0.0% -0.0% -0.0% -0.0%
tak -0.1% 0.0% -0.0% -0.0% -0.0%
transform -0.1% 0.0% -0.0% -0.0% -0.0%
treejoin -0.1% 0.0% -0.0% -0.0% -0.0%
typecheck -0.1% 0.0% -0.0% -0.0% -0.0%
veritas -0.0% 0.0% -0.0% -0.0% -0.0%
wang -0.1% 0.0% -0.0% -0.0% -0.0%
wave4main -0.1% 0.0% -0.0% -0.0% -0.0%
wheel-sieve1 -0.1% 0.0% -0.0% -0.0% -0.0%
wheel-sieve2 -0.1% 0.0% -0.0% -0.0% -0.0%
x2n1 -0.1% 0.0% -0.0% -0.0% -0.0%
--------------------------------------------------------------------------------
Min -0.1% 0.0% -0.5% -0.3% -0.4%
Max -0.0% 0.0% +0.0% +0.0% +0.0%
Geometric Mean -0.1% -0.0% -0.0% -0.0% -0.0%
Test changes
------------
- break006 is marked as broken, see #17833
- The compiler allocates less when building T14683 (an unsafeCoerce#-
heavy happy-generated code) on 64-platforms. Allocates more on 32-bit
platforms.
- Rest of the increases are tiny amounts (still enough to pass the
threshold) in micro-benchmarks. I briefly looked at each one in a
profiling build: most of the increased allocations seem to be because
of random changes in the generated code.
Metric Decrease:
T14683
Metric Increase:
T12150
T12234
T12425
T13035
T14683
T5837
T6048
Co-Authored-By: Richard Eisenberg <rae@cs.brynmawr.edu>
Co-Authored-By: Ömer Sinan Ağacan <omeragacan@gmail.com>
|
| |
|
| |
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
There were two issues with this instance:
* its existence meant that a pattern match failure in the P monad would
produce a user-visible parse error, but the error message would not be
helpful to the user
* due to the MFP migration strategy, we had to use CPP in Lexer.x,
and that created issues for #17750
Updates haddock submodule.
|
| |
|
|
|
|
| |
This flag is deemed not useful.
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
We now always show "forall {a}. T" for inferred variables,
previously this was controlled by -fprint-explicit-foralls.
This implements part 1 of https://github.com/ghc-proposals/ghc-proposals/pull/179.
Part of GHC ticket #16320.
Furthermore, when printing a levity restriction error, we now display
the HsWrap of the expression. This lets users see the full elaboration with
-fprint-typechecker-elaboration (see also #17670)
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
The reasons for that can be found in the wiki:
https://gitlab.haskell.org/ghc/ghc/wikis/nested-cpr/split-off-cpr
We now run CPR after demand analysis (except for after the final demand
analysis run just before code gen). CPR got its own dump flags
(`-ddump-cpr-anal`, `-ddump-cpr-signatures`), but not its own flag to
activate/deactivate. It will run with `-fstrictness`/`-fworker-wrapper`.
As explained on the wiki page, this step is necessary for a sane Nested
CPR analysis. And it has quite positive impact on compiler performance:
Metric Decrease:
T9233
T9675
T9961
T15263
|
|
|
|
| |
Update haddock submodule
|
|
|
|
|
|
| |
There is no issue with nested splices as they do not require any compile
time code execution. All execution is delayed until the top-level
splice.
|