summaryrefslogtreecommitdiff
path: root/compiler
Commit message (Collapse)AuthorAgeFilesLines
* Fix distinctionwip/llvm-debug-infoBen Gamari2017-09-156-30/+37
|
* [WIP] llvmGen: Produce debug information metadata for functionsBen Gamari2017-09-158-30/+210
| | | | | | | | | | | | | | | Summary: It turns out that providing debug information in LLVM is relatively straightforward. At this moment this only provides debug information with procedure-level granularity. Test Plan: Validate, look at DWARF output, try poking around in GDB Reviewers: scpmw, simonmar, austin Subscribers: spacekitteh, cocreature, thomie Differential Revision: https://phabricator.haskell.org/D2343
* Remove dead function TcUnify.wrapFunResCoercionArnaud Spiwack2017-09-151-17/+0
| | | | | | | | | | Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3970
* Renamer now preserves location for IEThingWith list itemsAlan Zimmerman2017-09-151-18/+19
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | Prior to this, in the RenamedSource for module Renaming.RenameInExportedType ( MyType (NT) ) where data MyType = MT Int | NT The (NT) was given the location of MyType earlier on the line in the export list. Also the location was discarded for any field labels, and replaced with a `noLoc`. Test Plan: ./validate Reviewers: bgamari, austin Reviewed By: bgamari Subscribers: rwbarton, thomie GHC Trac Issues: #14189 Differential Revision: https://phabricator.haskell.org/D3968
* Fix #14228 by marking SumPats as non-irrefutableRyan Scott2017-09-151-2/+25
| | | | | | | | | | | | | | | | | | | | `isIrrefutableHsPat` should always return `False` for unboxed sum patterns (`SumPat`s), since they always have at least one other corresponding pattern of the same arity (since the minimum arity for a `SumPat` is 2). Failure to do so causes incorrect code to be generated for pattern synonyms that use unboxed sums, as shown in #14228. Test Plan: make test TEST=T14228 Reviewers: austin, bgamari, simonpj Reviewed By: simonpj Subscribers: simonpj, rwbarton, thomie GHC Trac Issues: #14228 Differential Revision: https://phabricator.haskell.org/D3951
* Fix missing fields warnings in empty record construction, fix #13870HE, Tao2017-09-151-7/+14
| | | | | | | | | | | | | | | | Test Plan: make test TEST=T13870 Reviewers: RyanGlScott, austin, bgamari, mpickering Reviewed By: mpickering Subscribers: mpickering, rwbarton, thomie, RyanGlScott Tags: #ghc GHC Trac Issues: #13870 Differential Revision: https://phabricator.haskell.org/D3940
* Fix name of noteBen Gamari2017-09-151-1/+1
| | | | [skip ci]
* Fix #13963.Richard Eisenberg2017-09-143-10/+59
| | | | | | | | | | | | | | | This commit fixes several things: 1. RuntimeRep arg suppression was overeager for *visibly*-quantified RuntimeReps, which should remain. 2. The choice of whether to used a Named TyConBinder or an anonymous was sometimes wrong. Now, we do an extra little pass right before constructing the tycon to fix these. 3. TyCons that normally cannot appear unsaturated can appear unsaturated in :kind. But this fact was not propagated into the type checker. It now is.
* Fix #13929 by adding another levity polymorphism checkRichard Eisenberg2017-09-141-5/+4
| | | | test case: typecheck/should_fail/T13929
* Fix #13909 by tweaking an error message.Richard Eisenberg2017-09-141-1/+6
| | | | | | | GHC was complaining about numbers of arguments when the real problem is impredicativity. test case: typecheck/should_fail/T13909
* nativeGen: A few strictness fixesBen Gamari2017-09-142-5/+6
| | | | | | | | | | Test Plan: Validate Reviewers: austin, simonmar Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3948
* Fix #13407 by suppressing invisibles better.Richard Eisenberg2017-09-141-3/+3
| | | | | | | Previously, the iface-invisible-suppresser assumed that all invisible things are up front. Not true! test case: ghci/scripts/T13407
* Remove unused variable bindingSimon Peyton Jones2017-09-141-1/+1
|
* Interim fix for a nasty type-matching bugSimon Peyton Jones2017-09-141-10/+58
| | | | | | | | | | | | | The type matcher in types/Unify.hs was producing a substitution that had variables from the template in its range. Yikes! This patch, documented in Note [Matching in the presence of casts], is an interm fix. Richard and I don't like it much, and are pondering a better solution (Trac #14119). All this came up in investigating Trac #13910. Alas this patch doesn't fix #13910, which still has ASSERT failures, so I have not yet added a test. But the patch does fix a definite bug.
* Refactor tcInferAppsSimon Peyton Jones2017-09-141-28/+31
| | | | | | | | | This is a simple refactor * Remove an unnecessary accumulating argument (acc_hs_apps) from the 'go' function * And put 'n' first in the same function
* Refactor to eliminate FamTyConShapeSimon Peyton Jones2017-09-146-105/+78
| | | | | | | | | | | | | | | | | | | | | | Consider this note (TcTyClsDecls) Note [Type-checking type patterns] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ When typechecking the patterns of a family instance declaration, we can't rely on using the family TyCon itself, because this is sometimes called from within a type-checking knot. (Specifically for closed type families.) The FamTyConShape gives just enough information to do the job. I realised that this exact purpose can be served by TcTyCons, and in fact rather better. So this patch * Refactors FamTyConShape out of existence, replacing it with TcTyCOn * I also got rid Type.filterOutInvisibleTyVars, which was a very complex way to do something quite simple. I replaced the calls with TyCon.tyConVisibleTyVars. No change in behaviour.
* Tidying could cause ill-kinded typesSimon Peyton Jones2017-09-147-81/+114
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | I found (Trac #14175) that the tidying we do when reporting type error messages could cause a well-kinded type to become ill-kinded. Reason: we initialised the tidy-env with a completely un-zonked TidyEnv accumulated in the TcLclEnv as we come across lexical type-varialbe bindings. Solution: zonk them. But I ended up refactoring a bit: * Get rid of tcl_tidy :: TidyEnv altogether * Instead use tcl_bndrs :: TcBinderStack This used to contain only Ids, but now I've added those lexically scoped TyVars too. * Change names: TcIdBinderStack -> TcBinderStack TcIdBinder -> TcBinder extendTcIdBndrs -> extendTcBinderStack * Now tcInitTidyEnv can grab those TyVars from the tcl_bndrs, zonk, and tidy them. The only annoyance is that I had to add TcEnv.hs-boot, to break the recursion between the zonking code and the TrRnMonad functions like addErrTc that call tcInitTidyEnv. Tiresome, but in fact that file existed already.
* Fix subtle bug in TcTyClsDecls.mkGADTVarsSimon Peyton Jones2017-09-141-30/+52
| | | | | | | | | | | | | | | | | This bug was revealed by Trac #14162. In a GADT-style data-family instance we ended up a data constructor whose type mentioned an out-of-scope variable. (This variable was in the kind of a variable in the kind of a variable.) Only Lint complained about this (actually only when the data constructor was injected into the bindings by CorePrep). So it doesn't matter much -- but it's a solid bug and might bite us some day. It took me quite a while to unravel because the test case was itself quite tricky. But the fix is easy; just add a missing binding to the substitution we are building up. It's in the regrettably-subtle mkGADTVars function.
* More refinements to debugPprTypeSimon Peyton Jones2017-09-141-12/+9
|
* No need to check ambiguity for visible type argsSimon Peyton Jones2017-09-141-0/+5
| | | | Seems unnecesarry to me.
* Model divergence of retry# as ThrowsExn, not DivergesBen Gamari2017-09-132-2/+6
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | The demand signature of the retry# primop previously had a Diverges result. However, this caused the demand analyser to conclude that a program of the shape, catchRetry# (... >> retry#) would diverge. Of course, this is plainly wrong; catchRetry#'s sole reason to exist is to "catch" the "exception" thrown by retry#. While catchRetry#'s demand signature correctly had the ExnStr flag set on its first argument, indicating that it should catch divergence, the logic associated with this flag doesn't apply to Diverges results. This resulted in #14171. The solution here is to treat the divergence of retry# as an exception. Namely, give it a result type of ThrowsExn rather than Diverges. Updates stm submodule for tests. Test Plan: Validate with T14171 Reviewers: simonpj, austin Subscribers: rwbarton, thomie GHC Trac Issues: #14171, #8091 Differential Revision: https://phabricator.haskell.org/D3919
* Clarify seq documentationSibi Prabakaran2017-09-131-2/+3
| | | | | | | | | | | | | | | Improves the documentation by specifying that the first argument in seq function is evaluated to WHNF. Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: harendra, rwbarton, thomie GHC Trac Issues: #14213 Differential Revision: https://phabricator.haskell.org/D3945
* Option "-ddump-rn-ast" dumps imports and exports tooAlan Zimmerman2017-09-133-11/+32
| | | | | | | | | | | | | | | | | | Summary: Previously the renamed source decls only were dumped, now the imports, exports and doc_hdr are too. Test Plan: ./validate Reviewers: bgamari, austin Reviewed By: bgamari Subscribers: rwbarton, thomie GHC Trac Issues: #14197 Differential Revision: https://phabricator.haskell.org/D3949
* Use ar for -staticlibMoritz Angermann2017-09-137-22/+395
| | | | | | | | | | | | | | | | Hopefully we can get rid of libtool, by using ar only Depends on: D3579 Test Plan: validate Reviewers: austin, hvr, bgamari, erikd Reviewed By: bgamari Subscribers: rwbarton, thomie, erikd Differential Revision: https://phabricator.haskell.org/D3721
* DriverMkDepend: Kill redundant importBen Gamari2017-09-131-1/+0
| | | | | | | | Reviewers: austin Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3941
* Check if -XStaticPointers is enabled when renaming static expressionsRyan Scott2017-09-131-0/+10
| | | | | | | | | | | | | | | | | | | | | | | Summary: Trying to use `static` expressions without the `-XStaticPointers` extension enabled can lead to runtime errors. Normally, such a situation isn't possible, but Template Haskell provides a backdoor that allows it to happen, as shown in #14204. To prevent this, we ensure that `-XStaticPointers` is enabled when renaming `static` expressions. Test Plan: make test TEST=T14204 Reviewers: facundominguez, austin, bgamari, simonpj Reviewed By: facundominguez, simonpj Subscribers: simonpj, rwbarton, thomie GHC Trac Issues: #14204 Differential Revision: https://phabricator.haskell.org/D3931
* Allow CSE'ing of work-wrapped bindings (#14186)Joachim Breitner2017-09-1211-29/+39
| | | | | | | | the worker/wrapper creates an artificial INLINE pragma, which caused CSE to not do its work. We now recognize such artificial pragmas by using `NoUserInline` instead of `Inline` as the `InlineSpec`. Differential Revision: https://phabricator.haskell.org/D3939
* Canonicalise MonoidFail instances in GHCHerbert Valerio Riedel2017-09-0911-10/+15
| | | | | | | | | | | | | | | | | | | | | | IOW, code compiles -Wnoncanonical-monoidfail-instances clean now This is easy now since we require GHC 8.0/base-4.9 or later for bootstrapping. Note that we can easily enable `MonadFail` via default-extensions: MonadFailDesugaring in compiler/ghc.cabal.in which currently would point out that NatM doesn't have a proper `fail` method, even though failable patterns are made use of: compiler/nativeGen/SPARC/CodeGen.hs:425:25: error: * No instance for (Control.Monad.Fail.MonadFail NatM) arising from a do statement with the failable pattern ‘(dyn_c, [dyn_r])’
* Canonicalise Monoid instances in GHCHerbert Valerio Riedel2017-09-096-15/+12
| | | | IOW, code compiles -Wnoncanonical-monoid-instances clean now
* Remove now redundant cabal conditionals in {ghc,template-haskell}.cabalHerbert Valerio Riedel2017-09-091-9/+3
| | | | | | | | | | | | | | In the past we needed the construct below for wired-in packages, but since GHC 8.0 (which we require at least for stage0 now) the CLI has stabilised, so we can unconditionally use `-this-unit-id` since GHC 8.0. if impl( ghc >= 7.11 ) ghc-options: -this-unit-id template-haskell else if impl( ghc >= 7.9 ) ghc-options: -this-package-key template-haskell else ghc-options: -package-name template-haskell
* Remove now redundant CPPHerbert Valerio Riedel2017-09-093-11/+0
| | | | Resulting from requiring to boot with GHC 8.0 or later
* Deal with unbreakable blocks in Applicative DoDavid Feuer2017-09-071-2/+5
| | | | | | | | | | | | | | | | The renamer wasn't able to deal with more than a couple strict patterns in a row with `ApplicativeDo` when using the heuristic splitter. Update it to work with them properly. Reviewers: simonmar, austin, bgamari, hvr Reviewed By: simonmar Subscribers: RyanGlScott, lippling, rwbarton, thomie GHC Trac Issues: #14163 Differential Revision: https://phabricator.haskell.org/D3900
* Drop special handling of iOS and AndroidMoritz Angermann2017-09-074-13/+2
| | | | | | | | | | | | | | | As far as GHC is concerned, iOS **is** Darwin, and Android **is** Linux. Depends on D3352 Reviewers: austin, hvr, bgamari Reviewed By: bgamari Subscribers: Ericson2314, ryantrinkle, rwbarton, thomie, erikd Differential Revision: https://phabricator.haskell.org/D3579
* Make Semigroup a superclass of Monoid (re #14191)Herbert Valerio Riedel2017-09-071-5/+3
| | | | | | | | | | | | | | | | | | | Unfortunately, this requires introducing a couple of .hs-boot files to break up import cycles (mostly to provide class & typenames in order to be able to write type signatures). This does not yet re-export `(<>)` from Prelude (while the class-name `Semigroup` is reexported); that will happen in a future commit. Test Plan: local ./validate passed Reviewers: ekmett, austin, bgamari, erikd, RyanGlScott Reviewed By: ekmett, RyanGlScott GHC Trac Issues: #14191 Differential Revision: https://phabricator.haskell.org/D3927
* Fix typos in diagnostics, testsuite and commentsGabor Greif2017-09-0718-21/+21
|
* Handle W80 in floatFormatGabor Greif2017-09-071-0/+1
|
* Cleanups, remove commented-out codeGabor Greif2017-09-071-5/+1
| | | | and join type signatures
* Clean up opt and llcMoritz Angermann2017-09-067-166/+207
| | | | | | | | | | | | | | | | | | | | | The LLVM backend shells out to LLVMs `opt` and `llc` tools. This clean up introduces a shared data structure to carry the arguments we pass to each tool so that corresponding flags are next to each other. It drops the hard coded data layouts in favor of using `-mtriple` and have LLVM infer them. Furthermore we add `clang` as a proper tool, so we don't rely on assuming that `clang` is called `clang` on the `PATH` when using `clang` as the assembler. Finally this diff also changes the type of `optLevel` from `Int` to `Word`, as we do not have negative optimization levels. Reviewers: erikd, hvr, austin, rwbarton, bgamari, kavon Reviewed By: kavon Subscribers: michalt, Ericson2314, ryantrinkle, dfeuer, carter, simonpj, kavon, simonmar, thomie, erikd, snowleopard Differential Revision: https://phabricator.haskell.org/D3352
* Implicitly bind kind variables in type family instance RHSes when it's sensibleRyan Scott2017-09-054-36/+132
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | Summary: Before, there was a discrepancy in how GHC renamed type synonyms as opposed to type family instances. That is, GHC would accept definitions like this one: ```lang=haskell type T = (Nothing :: Maybe a) ``` However, it would not accept a very similar type family instance: ```lang=haskell type family T :: Maybe a type instance T = (Nothing :: Maybe a) ``` The primary goal of this patch is to bring the renaming of type family instances up to par with that of type synonyms, causing the latter definition to be accepted, and fixing #14131. In particular, we now allow kind variables on the right-hand sides of type (and data) family instances to be //implicitly// bound by LHS type (or kind) patterns (as opposed to type variables, which must always be explicitly bound by LHS type patterns only). As a consequence, this allows programs reported in #7938 and #9574 to typecheck, whereas before they would have been rejected. Implementation-wise, there isn't much trickery involved in making this happen. We simply need to bind additional kind variables from the RHS of a type family in the right place (in particular, see `RnSource.rnFamInstEqn`, which has undergone a minor facelift). While doing this has the upside of fixing #14131, it also made it easier to trigger #13985, so I decided to fix that while I was in town. This was accomplished by a careful blast of `reportFloatingKvs` in `tcFamTyPats`. Test Plan: ./validate Reviewers: simonpj, goldfire, austin, bgamari Reviewed By: simonpj Subscribers: rwbarton, thomie GHC Trac Issues: #13985, #14131 Differential Revision: https://phabricator.haskell.org/D3872
* StgLint: Show constructor arity in mismatch messageBen Gamari2017-09-051-1/+1
| | | | | | | | Reviewers: austin Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3921
* SetLevels: Substitute in ticks in lvlMFEBen Gamari2017-09-051-1/+2
| | | | | | | | | | | | | | | | | Previously SetLevels.lvlMFE would fail to substitute in ticks, unlike lvlExpr. This lead to #13481. Fix this. Test Plan: `make test TEST=T12622 WAY=ghci` Reviewers: austin, simonpj Reviewed By: simonpj Subscribers: simonpj, rwbarton, thomie GHC Trac Issues: #13481 Differential Revision: https://phabricator.haskell.org/D3920
* Fix egregious duplication of vars in RnTypesRyan Scott2017-09-051-29/+102
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | `RnTypes` contains a fairly intricate algorithm to extract the kind and type variables of an HsType. This algorithm carefully maintains the separation between type variables and kind variables so that the difference between `-XPolyKinds` and `-XTypeInType` can be respected. But after doing all this, `rmDupsInRdrTyVars` stupidly just concatenated the lists of type and kind variables at the end. If a variable were used as both a type and a kind, the algorithm would produce *both*! This led to all kinds of problems, including #13988. This is mostly Richard Eisenberg's patch. The only original contribution I made was adapting call sites of `rnImplicitBndrs` to work with the new definition of `rmDupsInRdrTyVars`. That is, `rnImplicitBndrs` checks for variables that are illegally used in both type and kind positions without using `-XTypeInType`, but in order to check this, one cannot have filtered duplicate variables out before passing them to `rnImplicitBndrs`. To accommodate for this, I needed to concoct variations on the existing `extract-` functions in `RnTypes` which do not remove duplicates, and use those near `rnImplicitBndrs` call sites. test case: ghci/scripts/T13988 Test Plan: make test TEST=T13988 Reviewers: goldfire, simonpj, austin, bgamari Reviewed By: goldfire, simonpj Subscribers: rwbarton, thomie GHC Trac Issues: #13988 Differential Revision: https://phabricator.haskell.org/D3902
* Remember the AvailInfo for each IEalexbiehl2017-09-056-22/+31
| | | | | | | | | | | | | | | | | | | | | | | | | | | | This is another take on https://phabricator.haskell.org/D3844. This patch removes then need for haddock to reimplement the calculation of exported names from modules. Instead when renaming export lists ghc annotates each IE with its exported names. Haddocks current export logic has caused lots of trouble in the past (on the Github issue tracker): - https://github.com/haskell/haddock/issues/121 - https://github.com/haskell/haddock/issues/174 - https://github.com/haskell/haddock/issues/225 - https://github.com/haskell/haddock/issues/344 - https://github.com/haskell/haddock/issues/584 - https://github.com/haskell/haddock/issues/591 - https://github.com/haskell/haddock/issues/597 Updates haddock submodule. Reviewers: austin, bgamari, ezyang Reviewed By: bgamari, ezyang Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3864
* Fix #14167 by using isGadtSyntaxTyCon in more placesRyan Scott2017-09-023-59/+33
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | Summary: Two places in GHC effectively attempt to //guess// whether a data type was declared using GADT syntax: 1. When reifying a data type in Template Haskell 2. When pretty-printing a data type (e.g., via `:info` in GHCi) But there's no need for heuristics here, since we have a 100% accurate way to determine whether a data type was declared using GADT syntax: the `isGadtSyntaxTyCon` function! By simply using that as the metric, we obtain far more accurate TH reification and pretty-printing results. This is technically a breaking change, since Template Haskell reification will now reify some data type constructors as `(Rec)GadtC` that it didn't before, and some data type constructors that were previously reified as `(Rec)GadtC` will no longer be reified as such. But it's a very understandable breaking change, since the previous behavior was simply incorrect. Test Plan: ./validate Reviewers: simonpj, goldfire, austin, bgamari Reviewed By: simonpj Subscribers: rwbarton, thomie GHC Trac Issues: #14167 Differential Revision: https://phabricator.haskell.org/D3901
* Disallow bang/lazy patterns in the RHSes of implicitly bidirectional patsynsRyan Scott2017-09-021-6/+26
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | Summary: GHC was allowing implicitly bidirectional pattern synonyms with bang patterns and irrefutable patterns in the RHS, like so: ```lang=haskell pattern StrictJust a = Just !a ``` This has multiple problems: 1. `Just !a` isn't a valid expression, so it feels strange to allow it in an implicitly bidirectional pattern synonym. 2. `StrictJust` doesn't provide the strictness properties one would expect from a strict constructor. (One could imagine a design where the `StrictJust` builder infers a bang pattern for its pattern variable, but accomplishing this inference in a way that accounts for all possible patterns on the RHS, including other pattern synonyms, is somewhat awkward, so we do not pursue this design.) We nip these issues in the bud by simply disallowing bang/irrefutable patterns on the RHS. Test Plan: make test TEST="T14112 unidir" Reviewers: simonpj, austin, bgamari Reviewed By: simonpj Subscribers: rwbarton, thomie GHC Trac Issues: #14112 Differential Revision: https://phabricator.haskell.org/D3896
* Fix order of PrelRuleBen Gamari2017-09-011-1/+1
| | | | | | | | | | | | Test Plan: Added testcase in D3905. Reviewers: austin Subscribers: angerman, rwbarton, thomie GHC Trac Issues: #14178 Differential Revision: https://phabricator.haskell.org/D3904
* Add missing Semigroup instances to compilerHerbert Valerio Riedel2017-08-3110-58/+96
| | | | | This is a pre-requisite for implementing the Semigroup/Monoid proposal. The instances have been introduced in a way to minimise warnings.
* Really fix Trac #14158Simon Peyton Jones2017-08-311-2/+42
| | | | | | | | | | | | | | | | | I dug more into how #14158 started working. I temporarily reverted the patch that "fixed" it, namely commit a6c448b403dbe8720178ca82100f34baedb1f47e Author: Simon Peyton Jones <simonpj@microsoft.com> Date: Mon Aug 28 17:33:59 2017 +0100 Small refactor of getRuntimeRep Sure enough, there was a real bug, described in the new TcExpr Note [Visible type application zonk] In general, syntactic substituion should be kind-preserving! Maybe we should check that invariant...
* Small changes to ddump-tc tracingSimon Peyton Jones2017-08-314-8/+12
|
* Add debugPprTypeSimon Peyton Jones2017-08-3132-98/+154
| | | | | | | | | | | | | | | | | | | | | | | | | | | We pretty-print a type by converting it to an IfaceType and pretty-printing that. But (a) that's a bit indirect, and (b) delibrately loses information about (e.g.) the kind on the /occurrences/ of a type variable So this patch implements debugPprType, which pretty prints the type directly, with no fancy formatting. It's just used for debugging. I took the opportunity to refactor the debug-pretty-printing machinery a little. In particular, define these functions and use them: ifPprDeubug :: SDoc -> SDOc -> SDoc -- Says what to do with and without -dppr-debug whenPprDebug :: SDoc -> SDoc -- Says what to do with -dppr-debug; without is empty getPprDebug :: (Bool -> SDoc) -> SDoc getPprDebug used to be called sdocPprDebugWith whenPprDebug used to be called ifPprDebug So a lot of files get touched in a very mechanical way