| Commit message (Collapse) | Author | Age | Files | Lines |
|
|
|
|
|
|
|
|
|
|
|
| |
Previously, the SDocContext used for code generation contained
information whether the labels should use Asm or C style.
However, at every individual call site, this is known statically.
This removes the parameter to 'PprCode' and replaces every 'pdoc'
used to print a label in code style with 'pprCLabel' or 'pprAsmLabel'.
The OutputableP instance is now used only for dumps.
The output of T15155 changes, it now uses the Asm style
(which is faithful to what actually happens).
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
This patch massages the keys used in the `TmOracle` `CoreMap` to ensure
that dictionaries of coherent classes give the same key.
That is, whenever we have an expression we want to insert or lookup in
the `TmOracle` `CoreMap`, we first replace any dictionary
`$dict_abcd :: ct` with a value of the form `error @ct`.
This allows us to common-up view pattern functions with required
constraints whose arguments differed only in the uniques of the
dictionaries they were provided, thus fixing #21662.
This is a rather ad-hoc change to the keys used in the
`TmOracle` `CoreMap`. In the long run, we would probably want to use
a different representation for the keys instead of simply using
`CoreExpr` as-is. This more ambitious plan is outlined in #19272.
Fixes #21662
Updates unix submodule
|
|
|
|
|
|
| |
As noted in #16802, this is no longer needed.
Closes #16802.
|
|
|
|
|
|
|
|
|
|
|
| |
Here we at long last remove the `make`-based build system, it having
been replaced with the Shake-based Hadrian build system. Users are
encouraged to refer to the documentation in `hadrian/doc` and this [1]
blog post for details on using Hadrian.
Closes #17527.
[1] https://www.haskell.org/ghc/blog/20220805-make-to-hadrian.html
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
This MR fixes #21694, #21755. It also makes sure that #21948 and
fix to #21694.
* For #21694 the underlying problem was that we were calling arityType
on an expression that had free join points. This is a Bad Bad Idea.
See Note [No free join points in arityType].
* To make "no free join points in arityType" work out I had to avoid
trying to use eta-expansion for runRW#. This entailed a few changes
in the Simplifier's treatment of runRW#. See
GHC.Core.Opt.Simplify.Iteration Note [No eta-expansion in runRW#]
* I also made andArityType work correctly with -fpedantic-bottoms;
see Note [Combining case branches: andWithTail].
* Rewrote Note [Combining case branches: optimistic one-shot-ness]
* arityType previously treated join points differently to other
let-bindings. This patch makes them unform; arityType analyses
the RHS of all bindings to get its ArityType, and extends am_sigs.
I realised that, now we have am_sigs giving the ArityType for
let-bound Ids, we don't need the (pre-dating) special code in
arityType for join points. But instead we need to extend the env for
Rec bindings, which weren't doing before. More uniform now. See
Note [arityType for let-bindings].
This meant we could get rid of ae_joins, and in fact get rid of
EtaExpandArity altogether. Simpler.
* And finally, it was the strange treatment of join-point Ids in
arityType (involving a fake ABot type) that led to a serious bug:
#21755. Fixed by this refactoring, which treats them uniformly;
but without breaking #18328.
In fact, the arity for recursive join bindings is pretty tricky;
see the long Note [Arity for recursive join bindings]
in GHC.Core.Opt.Simplify.Utils. That led to more refactoring,
including deciding that an Id could have an Arity that is bigger
than its JoinArity; see Note [Invariants on join points], item
2(b) in GHC.Core
* Make sure that the "demand threshold" for join points in DmdAnal
is no bigger than the join-arity. In GHC.Core.Opt.DmdAnal see
Note [Demand signatures are computed for a threshold arity based on idArity]
* I moved GHC.Core.Utils.exprIsDeadEnd into GHC.Core.Opt.Arity,
where it more properly belongs.
* Remove an old, redundant hack in FloatOut. The old Note was
Note [Bottoming floats: eta expansion] in GHC.Core.Opt.SetLevels.
Compile time improves very slightly on average:
Metrics: compile_time/bytes allocated
---------------------------------------------------------------------------------------
T18223(normal) ghc/alloc 725,808,720 747,839,216 +3.0% BAD
T6048(optasm) ghc/alloc 105,006,104 101,599,472 -3.2% GOOD
geo. mean -0.2%
minimum -3.2%
maximum +3.0%
For some reason Windows was better
T10421(normal) ghc/alloc 125,888,360 124,129,168 -1.4% GOOD
T18140(normal) ghc/alloc 85,974,520 83,884,224 -2.4% GOOD
T18698b(normal) ghc/alloc 236,764,568 234,077,288 -1.1% GOOD
T18923(normal) ghc/alloc 75,660,528 73,994,512 -2.2% GOOD
T6048(optasm) ghc/alloc 112,232,512 108,182,520 -3.6% GOOD
geo. mean -0.6%
I had a quick look at T18223 but it is knee deep in coercions and
the size of everything looks similar before and after. I decided
to accept that 3% increase in exchange for goodness elsewhere.
Metric Decrease:
T10421
T18140
T18698b
T18923
T6048
Metric Increase:
T18223
|
| |
|
| |
|
|
|
|
|
|
|
|
|
|
|
| |
#21723 and #21942.
* refines the precedence levels, adding `qualPrec` and `funPrec` to better control parenthesization
* `pprParendType`, `pprFunArgType`, and `instance Ppr Type` all just call `pprType` with proper precedence
* `ParensT` constructor is now always printed parenthesized
* adds the precedence argument to `pprTyApp` as well, as it needs to keep track and pass it down
* using `>=` instead of former `>` to match the Core type printing logic
* some test outputs have changed, losing extraneous parentheses
|
| |
|
| |
|
|
|
|
|
|
|
| |
This patch improves the uniformity of error message formatting by
printing constraints in quotes, as we do for types.
Fix #21167
|
|
|
|
| |
Now we also filter the local rules (again) which fixes the issue.
|
| |
|
| |
|
|
|
|
|
|
|
| |
This fixes #22065. We were failing to retain a quantifier that
was mentioned in the kind of another retained quantifier.
Easy to fix.
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
The -x option is used to manually specify which phase a file should be
started to be compiled from (even if it lacks the correct extension). I
just failed to implement this when refactoring the driver.
In particular Cabal calls GHC with `-E -cpp -x hs Foo.cpphs` to
preprocess source files using GHC.
I added a test to exercise this case.
Fixes #22044
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
For the code
{-# LANGUAGE OverloadedRecordUpdate #-}
operatorUpdate f = f{(+) = 1}
There are no exact print annotations for the parens around the +
symbol, nor does normal ppr print them.
This MR fixes that.
Closes #21805
Updates haddock submodule
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
This patch adds a new command-line flag:
-fplugin-library=<file-path>;<unit-id>;<module>;<args>
used like this:
-fplugin-library=path/to/plugin.so;package-123;Plugin.Module;["Argument","List"]
It allows a plugin to be loaded directly from a shared library. With
this approach, GHC doesn't compile anything for the plugin and doesn't
load any .hi file for the plugin and its dependencies. As such GHC
doesn't need to support two environments (one for plugins, one for
target code), which was the more ambitious approach tracked in #14335.
Fix #20964
Co-authored-by: Josh Meredith <joshmeredith2008@gmail.com>
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Fix for #21651
Fixes three bugs:
- writes to eventManager should be atomic. It is accessed concurrently by ioManagerCapabilitiesChanged and closeFdWith.
- The race in closeFdWith described in the ticket.
- A race in getSystemEventManager where it accesses the 'IOArray' in
'eventManager' before 'ioManagerCapabilitiesChanged' has written to
'eventManager', causing an Array Index exception. The fix here is to
'yield' and retry.
|
|
|
|
|
| |
This bug does not affect windows, which does not use the
base module GHC.Event.Thread.
|
|
|
|
|
|
|
|
|
|
| |
* Remove hack when printing OccNames. No longer needed since e3dcc0d5
* Remove unused `pprCmms` and `instance Outputable Instr`
* Simplify `pprCLabel` (no need to pass platform)
* Remove evil `Show`/`Eq` instances for `SDoc`. They were needed by
ImmLit, but that can take just a String instead.
* Remove instance `Outputable CLabel` - proper output of labels
needs a platform, and is done by the `OutputableP` instance
|
| |
|
|
|
|
| |
This addresses one part of #21710.
|
| |
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
The former behaviour of adding cost centres after optimization but
before unfoldings are created is not available via the flag
`prof-late-inline` instead.
I also reduced the overhead of -fprof-late* by pushing the cost centres
into lambdas. This means the cost centres will only account for
execution of functions and not their partial application.
Further I made LATE_CC cost centres it's own CC flavour so they now
won't clash with user defined ones if a user uses the same string for
a custom scc.
LateCC: Don't put cost centres inside constructor workers.
With -fprof-late they are rarely useful as the worker is usually
inlined. Even if the worker is not inlined or we use -fprof-late-linline
they are generally not helpful but bloat compile and run time
significantly. So we just don't add sccs inside constructor workers.
-------------------------
Metric Decrease:
T13701
-------------------------
|
| |
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
This patch fixes quite a tricky leak where we would end up retaining
stale ModDetails due to rehydrating modules against non-finalised
interfaces.
== Loops with multiple boot files
It is possible for a module graph to have a loop (SCC, when ignoring boot files)
which requires multiple boot files to break. In this case we must perform the
necessary hydration steps before and after compiling modules which have boot files
which are described above for corectness but also perform an additional hydration step
at the end of the SCC to remove space leaks.
Consider the following example:
┌───────┐ ┌───────┐
│ │ │ │
│ A │ │ B │
│ │ │ │
└─────┬─┘ └───┬───┘
│ │
┌────▼─────────▼──┐
│ │
│ C │
└────┬─────────┬──┘
│ │
┌────▼──┐ ┌───▼───┐
│ │ │ │
│ A-boot│ │ B-boot│
│ │ │ │
└───────┘ └───────┘
A, B and C live together in a SCC. Say we compile the modules in order
A-boot, B-boot, C, A, B then when we compile A we will perform the hydration steps
(because A has a boot file). Therefore C will be hydrated relative to A, and the
ModDetails for A will reference C/A. Then when B is compiled C will be rehydrated again,
and so B will reference C/A,B, its interface will be hydrated relative to both A and B.
Now there is a space leak because say C is a very big module, there are now two different copies of
ModDetails kept alive by modules A and B.
The way to avoid this space leak is to rehydrate an entire SCC together at the
end of compilation so that all the ModDetails point to interfaces for .hs files.
In this example, when we hydrate A, B and C together then both A and B will refer to
C/A,B.
See #21900 for some more discussion.
-------------------------------------------------------
In addition to this simple case, there is also the potential for a leak
during parallel upsweep which is also fixed by this patch. Transcibed is
Note [ModuleNameSet, efficiency and space leaks]
Note [ModuleNameSet, efficiency and space leaks]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
During unsweep the results of compiling modules are placed into a MVar, to find
the environment the module needs to compile itself in the MVar is consulted and
the HomeUnitGraph is set accordingly. The reason we do this is that precisely tracking
module dependencies and recreating the HUG from scratch each time is very expensive.
In serial mode (-j1), this all works out fine because a module can only be compiled after
its dependencies have finished compiling and not interleaved with compiling module loops.
Therefore when we create the finalised or no loop interfaces, the HUG only contains
finalised interfaces.
In parallel mode, we have to be more careful because the HUG variable can contain
non-finalised interfaces which have been started by another thread. In order to avoid
a space leak where a finalised interface is compiled against a HPT which contains a
non-finalised interface we have to restrict the HUG to only the visible modules.
The visible modules is recording in the ModuleNameSet, this is propagated upwards
whilst compiling and explains which transitive modules are visible from a certain point.
This set is then used to restrict the HUG before the module is compiled to only
the visible modules and thus avoiding this tricky space leak.
Efficiency of the ModuleNameSet is of utmost importance because a union occurs for
each edge in the module graph. Therefore the set is represented directly as an IntSet
which provides suitable performance, even using a UniqSet (which is backed by an IntMap) is
too slow. The crucial test of performance here is the time taken to a do a no-op build in --make mode.
See test "jspace" for an example which used to trigger this problem.
Fixes #21900
|
|
|
|
|
|
| |
Previously, we had to disable defer-type-errors in splices because of #7276.
But this fix is no longer necessary, the test T7276 no longer segfaults
and is now correctly deferred.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
This patch removes the TCvSubst data type and instead uses Subst as
the environment for both term and type level substitution. This
change is partially motivated by the existential type proposal,
which will introduce types that contain expressions and therefore
forces us to carry around an "IdSubstEnv" even when substituting for
types. It also reduces the amount of code because "Subst" and
"TCvSubst" share a lot of common operations. There isn't any
noticeable impact on performance (geo. mean for ghc/alloc is around
0.0% but we have -94 loc and one less data type to worry abount).
Currently, the "TCvSubst" data type for substitution on types is
identical to the "Subst" data type except the former doesn't store
"IdSubstEnv". Using "Subst" for type-level substitution means there
will be a redundant field stored in the data type. However, in cases
where the substitution starts from the expression, using "Subst" for
type-level substitution saves us from having to project "Subst" into a
"TCvSubst". This probably explains why the allocation is mostly even
despite the redundant field.
The patch deletes "TCvSubst" and moves "Subst" and its relevant
functions from "GHC.Core.Subst" into "GHC.Core.TyCo.Subst".
Substitution on expressions is still defined in "GHC.Core.Subst" so we
don't have to expose the definition of "Expr" in the hs-boot file that
"GHC.Core.TyCo.Subst" must import to refer to "IdSubstEnv" (whose
codomain is "CoreExpr"). Most functions named fooTCvSubst are renamed
into fooSubst with a few exceptions (e.g. "isEmptyTCvSubst" is a
distinct function from "isEmptySubst"; the former ignores the
emptiness of "IdSubstEnv"). These exceptions mainly exist for
performance reasons and will go away when "Expr" and "Type" are
mutually recursively defined (we won't be able to take those
shortcuts if we can't make the assumption that expressions don't
appear in types).
|
|
|
|
|
| |
Instead of `` `cast` <Co:11> :: (Some -> Really -> Large Type)``
simply print `` `cast` <Co:11> :: ... ``
|
|
|
|
| |
Fixes #21866
|
| |
|
|
|
|
|
|
|
|
|
| |
Residency monitoring under the non-moving collector is quite
conservative (e.g. the reported value is larger than reality) since
otherwise we would need to block on concurrent collection. Skip a few
tests that are sensitive to residency.
(cherry picked from commit 6880e4fbf728c04e8ce83e725bfc028fcb18cd70)
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
We no longer generate .s files anyway.
Metric Decrease:
MultiLayerModules
T10421
T13035
T13701
T14697
T16875
T18140
T18304
T18923
T9198
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
There was an assert error, as Gergo pointed out in #21896.
I fixed this by adding an InScopeSet argument to tcUnifyTyWithTFs.
And also to GHC.Core.Unify.niFixTCvSubst.
I also took the opportunity to get a couple more InScopeSets right,
and to change some substTyUnchecked into substTy.
This MR touches a lot of other files, but only because I also took the
opportunity to introduce mkInScopeSetList, and use it.
|
|
|
|
|
| |
This file is just a place to accumlate notes about particular
benchmarks, so that I don't keep re-inventing the wheel.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
This patch addresses #21831, point 2. See
Note [generaliseDictPats] in SpecConstr
I took the opportunity to refactor the construction of specialisation
rules a bit, so that the rule name says what type we are specialising
at.
Surprisingly, there's a 20% decrease in compile time for test
perf/compiler/T18223. I took a look at it, and the code size seems the
same throughout. I did a quick ticky profile which seemed to show a
bit less substitution going on. Hmm. Maybe it's the "don't do
eta-expansion in stable unfoldings" patch, which is part of the
same MR as this patch.
Anyway, since it's a move in the right direction, I didn't think it
was worth looking into further.
Metric Decrease:
T18223
|
|
|
|
|
|
|
| |
Gergo points out (#21801) that GHC.Core.Opt.Arity.tryEtaReduce was
making an ill-formed cast. It didn't matter, because the subsequent
guard discarded it; but still worth fixing. Spurious warnings are
distracting.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
This patch fixes #21888, and simplifies finaliseArgBoxities
by eliminating the (recently introduced) data type FinalDecision.
A delicate interaction meant that this patch
commit d1c25a48154236861a413e058ea38d1b8320273f
Date: Tue Jul 12 16:33:46 2022 +0100
Refactor wantToUnboxArg a bit
make worker/wrapper go into an infinite loop. This patch
fixes it by narrowing the handling of case (B) of
Note [Boxity for bottoming functions], to deal only the
arguemnts that are type variables. Only then do we drop
the trimBoxity call, which is what caused the bug.
I also
* Added documentation of case (B), which was previously
completely un-mentioned. And a regression test,
T21888a, to test it.
* Made unboxDeeplyDmd stop at lazy demands. It's rare anyway
for a bottoming function to have a lazy argument (mainly when
the data type is recursive and then we don't want to unbox
deeply). Plus there is Note [No lazy, Unboxed demands in
demand signature]
* Refactored the Case equation for dmdAnal a bit, to do less
redundant pattern matching.
|
| |
|
| |
|
| |
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
This MR adds the language extension -XDeepSubsumption, implementing
GHC proposal #511. This change mitigates the impact of GHC proposal
The changes are highly localised, by design. See Note [Deep subsumption]
in GHC.Tc.Utils.Unify.
The main changes are:
* Add -XDeepSubsumption, which is on by default in Haskell98 and Haskell2010,
but off in Haskell2021.
-XDeepSubsumption largely restores the behaviour before the "simple subsumption" change.
-XDeepSubsumpition has a similar flavour as -XNoMonoLocalBinds:
it makes type inference more complicated and less predictable, but it
may be convenient in practice.
* The main changes are in:
* GHC.Tc.Utils.Unify.tcSubType, which does deep susumption and eta-expanansion
* GHC.Tc.Utils.Unify.tcSkolemiseET, which does deep skolemisation
* In GHC.Tc.Gen.App.tcApp we call tcSubTypeNC to match the result
type. Without deep subsumption, unifyExpectedType would be sufficent.
See Note [Deep subsumption] in GHC.Tc.Utils.Unify.
* There are no changes to Quick Look at all.
* The type of `withDict` becomes ambiguous; so add -XAllowAmbiguousTypes to
GHC.Magic.Dict
* I fixed a small but egregious bug in GHC.Core.FVs.varTypeTyCoFVs, where
we'd forgotten to take the free vars of the multiplicity of an Id.
* I also had to fix tcSplitNestedSigmaTys
When I did the shallow-subsumption patch
commit 2b792facab46f7cdd09d12e79499f4e0dcd4293f
Date: Sun Feb 2 18:23:11 2020 +0000
Simple subsumption
I changed tcSplitNestedSigmaTys to not look through function arrows
any more. But that was actually an un-forced change. This function
is used only in
* Improving error messages in GHC.Tc.Gen.Head.addFunResCtxt
* Validity checking for default methods: GHC.Tc.TyCl.checkValidClass
* A couple of calls in the GHCi debugger: GHC.Runtime.Heap.Inspect
All to do with validity checking and error messages. Acutally its
fine to look under function arrows here, and quite useful a test
DeepSubsumption05 (a test motivated by a build failure in the
`lens` package) shows.
The fix is easy. I added Note [tcSplitNestedSigmaTys].
|
|
|
|
|
|
|
|
|
| |
The way record updates are typechecked/desugared changed in MR !7981.
Because we desugar in the typechecker to a simple case expression, the
pattern match checker becomes able to spot the long-distance information
and avoid emitting an incorrect pattern match warning.
Fixes #21360
|
|
|
|
|
|
|
| |
This adds a test for #21871, which was fixed by the No Skolem Info
rework (MR !7105).
Fixes #21871
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
* Removed references to driver from GHC.Core.LateCC, GHC.Core.Simplify
namespace and GHC.Core.Opt.Stats.
Also removed services from configuration records.
* Renamed GHC.Core.Opt.Simplify to GHC.Core.Opt.Simplify.Iteration.
* Inlined `simplifyPgm` and renamed `simplifyPgmIO` to `simplifyPgm`
and moved the Simplify driver to GHC.Core.Opt.Simplify.
* Moved `SimplMode` and `FloatEnable` to GHC.Core.Opt.Simplify.Env.
* Added a configuration record `TopEnvConfig` for the `SimplTopEnv` environment
in GHC.Core.Opt.Simplify.Monad.
* Added `SimplifyOpts` and `SimplifyExprOpts`. Provide initialization functions
for those in a new module GHC.Driver.Config.Core.Opt.Simplify.
Also added initialization functions for `SimplMode` to that module.
* Moved `CoreToDo` and friends to a new module GHC.Core.Pipeline.Types
and the counting types and functions (`SimplCount` and `Tick`) to new
module GHC.Core.Opt.Stats.
* Added getter functions for the fields of `SimplMode`. The pedantic bottoms
option and the platform are retrieved from the ArityOpts and RuleOpts and the
getter functions allow us to retrieve values from `SpecEnv` without the
knowledge where the data is stored exactly.
* Moved the coercion optimization options from the top environment to
`SimplMode`. This way the values left in the top environment are those
dealing with monadic functionality, namely logging, IO related stuff and
counting. Added a note "The environments of the Simplify pass".
* Removed `CoreToDo` from GHC.Core.Lint and GHC.CoreToStg.Prep and got rid of
`CoreDoSimplify`. Pass `SimplifyOpts` in the `CoreToDo` type instead.
* Prep work before removing `InteractiveContext` from `HscEnv`.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
As pointed out in #21575, it is not sufficient to set withDict to inline
after the typeclass specialiser, because we might inline withDict in one
module and then import it in another, and we run into the same problem.
This means we could still end up with incorrect runtime results because
the typeclass specialiser would assume that distinct typeclass evidence
terms at the same type are equal, when this is not necessarily the case
when using withDict.
Instead, this patch introduces a new magicId, 'nospec', which is only
inlined in CorePrep. We make use of it in the definition of withDict
to ensure that the typeclass specialiser does not common up distinct
typeclass evidence terms.
Fixes #21575
|
|
|
|
|
|
|
| |
We were failing to stop before running the assembler so the object file
was also created.
Fixes #21869
|
|
|
|
|
|
| |
It appears that Centos 7 has a more strict C++ compiler than most
distributions since std::runtime_error is defined in <stdexcept> rather
than <exception>. In T11829 we mistakenly imported the latter.
|
| |
|