| Commit message (Collapse) | Author | Age | Files | Lines |
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Before this patch we could generate addresses of this form:
movzbl cP0_str+-9223372036854775808,%eax
The linker can't handle them because the offset is too large:
ld.lld: error: Main.o:(.text+0xB3): relocation R_X86_64_32S out of range: -9223372036852653050 is not in [-2147483648, 2147483647]
With this patch we detect those cases and generate:
movq $-9223372036854775808,%rax
addq $cP0_str,%rax
movzbl (%rax),%eax
I've also refactored `getAmode` a little bit to make it easier to
understand and to trace.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
The way that `GHC.HsToCore.Quote` desugared quoted `via` types (e.g.,
`deriving via forall a. [a] instance Eq a => Eq (List a)`) and
explicit type annotations in signatures (e.g.,
`f = id @a :: forall a. a -> a`) was completely wrong, as it did not
implement the scoping guidelines laid out in
`Note [Scoped type variables in bindings]`. This is easily fixed.
While I was in town, I did some minor cleanup of related Notes:
* `Note [Scoped type variables in bindings]` and
`Note [Scoped type variables in class and instance declarations]`
say very nearly the same thing. I decided to just consolidate the
two Notes into `Note [Scoped type variables in quotes]`.
* `Note [Don't quantify implicit type variables in quotes]` is
somewhat outdated, as it predates GHC 8.10, where the
`forall`-or-nothing rule requires kind variables to be explicitly
quantified in the presence of an explicit `forall`. As a result,
the running example in that Note doesn't even compile. I have
changed the example to something simpler that illustrates the
same point that the original Note was making.
Fixes #18388.
|
|
|
|
|
|
|
|
|
|
|
|
| |
This patch improves debug tracing a bit (#18395)
* Remove the ancient SDoc argument to substitution, replacing it
with a HasDebugCallStack constraint. The latter does the same
job (indicate the call site) but much better.
* Add HasDebugCallStack to simpleOptExpr, exprIsConApp_maybe
I needed this to help nail the lookupIdSubst panic in
#18326, #17784
|
|
|
|
|
|
|
|
| |
This patch introduces a new extension, -XLexicalNegation, which detects
whether the minus sign stands for negation or subtraction using the
whitespace-based rules described in GHC Proposal #229.
Updates haddock submodule.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
GHC is very wishy-washy about rejecting instance declarations with
nested `forall`s or contexts that are surrounded by outermost
parentheses. This can even lead to some strange interactions with
`ScopedTypeVariables`, as demonstrated in #18240. This patch makes
GHC more consistently reject instance types with nested
`forall`s/contexts so as to prevent these strange interactions.
On the implementation side, this patch tweaks `splitLHsInstDeclTy`
and `getLHsInstDeclHead` to not look through parentheses, which can
be semantically significant. I've added a
`Note [No nested foralls or contexts in instance types]` in
`GHC.Hs.Type` to explain why. This also introduces a
`no_nested_foralls_contexts_err` function in `GHC.Rename.HsType` to
catch nested `forall`s/contexts in instance types. This function is
now used in `rnClsInstDecl` (for ordinary instance declarations) and
`rnSrcDerivDecl` (for standalone `deriving` declarations), the latter
of which fixes #18271.
On the documentation side, this adds a new
"Formal syntax for instance declaration types" section to the GHC
User's Guide that presents a BNF-style grammar for what is and isn't
allowed in instance types.
Fixes #18240. Fixes #18271.
|
|
|
|
|
|
|
| |
This simple error in GHC.Core.Litn.lintJoinLams meant that
Lint reported bogus errors.
Fixes #18399
|
| |
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
`GeneralizedNewtypeDeriving` is in the unique situation where it must
produce an `LHsType GhcPs` from a Core `Type`. Historically, this was
done with the `typeToLHsType` function, which walked over the entire
`Type` and attempted to construct an `LHsType` with the same overall
structure. `typeToLHsType` is quite complicated, however, and has
been the subject of numerous bugs over the years (e.g., #14579).
Luckily, there is an easier way to accomplish the same thing: the
`XHsType` constructor of `HsType`. `XHsType` bundles an `NHsCoreTy`,
which allows embedding a Core `Type` directly into an `HsType`,
avoiding the need to laboriously convert from one to another (as
`typeToLHsType` did). Moreover, renaming and typechecking an
`XHsType` is simple, since one doesn't need to do anything to a
Core `Type`...
...well, almost. For the reasons described in
`Note [Typechecking NHsCoreTys]` in `GHC.Tc.Gen.HsType`, we must
apply a substitution that we build from the local `tcl_env` type
environment. But that's a relatively modest price to pay.
Now that `GeneralizedNewtypeDeriving` uses `NHsCoreTy`, the
`typeToLHsType` function no longer has any uses in GHC, so this patch
rips it out. Some additional tweaks to `hsTypeNeedsParens` were
necessary to make the new `-ddump-deriv` output correctly
parenthesized, but other than that, this patch is quite
straightforward.
This is a mostly internal refactoring, although it is likely that
`GeneralizedNewtypeDeriving`-generated code will now need fewer
language extensions in certain situations than it did before.
|
|
|
|
| |
The code is simpler and cleaner.
|
|
|
|
|
|
|
|
|
|
|
|
| |
`DynFlags.buildTag` was a field created from the set of Ways in
`DynFlags.ways`. It had to be kept in sync with `DynFlags.ways` which
was fragile. We want to avoid global state like this (#17957).
Moreover in #14335 we also want to support loading units with different
ways: target units would still use `DynFlags.ways` but plugins would use
`GHC.Driver.Ways.hostFullWays`. To avoid having to deal both with build
tag and with ways, we recompute the buildTag on-the-fly (should be
pretty cheap) and we remove `DynFlags.buildTag` field.
|
|
|
|
|
|
|
| |
Andreas pointed out, in !3466, that my fix for #18304 was not
quite right. This patch fixes it properly, by having just one
RecTcChecker rather than (implicitly) two nested ones, in
findTypeShape.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
We must ensure that exceptions are not simplified. Previously we used:
case raiseDivZero of
_ -> 0## -- dummyValue
But it was wrong because the evaluation of `raiseDivZero` was removed and
the dummy value was directly returned. See new Note [ghc-bignum exceptions].
I've also removed the exception triggering primops which were fragile.
We don't need them to be primops, we can have them exported by ghc-prim.
I've also added a test for #18359 which triggered this patch.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
This started as a simple fix for #18321 that organically grew into a
much more sweeping refactor of how auxiliary bindings for derived
instances are handled. I have rewritten `Note [Auxiliary binders]`
in `GHC.Tc.Deriv.Generate` to explain all of the moving parts, but
the highlights are:
* Previously, the OccName of each auxiliary binding would be given
a suffix containing a hash of its package name, module name, and
parent data type to avoid name clashes. This was needlessly
complicated, so we take the more direct approach of generating
`Exact` `RdrName`s for each auxiliary binding with the same
`OccName`, but using an underlying `System` `Name` with a fresh
`Unique` for each binding. Unlike hashes, allocating new `Unique`s
does not require any cleverness and avoid name clashes all the
same...
* ...speaking of which, in order to convince the renamer that multiple
auxiliary bindings with the same `OccName` (but different
`Unique`s) are kosher, we now use `rnLocalValBindsLHS` instead of
`rnTopBindsLHS` to rename auxiliary bindings. Again, see
`Note [Auxiliary binders]` for the full story.
* I have removed the `DerivHsBind` constructor for
`DerivStuff`—which was only used for `Data.Data`-related
auxiliary bindings—and refactored `gen_Data_binds` to use
`DerivAuxBind` instead. This brings the treatment of
`Data.Data`-related auxiliary bindings in line with every other
form of auxiliary binding.
Fixes #18321.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Co-authored-by: Facundo Domínguez <facundo.dominguez@tweag.io>
QualifiedDo is implemented using the same placeholders for operation names in
the AST that were devised for RebindableSyntax. Whenever the renamer checks
which names to use for do syntax, it first checks if the do block is qualified
(e.g. M.do { stmts }), in which case it searches for qualified names in
the module M.
This allows users to write
{-# LANGUAGE QualifiedDo #-}
import qualified SomeModule as M
f x = M.do -- desugars to:
y <- M.return x -- M.return x M.>>= \y ->
M.return y -- M.return y M.>>
M.return y -- M.return y
See Note [QualifiedDo] and the users' guide for more details.
Issue #18214
Proposal:
https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0216-qualified-do.rst
Since we change the constructors `ITdo` and `ITmdo` to carry the new module
name, we need to bump the haddock submodule to account or the new shape of
these constructors.
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
This MR makes the UM monad in GHC.Core.Unify into a one-shot
monad. See the long Note [The one-shot state monad trick].
See also #18202 and !3309, which applies this to all Reader/State-like
monads in GHC for compile-time perf improvements. The pattern used
here enables something similar to the state-hack, but is applicable to
user-defined monads, not just `IO`.
Metric Decrease 'runtime/bytes allocated' (test_env='i386-linux-deb9'):
haddock.Cabal
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Consider the Literal `[256] :: [Data.Word.Word8]`
When the `OverloadedLists` extension is not active, then the `ol_ext` field
in the `OverLitTc` record that is passed to the function `getIntegralLit`
contains the type `Word8`. This is a simple type, and we can use its
type constructor immediately for the `warnAboutOverflowedLiterals` function.
When the `OverloadedLists` extension is active, then the `ol_ext` field
contains the type family `Item [Word8]`. The function `nomaliseType` is used
to convert it to the needed type `Word8`.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
This updates haddock comments only.
This patch focuses to update for hyperlinks in GHC API's haddock comments,
because broken links especially discourage newcomers.
This includes the following hierarchies:
- GHC.Iface.*
- GHC.Llvm.*
- GHC.Rename.*
- GHC.Tc.*
- GHC.HsToCore.*
- GHC.StgToCmm.*
- GHC.CmmToAsm.*
- GHC.Runtime.*
- GHC.Unit.*
- GHC.Utils.*
- GHC.SysTools.*
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
This updates haddock comments only.
This patch focuses to update for hyperlinks in GHC API's haddock comments,
because broken links especially discourage newcomers.
This includes the following hierarchies:
- GHC.Hs.*
- GHC.Core.*
- GHC.Stg.*
- GHC.Cmm.*
- GHC.Types.*
- GHC.Data.*
- GHC.Builtin.*
- GHC.Parser.*
- GHC.Driver.*
- GHC top
|
|
|
|
|
|
|
|
| |
This lets us reuse these functions in haddock, avoiding synchronization bugs.
Also fixed some divergences with haddock in that file
Updates haddock submodule
|
| |
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
GHC.Hs.Extension had
type GhcPs = GhcPass 'Parsed
type GhcRn = GhcPass 'Renamed
type GhcTc = GhcPass 'Typechecked
type GhcTcId = GhcTc
The last of these, GhcTcId, is a vestige of the past.
This patch expunges it from GHC.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
This patch fixes the bug and implements the feature request of #3000.
1. If `Module` is a real module name and `identifier` a name of a
top-level function in `Module` then `:break Module.identifer` works
also for an `identifier` that is out of scope.
2. Extend the syntax for `:break identifier` to:
:break [ModQual.]topLevelIdent[.nestedIdent]...[.nestedIdent]
`ModQual` is optional and is either the effective name of a module or
the local alias of a qualified import statement.
`topLevelIdent` is the name of a top level function in the module
referenced by `ModQual`.
`nestedIdent` is optional and the name of a function nested in a let or
where clause inside the previously mentioned function `nestedIdent` or
`topLevelIdent`.
If `ModQual` is a module name, then `topLevelIdent` can be any top level
identifier in this module. If `ModQual` is missing or a local alias of a
qualified import, then `topLevelIdent` must be in scope.
Breakpoints can be set on arbitrarily deeply nested functions, but the
whole chain of nested function names must be specified.
3. To support the new functionality rewrite the code to tab complete `:break`.
|
| |
|
|
|
|
|
|
|
|
|
|
|
| |
These tweaks affect the inner loop of simplifyArgsWorker, which
in turn is called from the flattener in Flatten.hs. This is
a key perf bottleneck to T9872{a,b,c,d}.
These two small changes have a modest but useful benefit.
No change in functionality whatsoever.
Relates to #18354
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
This bug, revealed by #18347, is just a missing update to
sc_hole_ty in simplCast. I'd missed a code path when I
made the recentchanges in
commit 6d49d5be904c0c01788fa7aae1b112d5b4dfaf1c
Author: Simon Peyton Jones <simonpj@microsoft.com>
Date: Thu May 21 12:53:35 2020 +0100
Implement cast worker/wrapper properly
The fix is very easy.
Two other minor changes
* Tidy up in SimpleOpt.simple_opt_expr. In fact I think this is an
outright bug, introduced in the fix to #18112: we were simplifying
the same coercion twice *with the same substitution*, which is just
wrong. It'd be a hard bug to trigger, so I just fixed it; less code
too.
* Better debug printing of ApplyToVal
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Zonk residual constraints in checkForExistence to reveal user type
errors.
Previously when `:instances` was used with instances that have TypeError
constraints the result would look something like:
instance [safe] s0 => Err 'A -- Defined at ../Bug2.hs:8:10
whereas after zonking, `:instances` now sees the `TypeError` and
properly eliminates the constraint from the results.
|
| |
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Previously, if a .cmm file *not in the RTS* contained something like:
```cmm
section "rodata" { msg : bits8[] "Test\n"; }
```
It would get compiled by CmmToC into:
```c
ERW_(msg);
const char msg[] = "Test\012";
```
and fail with:
```
/tmp/ghc32129_0/ghc_4.hc:5:12: error:
error: conflicting types for \u2018msg\u2019
const char msg[] = "Test\012";
^~~
In file included from /tmp/ghc32129_0/ghc_4.hc:3:0: error:
/tmp/ghc32129_0/ghc_4.hc:4:6: error:
note: previous declaration of \u2018msg\u2019 was here
ERW_(msg);
^
/builds/hsyl20/ghc/_build/install/lib/ghc-8.11.0.20200605/lib/../lib/x86_64-linux-ghc-8.11.0.20200605/rts-1.0/include/Stg.h:253:46: error:
note: in definition of macro \u2018ERW_\u2019
#define ERW_(X) extern StgWordArray (X)
^
```
See the rationale for this on https://gitlab.haskell.org/ghc/ghc/-/wikis/commentary/compiler/backends/ppr-c#prototypes
Now we don't generate these extern declarations (ERW_, etc.) for
top-level data. It shouldn't change anything for the RTS (the only place
we use .cmm files) as it is already special cased in
`GHC.Cmm.CLabel.needsCDecl`. And hand-written Cmm can use explicit
extern declarations when needed.
Note that it allows `cgrun069` test to pass with CmmToC (cf #15467).
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
We don't want to save both Fn and Dn register sets on x86-64 as they are
aliased to the same arch register (XMMn).
Moreover, when SAVE_STGREGS was used in conjunction with `jump foo [*]`
which makes a set of Cmm registers alive so that they cover all arch
registers used to pass parameter, we could have Fn, Dn and XMMn alive at
the same time. It made the LLVM code generator choke (see #17920).
Now `SAVE_REGS/RESTORE_REGS` and `jump foo [*]` use the same set of
registers.
|
|
|
|
|
|
|
| |
We look up modules by their name, and not their contents. There is no
way to separately reference a signature vs regular module; you get what
you get. Only boot files can be referenced indepenently with `import {-#
SOURCE #-}`.
|
|
|
|
|
|
|
| |
tablesNextToCode is a platform setting and doesn't belong into DynFlags
(#17957). Doing this is also a prerequisite to fix #14335 where we deal
with two platforms (target and host) that may have different platform
settings.
|
|
|
|
| |
It avoids having to use DynFlags to reach for pprUserLength.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Thanks to ghc-bignum, the compiler can be simplified:
* Types and constructors of Integer and Natural can be wired-in. It
means that we don't have to query them from interfaces. It also means
that numeric literals don't have to carry their type with them.
* The same code is used whatever ghc-bignum backend is enabled. In
particular, conversion of bignum literals into final Core expressions
is now much more straightforward. Bignum closure inspection too.
* GHC itself doesn't depend on any integer-* package anymore
* The `integerLibrary` setting is gone.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
This implements several general performance improvements to GHC,
to offset the effect of the linear types change.
General optimisations:
- Add a `coreFullView` function which iterates `coreView` on the
head. This avoids making function recursive solely because the
iterate `coreView` themselves. As a consequence, this functions can
be inlined, and trigger case-of-known constructor (_e.g._
`kindRep_maybe`, `isLiftedRuntimeRep`, `isMultiplicityTy`,
`getTyVar_maybe`, `splitAppTy_maybe`, `splitFunType_maybe`,
`tyConAppTyCon_maybe`). The common pattern about all these functions
is that they are almost always used as views, and immediately
consumed by a case expression. This commit also mark them asx `INLINE`.
- In `subst_ty` add a special case for nullary `TyConApp`, which avoid
allocations altogether.
- Use `mkTyConApp` in `subst_ty` for the general `TyConApp`. This
required quite a bit of module shuffling.
case. `myTyConApp` enforces crucial sharing, which was lost during
substitution. See also !2952 .
- Make `subst_ty` stricter.
- In `eqType` (specifically, in `nonDetCmpType`), add a special case,
tested first, for the very common case of nullary `TyConApp`.
`nonDetCmpType` has been made `INLINE` otherwise it is actually a
regression. This is similar to the optimisations in !2952.
Linear-type specific optimisations:
- Use `tyConAppTyCon_maybe` instead of the more complex `eqType` in
the definition of the pattern synonyms `One` and `Many`.
- Break the `hs-boot` cycles between `Multiplicity.hs` and `Type.hs`:
`Multiplicity` now import `Type` normally, rather than from the
`hs-boot`. This way `tyConAppTyCon_maybe` can inline properly in the
`One` and `Many` pattern synonyms.
- Make `updateIdTypeAndMult` strict in its type and multiplicity
- The `scaleIdBy` gets a specialised definition rather than being an
alias to `scaleVarBy`
- `splitFunTy_maybe` is given the type `Type -> Maybe (Mult, Type,
Type)` instead of `Type -> Maybe (Scaled Type, Type)`
- Remove the `MultMul` pattern synonym in favour of a view `isMultMul`
because pattern synonyms appear not to inline well.
- in `eqType`, in a `FunTy`, compare multiplicities last: they are
almost always both `Many`, so it helps failing faster.
- Cache `manyDataConTy` in `mkTyConApp`, to make sure that all the
instances of `TyConApp ManyDataConTy []` are physically the same.
This commit has been authored by
* Richard Eisenberg
* Krzysztof Gogolewski
* Arnaud Spiwack
Metric Decrease:
haddock.base
T12227
T12545
T12990
T1969
T3064
T5030
T9872b
Metric Increase:
haddock.base
haddock.Cabal
haddock.compiler
T12150
T12234
T12425
T12707
T13035
T13056
T15164
T16190
T18304
T1969
T3064
T3294
T5631
T5642
T5837
T6048
T9020
T9233
T9675
T9872a
T9961
WWRec
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
This is the first step towards implementation of the linear types proposal
(https://github.com/ghc-proposals/ghc-proposals/pull/111).
It features
* A language extension -XLinearTypes
* Syntax for linear functions in the surface language
* Linearity checking in Core Lint, enabled with -dlinear-core-lint
* Core-to-core passes are mostly compatible with linearity
* Fields in a data type can be linear or unrestricted; linear fields
have multiplicity-polymorphic constructors.
If -XLinearTypes is disabled, the GADT syntax defaults to linear fields
The following items are not yet supported:
* a # m -> b syntax (only prefix FUN is supported for now)
* Full multiplicity inference (multiplicities are really only checked)
* Decent linearity error messages
* Linear let, where, and case expressions in the surface language
(each of these currently introduce the unrestricted variant)
* Multiplicity-parametric fields
* Syntax for annotating lambda-bound or let-bound with a multiplicity
* Syntax for non-linear/multiple-field-multiplicity records
* Linear projections for records with a single linear field
* Linear pattern synonyms
* Multiplicity coercions (test LinearPolyType)
A high-level description can be found at
https://ghc.haskell.org/trac/ghc/wiki/LinearTypes/Implementation
Following the link above you will find a description of the changes made to Core.
This commit has been authored by
* Richard Eisenberg
* Krzysztof Gogolewski
* Matthew Pickering
* Arnaud Spiwack
With contributions from:
* Mark Barbone
* Alexander Vershilov
Updates haddock submodule.
|
| |
|
|
|
|
|
| |
It avoids using DynFlags in the Outputable instance of Clabel to check
assertions at pretty-printing time.
|
|
|
|
|
| |
This bit of documentation got outdated after commit
1fcede43d2b30f33b7505e25eb6b1f321be0407f
|
| |
|
|
|
|
|
|
|
|
|
|
| |
The Haskell calling convention requires integer parameters smaller
than wordsize to be promoted to wordsize (where the upper bits are
don't care). To access such small integer parameter read a word from
the parameter array and then cast that word to the small integer
target type.
Fixes #15933
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Previously CoreToStg would unconditionally discard cases of the form:
case unsafeEqualityProof of wild { _ -> rhs }
and rather replace the whole thing with `rhs`. However, in some cases
(see #18227) the case binder is still live, resulting in unbound
occurrences in `rhs`. Fix this by only discarding the case if the case
binder is dead.
Fixes #18227.
|
|
|
|
|
|
|
| |
The initial version was rewritten by Tamar Christina.
It was rewritten in large parts by Andreas Klebinger.
Co-authored-by: Andreas Klebinger <klebinger.andreas@gmx.at>
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Currently, `HsForAllTy` permits the combination of `ForallVis` and
`Inferred`, but you can't actually typecheck code that uses it
(e.g., `forall {a} ->`). This patch refactors `HsForAllTy` to use a
new `HsForAllTelescope` data type that makes a type-level distinction
between visible and invisible `forall`s such that visible `forall`s
do not track `Specificity`. That part of the patch is actually quite
small; the rest is simply changing consumers of `HsType` to
accommodate this new type.
Fixes #18235. Bumps the `haddock` submodule.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Ticket #18304 showed that we need to be very careful
when exploring the demand (esp usage demand) on recursive
product types.
This patch solves the problem by trimming the demand on such types --
in effect, a form of "widening".
See the Note [Trimming a demand to a type] in DmdAnal, which explains
how I did this by piggy-backing on an existing mechansim for trimming
demands becuase of GADTs. The significant payload of this patch is
very small indeed:
* Make GHC.Core.Opt.WorkWrap.Utils.typeShape use RecTcChecker to
avoid looking through recursive types.
But on the way
* I found that ae_rec_tc was entirely inoperative and did nothing.
So I removed it altogether from DmdAnal.
* I moved some code around in DmdAnal and Demand.
(There are no actual changes in dmdFix.)
* I changed the API of DmsAnal.dmdAnalRhsLetDown to return
a StrictSig rather than a decorated Id
* I removed the dead function peelTsFuns from Demand
Performance effects:
Nofib: 0.0% changes. Not surprising, because they don't
use recursive products
Perf tests
T12227:
1% increase in compiler allocation, becuase $cto gets w/w'd.
It did not w/w before because it takes a deeply nested
argument, so the worker gets too many args, so we abandon w/w
altogether (see GHC.Core.Opt.WorkWrap.Utils.isWorkerSmallEnough)
With this patch we trim the demands. That is not strictly
necessary (since these Generic type constructors are like
tuples -- they can't cause a loop) but the net result is that
we now w/w $cto which is fine.
UniqLoop:
16% decrease in /runtime/ allocation. The UniqSupply is a
recursive product, so currently we abandon all strictness on
'churn'. With this patch 'churn' gets useful strictness, and
we w/w it. Hooray
Metric Decrease:
UniqLoop
Metric Increase:
T12227
|
| |
|
| |
|
|
|
|
| |
Preload units can be retrieved in UnitState when needed (i.e. in GHCi)
|
| |
|
| |
|
| |
|