summaryrefslogtreecommitdiff
Commit message (Collapse)AuthorAgeFilesLines
...
* Comments onlySimon Peyton Jones2018-08-312-3/+3
|
* Minor improvements to comments [skip ci]Richard Eisenberg2018-08-302-11/+7
|
* fix -ddump-asm descriptionAlp Mestanogullari2018-08-301-1/+1
| | | | | | | | | | | | | | Summary: It was missing some words. Test Plan: None (docs only) Reviewers: bgamari, monoidal Reviewed By: monoidal Subscribers: rwbarton, carter Differential Revision: https://phabricator.haskell.org/D5102
* A few typos [ci skip]Gabor Greif2018-08-303-3/+3
|
* Fix the __GLASGOW_HASKELL__ comparisonKrzysztof Gogolewski2018-08-302-6/+3
| | | | | | | | | | | | | | | | | Summary: GHC 8.4 corresponds to 804, not 840. Found by Gabor Greif. Test Plan: Harbormaster Reviewers: ggreif, bgamari, mpickering Reviewed By: ggreif Subscribers: rwbarton, carter Differential Revision: https://phabricator.haskell.org/D5064
* Finish stable splitDavid Feuer2018-08-2930-344/+586
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | Long ago, the stable name table and stable pointer tables were one. Now, they are separate, and have significantly different implementations. I believe the time has come to finish the split that began in #7674. * Divide `rts/Stable` into `rts/StableName` and `rts/StablePtr`. * Give each table its own mutex. * Add FFI functions `hs_lock_stable_ptr_table` and `hs_unlock_stable_ptr_table` and document them. These are intended to replace the previously undocumented `hs_lock_stable_tables` and `hs_lock_stable_tables`, which are now documented as deprecated synonyms. * Make `eqStableName#` use pointer equality instead of unnecessarily comparing stable name table indices. Reviewers: simonmar, bgamari, erikd Reviewed By: bgamari Subscribers: rwbarton, carter GHC Trac Issues: #15555 Differential Revision: https://phabricator.haskell.org/D5084
* Fix a constant folding ruleAndrey Mokhov2018-08-291-1/+1
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | Summary: One of the constant folding rules introduced in D2858 is: ``` (L y :-: v) :-: (L x :-: w) -> return $ mkL (y-x) `add` (w `add` v) ``` Or, after removing syntactic noise: `(y - v) - (x - w) ==> (y - x) + (w + v)`. This is incorrect, since the sign of `v` is changed from negative to positive. As a consequence, the following program prints `3` when compiled with `-O`: ``` -- This is just subtraction in disguise minus :: Int -> Int -> Int minus x y = (8 - y) - (8 - x) {-# NOINLINE minus #-} main :: IO () main = print (2 `minus` 1) ``` The correct rule is: `(y - v) - (x - w) ==> (y - x) + (w - v)`. This commit does the fix. I haven't found any other issues with the constant folding code, but it's difficult to be certain without some automated checking. Reviewers: bgamari, tdammers Subscribers: hsyl20, tdammers, rwbarton, carter GHC Trac Issues: #15569 Differential Revision: https://phabricator.haskell.org/D5109
* Fixed typo in exponent examplechris-bacon2018-08-291-1/+1
|
* Rename kind vars in left-to-right order in bindHsQTyVarsRyan Scott2018-08-2813-17/+123
| | | | | | | | | | | | | | | | | | | | Summary: When renaming kind variables in an `LHsQTyVars`, we were erroneously putting all of the kind variables in the binders //after// the kind variables in the body, resulting in #15568. The fix is simple: just swap the order of these two around. Test Plan: make test TEST=T15568 Reviewers: simonpj, bgamari, goldfire Reviewed By: goldfire Subscribers: goldfire, rwbarton, carter GHC Trac Issues: #15568 Differential Revision: https://phabricator.haskell.org/D5108
* Fix typo in 8.6.1 notesKrzysztof Gogolewski2018-08-281-1/+1
|
* Fix #15572 by checking for promoted names in ConTRyan Scott2018-08-284-1/+23
| | | | | | | | | | | | | | | | | | | | | | Summary: When converting `ConT`s to `HsTyVar`s in `Convert`, we were failing to account for the possibility of promoted data constructor names appearing in a `ConT`, which could result in improper pretty-printing results (as observed in #15572). The fix is straightforward: use `Promoted` instead of `NotPromoted` when the name of a `ConT` is a data constructor name. Test Plan: make test TEST=T15572 Reviewers: goldfire, bgamari, simonpj, monoidal Reviewed By: goldfire, simonpj Subscribers: monoidal, rwbarton, carter GHC Trac Issues: #15572 Differential Revision: https://phabricator.haskell.org/D5112
* Remove dead code for commandline parsingKrzysztof Gogolewski2018-08-282-16/+1
| | | | | | | | | | | | | | | | Summary: PrefixPred and AnySuffixPred are not used since static flags were removed in bbd3c399939. Test Plan: validate Reviewers: bgamari, tdammers Reviewed By: tdammers Subscribers: rwbarton, carter Differential Revision: https://phabricator.haskell.org/D5111
* rts: Handle SMALL_MUT_ARR_PTRS in retainer profilterBen Gamari2018-08-281-0/+4
| | | | | | | | | | | | | | Summary: These can be treated similarly to MUT_ARRY_PTRS. Fixes #15529. Reviewers: erikd, simonmar Reviewed By: simonmar Subscribers: RyanGlScott, rwbarton, carter GHC Trac Issues: #15529 Differential Revision: https://phabricator.haskell.org/D5075
* Remove dph, vector, primitive and random from .gitmodulesChaitanya Koparkar2018-08-271-16/+0
| | | | | | | | | | | | | | Summary: These packages were removed from the GHC source tree in Phab:D4761 and 0905fec089b3270f540c7ee33959cbf8ecfcb4d7. Reviewers: RyanGlScott, bgamari Reviewed By: RyanGlScott Subscribers: rwbarton, carter Differential Revision: https://phabricator.haskell.org/D5095
* Bump nofib submoduleKrzysztof Gogolewski2018-08-271-0/+0
|
* Fix #10859 by using foldr1 while deriving Eq instancesChaitanya Koparkar2018-08-271-1/+3
| | | | | | | | | | | | | | | | | | Summary: Previously, we were using foldl1 instead, which led to the derived code to be wrongly associated. Test Plan: ./validate Reviewers: RyanGlScott, nomeata, simonpj, bgamari Reviewed By: RyanGlScott, nomeata Subscribers: rwbarton, carter GHC Trac Issues: #10859 Differential Revision: https://phabricator.haskell.org/D5104
* Don't reify redundant class method tyvars/contextsRyan Scott2018-08-276-18/+32
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | Summary: Currently, reifying classes produces class methods with redundant tyvars and class contexts in their type signatures, such as in the following: ```lang=haskell class C a where method :: forall a. C a => a ``` Fixing this is very straightforward: just apply `tcSplitMethodTy` to the type of each class method to lop off the redundant parts. It's possible that this could break some TH code in the wild that assumes the existence of these tyvars and class contexts, so I'll advertise this change in the release notes just to be safe. Test Plan: make test TEST="TH_reifyDecl1 T9064 T10891 T14888" Reviewers: goldfire, bgamari, simonpj Reviewed By: simonpj Subscribers: simonpj, rwbarton, carter GHC Trac Issues: #15551 Differential Revision: https://phabricator.haskell.org/D5088
* Take strict fields into account in coverage checkingRyan Scott2018-08-276-60/+338
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | Summary: The current pattern-match coverage checker implements the formalism presented in the //GADTs Meet Their Match// paper in a fairly faithful matter. However, it was discovered recently that there is a class of unreachable patterns that //GADTs Meet Their Match// does not handle: unreachable code due to strict argument types, as demonstrated in #15305. This patch therefore goes off-script a little and implements an extension to the formalism presented in the paper to handle this case. Essentially, when determining if each constructor can be matched on, GHC checks if its associated term and type constraints are satisfiable. This patch introduces a new form of constraint, `NonVoid(ty)`, and checks if each constructor's strict argument types satisfy `NonVoid`. If any of them do not, then that constructor is deemed uninhabitable, and thus cannot be matched on. For the full story of how this works, see `Note [Extensions to GADTs Meet Their Match]`. Along the way, I did a little bit of much-needed refactoring. In particular, several functions in `Check` were passing a triple of `(ValAbs, ComplexEq, Bag EvVar)` around to represent a constructor and its constraints. Now that we're adding yet another form of constraint to the mix, I thought it appropriate to turn this into a proper data type, which I call `InhabitationCandidate`. Test Plan: make test TEST=T15305 Reviewers: simonpj, bgamari Reviewed By: simonpj Subscribers: rwbarton, carter GHC Trac Issues: #15305 Differential Revision: https://phabricator.haskell.org/D5087
* Fix #15502 by not casting to Int during TH conversionRyan Scott2018-08-274-2/+26
| | | | | | | | | | | | | | | | | | | | | | | Summary: When turning an `IntegerL` to an `IntegralLit` during TH conversion, we were stupidly casting an `Integer` to an `Int` in order to determine how it should be pretty-printed. Unsurprisingly, this causes problems when the `Integer` doesn't lie within the bounds of an `Int`, as demonstrated in #15502. The fix is simple: don't cast to an `Int`. Test Plan: make test TEST=T15502 Reviewers: bgamari, simonpj Reviewed By: simonpj Subscribers: simonpj, rwbarton, carter GHC Trac Issues: #15502 Differential Revision: https://phabricator.haskell.org/D5089
* Fix #15550 by quoting RULE names during TH conversionRyan Scott2018-08-274-2/+22
| | | | | | | | | | | | | | | | | | | Summary: When converting a `RuleP` to a GHC source `RuleD` during TH conversion, we were stupidly not double-quoting the name of the rule. Easily fixed. Test Plan: make test TEST=T15550 Reviewers: goldfire, bgamari, simonpj Reviewed By: simonpj Subscribers: simonpj, rwbarton, carter GHC Trac Issues: #15550 Differential Revision: https://phabricator.haskell.org/D5090
* ghc, ghc-pkg: use getExecutablePath on Windows when base >= 4.11.0Tamar Christina2018-08-253-17/+53
| | | | | | | | | | | | | | | | | | | | | | | | | | | Summary: This completes the work started in D4227 by using just 'getExecutablePath' in ghc and ghc-pkg when building with base >= 4.11.0. On the long term, we will be able to simply kill the existing code that follows (or not) symlinks and just get this behaviour for free from getExecutable. For now we however have to require base >= 4.11.0 to be able to just use getExecutablePath under Windows, and use the current code when building with an older base. Original code by @alpmestan commandeering since patch has been stale and bug remains open. Test Plan: Validate Reviewers: angerman, bgamari, erikd, alpmestan Reviewed By: bgamari Subscribers: carter, rwbarton, thomie GHC Trac Issues: #14483 Differential Revision: https://phabricator.haskell.org/D4229
* Better error reporting for inaccessible codeSimon Peyton Jones2018-08-249-30/+58
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | This patch fixes Trac #15558. There turned out to be two distinct problems * In TcExpr.tc_poly_expr_nc we had tc_poly_expr_nc (L loc expr) res_ty = do { traceTc "tcPolyExprNC" (ppr res_ty) ; (wrap, expr') <- tcSkolemiseET GenSigCtxt res_ty $ \ res_ty -> setSrcSpan loc $ -- NB: setSrcSpan *after* skolemising, -- so we get better skolem locations tcExpr expr res_ty Putting the setSrcSpan inside the tcSkolemise means that the location on the Implication constraint is the /call/ to the function rather than the /argument/ to the call, and that is really quite wrong. I don't know what Richard's comment NB means -- I moved the setSrcSpan outside, and the "binding site" info in error messages actually improved. The reason I found this is that it affects the span reported for Trac #15558. * In TcErrors.mkGivenErrorReporter we carefully munge the location for an insoluble Given constraint (Note [Inaccessible code]). But the 'implic' passed in wasn't necesarily the immediately- enclosing implication -- but for location-munging purposes it jolly well should be. Solution: use the innermost implication. This actually simplifies the code -- no need to pass an implication in to mkGivenErrorReporter.
* Add comments about pretty-printing via IfaceSynSimon Peyton Jones2018-08-244-55/+67
| | | | | Provoked by discussion on Phab:D5097 (Trac #15546), I'm adding a big Note explaing the strategy of pretty-printing via IfaceSyn
* Comments onlySimon Peyton Jones2018-08-241-1/+3
|
* Clean up TcHsSyn.zonkEnvSimon Peyton Jones2018-08-2410-158/+161
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | Triggered by Trac #15552, I'd been looking at ZonkEnv in TcHsSyn. This patch does some minor refactoring * Make ZonkEnv into a record with named fields, and use them. (I'm planning to add a new field, for TyCons, so this prepares the way.) * Replace UnboundTyVarZonker (a higer order function) with the simpler and more self-descriptive ZonkFlexi data type, below. It's just much more perspicuous and direct, and (I suspect) a tiny bit faster too -- no unknown function calls. data ZonkFlexi -- See Note [Un-unified unification variables] = DefaultFlexi -- Default unbound unificaiton variables to Any | SkolemiseFlexi -- Skolemise unbound unification variables -- See Note [Zonking the LHS of a RULE] | RuntimeUnkFlexi -- Used in the GHCi debugger There was one knock-on effect in the GHCi debugger -- the RuntimeUnkFlexi case. Somehow previously, these RuntimeUnk variables were sometimes getting SystemNames (and hence printed as 'a0', 'a1', etc) and sometimes not (and hence printed as 'a', 'b' etc). I'm not sure precisely why, but the new behaviour seems more uniform, so I just accepted the (small) renaming wibbles in some ghci.debugger tests. I had a quick look at perf: any changes are tiny.
* Update unicode tables to v. 12 of the standardArtem Pelenitsyn2018-08-236-1192/+1548
| | | | | | | | | | | | Reviewers: hvr, bgamari, Azel Reviewed By: bgamari Subscribers: thomie, Azel, rwbarton, carter GHC Trac Issues: #5518, #15525 Differential Revision: https://phabricator.haskell.org/D5066
* docs: Add changelog and release notes entry for traceBinaryEvent#Ben Gamari2018-08-232-0/+14
|
* TcSimplify: Condense MASSERT2() usage onto a single lineBen Gamari2018-08-231-3/+1
| | | | | Sadly macOS's C preprocessor gets angry at the sight of multi-line macro invocations.
* Accommodate API change in transSuperClassesSimon Peyton Jones2018-08-232-4/+3
| | | | | | | | | | | | | | | | | | | | | | | | In this patch commit 6eabb6ddb7c53784792ee26b1e0657bde7eee7fb Author: Simon Peyton Jones <simonpj@microsoft.com> Date: Tue Dec 15 14:26:13 2015 +0000 Allow recursive (undecidable) superclasses I changed (transSuperClasses p) to return only the superclasses of p, but not p itself. (Previously it always returned p as well.) The use of transSuperClasses in TcErrors.warnRedundantConstraints really needs 'p' in the result -- but I faild to fix this call site, and instead crippled the test for Trac #10100. This patch sets things right * Accomodates the API change * Re-enables T10100 * And thereby fixes Trac #11474
* Comments onlySimon Peyton Jones2018-08-234-26/+43
|
* Fix a typo in TcValidity.checkFamInstRhsSimon Peyton Jones2018-08-233-11/+23
| | | | | | | | | | | | | | | | | | | | | In error message generation we were using the wrong type constructor in inst_head. Result: the type became ill-kinded, and that sent the compiler into a loop. A separate patch fixes the loop. This patch fixes the actual bug -- Trac #15473. I also improved the "occurs more often" error message a bit. But it's still pretty terrible: * Variable ‘a’ occurs more often in the type family application ‘Undefined’ than in the instance head ‘LetInterleave xs t ts is y z’ It looks like nonsense, but all becomes clear if you use -fprint-explicit-kinds. Really we should fix this by spotting when invisible arguments are involved and at least suggesting -fprint-explicit-kinds.
* Turn infinite loop into a panicSimon Peyton Jones2018-08-222-7/+22
| | | | | | | | | | | | | | In these two functions * TcIface.toIfaceAppTyArgsX * Type.piResultTys we take a type application (f t1 .. tn) and try to find its kind. It turned out that, if (f t1 .. tn) was ill-kinded the function would go into an infinite loop. That's not good: it caused the loop in Trac #15473. This patch doesn't fix the bug in #15473, but it does turn the loop into a decent panic, which is a step forward.
* Revert "driver: unconditionally disable relaxation when linking partially"Ryan Scott2018-08-221-4/+5
| | | | | | | | This reverts commit 1cc9061fce4270739677d475190fd6e890e8b1f9. This appears to break a clean build with certain versions of `ld.gold`. See https://phabricator.haskell.org/rGHC1cc9061fce42#132967.
* Revert "Properly tag fun field of PAPs generated by ap_0_fast"Ömer Sinan Ağacan2018-08-221-8/+6
| | | | | | This reverts commit 2693eb11f55f2001701c90c24183e21c794a8be1. This patch isn't ready yet, see D5051.
* Add traceBinaryEvent# primopMitsutoshi Aoe2018-08-2114-9/+130
| | | | | | | | | | | | | | | | | | | | | | | | | | | | This adds a new primop called traceBinaryEvent# that takes the length of binary data and a pointer to the data, then emits it to the eventlog. There is some example code that uses this primop and the new event: * [traceBinaryEventIO][1] that calls `traceBinaryEvent#` * [A patch to ghc-events][2] that parses the new `EVENT_USER_BINARY_MSG` There's no corresponding issue on Trac but it was discussed at ghc-devs [3]. [1] https://github.com/maoe/ghc-trace-events/blob /fb226011ef1f85a97b4da7cc9d5f98f9fe6316ae/src/Debug/Trace/Binary.hs#L29) [2] https://github.com/maoe/ghc-events/commit /239ca77c24d18cdd10d6d85a0aef98e4a7c56ae6) [3] https://mail.haskell.org/pipermail/ghc-devs/2018-May/015791.html Reviewers: bgamari, erikd, simonmar Reviewed By: bgamari Subscribers: rwbarton, thomie, carter Differential Revision: https://phabricator.haskell.org/D5007
* docs: "state transformer" -> "state monad" / "ST" (whichever is meant)Artem Pelenitsyn2018-08-2110-30/+30
| | | | | | | | | | | | | | FIxes #15189. Reviewers: hvr, bgamari, simonmar, simonpj Reviewed By: simonpj Subscribers: simonpj, rwbarton, thomie, carter GHC Trac Issues: #15189 Differential Revision: https://phabricator.haskell.org/D5019
* Fix precision of asinh/acosh/atanh by making them primopsArtem Pelenitsyn2018-08-219-14/+94
| | | | | | | | | | Reviewers: hvr, bgamari, simonmar, jrtc27 Reviewed By: bgamari Subscribers: alpmestan, rwbarton, thomie, carter Differential Revision: https://phabricator.haskell.org/D5034
* Correct limb length and assertion for gcdExtIntegerDavidEichamnn2018-08-213-3/+46
| | | | | | | | | | | | Reviewers: hvr, bgamari, monoidal Reviewed By: monoidal Subscribers: monoidal, rwbarton, thomie, carter GHC Trac Issues: #15350 Differential Revision: https://phabricator.haskell.org/D5042
* Properly tag fun field of PAPs generated by ap_0_fastÖmer Sinan Ağacan2018-08-211-6/+8
| | | | | | | | | | | | | | | | | | | | | | | | | Currently ap_0_fast doesn't maintain the invariant for PAP fun fields which says if the closure can be tagged, it should be. This is checked by `Sanity.c:checkPAP` and correctly implemented by `genautoapply`. This causes sanity check failures when we have a profiling code like f = {-# SCC scc #-} g where g is a PAP or a FUN, and `scc` is different than the current cost centre. Test Plan: Slow validate (not done yet) Reviewers: simonmar, bgamari, erikd Reviewed By: simonmar Subscribers: rwbarton, carter GHC Trac Issues: #15508 Differential Revision: https://phabricator.haskell.org/D5051
* rts: Align the_gc_thread to 64 bytesBen Gamari2018-08-211-1/+3
| | | | | | | | | | | | | | | | | | | | | In a previous attempt (c6cc93bca69abc258513af8cf2370b14e70fd8fb) I had tried aligning to 8 bytes under the assumption that the problem was that the_gc_thread, a StgWord8[], wasn't being aligned to 8-bytes as the gc_thread struct would expect. However, we actually need even stronger alignment due to the alignment attribute attached to gen_workspace, which claims it should be aligned to a 64-byte boundary. This fixes #15482. Reviewers: erikd, simonmar Reviewed By: simonmar Subscribers: rwbarton, carter GHC Trac Issues: #15482 Differential Revision: https://phabricator.haskell.org/D5052
* Show -with-rtsopts options in runtime's --info (#15261)roland2018-08-2111-4/+32
| | | | | | | | | | | | | | | | | | Add an additional line to the output of +RTS --info. It shows the value of the flag -with-rtsopts provided at compile/link time. Test Plan: make test TESTS="T15261a T15261b" Reviewers: hvr, erikd, dfeuer, thomie, austin, bgamari, simonmar, osa1, monoidal Reviewed By: osa1, monoidal Subscribers: osa1, rwbarton, carter GHC Trac Issues: #15261 Differential Revision: https://phabricator.haskell.org/D5053
* Fix ambiguous/out-of-scope Haddock identifiersAlec Theriault2018-08-2158-254/+262
| | | | | | | | | | | | | | | | | This drastically cuts down on the number of Haddock warnings when making docs for `base`. Plus this means more actual links end up in the docs! Also fixed other small mostly markup issues in the documentation along the way. This is a docs-only change. Reviewers: hvr, bgamari, thomie Reviewed By: thomie Subscribers: thomie, rwbarton, carter Differential Revision: https://phabricator.haskell.org/D5055
* base: Mark `findIndices` as INLINABLE instead of INLINE (fixes #15426)Kevin Buhr2018-08-213-1/+25
| | | | | | | | | | | | | | | | | | | | If `findIndices` is marked INLINE in `Data.OldList`, then the unfolded versions of `elemIndex` and `findIndex` included in the interface file are unfusible (even though `findIndices` itself remains fusible). By marking it INLINABLE instead, elemIndex` and `findIndex` will fuse properly. Test Plan: make TEST=T15426 Reviewers: hvr, bgamari Reviewed By: bgamari Subscribers: rwbarton, carter GHC Trac Issues: #15426 Differential Revision: https://phabricator.haskell.org/D5063
* rts/RetainerProfile: Dump closure type if pop() failsRyan Scott2018-08-211-1/+1
| | | | | | | | | | | | | | | | While investigating #15529, I noticed that the `barf`ed error message in `pop()` doesn't print out the closure type that causes it to crash. Let's do so. Reviewers: bgamari, erikd, simonmar Reviewed By: bgamari Subscribers: rwbarton, carter GHC Trac Issues: #15529 Differential Revision: https://phabricator.haskell.org/D5072
* Explicitly tell 'getNameToInstances' mods to loadAlec Theriault2018-08-212-5/+13
| | | | | | | | | | | | | | | | | | | Calculating which modules to load based on the InteractiveContext means maintaining a potentially very large GblRdrEnv. In Haddock's case, it is much cheaper (from a memory perspective) to just keep track of which modules interfaces we want loaded then hand these off explicitly to 'getNameToInstancesIndex'. Bumps haddock submodule. Reviewers: alexbiehl, bgamari Reviewed By: alexbiehl Subscribers: rwbarton, thomie, carter Differential Revision: https://phabricator.haskell.org/D5003
* testsuite: Deduplicate source in wcompat-warnings testBen Gamari2018-08-217-101/+44
|
* Simplify callSiteInline a littleSimon Peyton Jones2018-08-211-17/+16
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | This patch has virtually no effect on anything (according to a nofib run). But it simplifies the definition of interesting_call by being a bit less gung-ho about inlining nested function bindings. See Note [Nested functions] ----------------------------------------------------------------------- Program Size Allocs Runtime Elapsed TotalMem ----------------------------------------------------------------------- anna +0.2% -0.0% 0.163 0.163 0.0% binary-trees +0.1% +0.0% -4.5% -4.5% 0.0% cacheprof -0.1% +0.1% -4.7% -4.8% +2.7% fasta +0.2% 0.0% +2.6% +3.0% 0.0% fluid -0.0% -0.6% 0.011 0.011 0.0% gamteb -0.1% -0.0% 0.069 0.070 0.0% hpg +0.1% +0.0% +0.7% +0.7% 0.0% infer +0.3% +0.2% 0.097 0.098 0.0% lambda -0.1% -0.0% +2.0% +2.0% 0.0% n-body +0.1% -0.1% -0.1% -0.1% 0.0% simple -0.2% -0.2% +0.6% +0.6% 0.0% spectral-norm +0.1% -0.0% -0.1% -0.1% 0.0% tak -0.0% -0.1% 0.024 0.024 0.0% -------------------------------------------------------------------------------- Min -0.4% -0.6% -5.3% -5.3% 0.0% Max +0.3% +0.2% +3.3% +3.3% +15.0% Geometric Mean -0.0% -0.0% -0.3% -0.3% +0.2% (cherry picked from commit 33de71fa06d03e6da396a7c0a314fea3b492ab91) (This reverts the previous reversion in commit 9dbf66d74e65309d02c9d700094e363f59c94096)
* Introduce flag -keep-hscpp-filesroland2018-08-218-0/+47
| | | | | | | | | | | | | | Test Plan: `make test=T10869` Reviewers: mpickering, thomie, ezyang, bgamari Reviewed By: thomie, bgamari Subscribers: rwbarton, carter GHC Trac Issues: #10869 Differential Revision: https://phabricator.haskell.org/D4861
* function-section: enable on windowsTamar Christina2018-08-211-1/+1
| | | | | | | | | | | | | | | | | gc-sections was onced observed to be slow on Windows, which is the only reason it's not enabled yet. However, it seems to be better now. Test Plan: ./validate Reviewers: bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie, carter GHC Trac Issues: #15051 Differential Revision: https://phabricator.haskell.org/D4916
* Replace most occurences of foldl with foldl'.klebinger.andreas@gmx.at2018-08-2169-128/+115
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | This patch adds foldl' to GhcPrelude and changes must occurences of foldl to foldl'. This leads to better performance especially for quick builds where GHC does not perform strictness analysis. It does change strictness behaviour when we use foldl' to turn a argument list into function applications. But this is only a drawback if code looks ONLY at the last argument but not at the first. And as the benchmarks show leads to fewer allocations in practice at O2. Compiler performance for Nofib: O2 Allocations: -1 s.d. ----- -0.0% +1 s.d. ----- -0.0% Average ----- -0.0% O2 Compile Time: -1 s.d. ----- -2.8% +1 s.d. ----- +1.3% Average ----- -0.8% O0 Allocations: -1 s.d. ----- -0.2% +1 s.d. ----- -0.1% Average ----- -0.2% Test Plan: ci Reviewers: goldfire, bgamari, simonmar, tdammers, monoidal Reviewed By: bgamari, monoidal Subscribers: tdammers, rwbarton, thomie, carter Differential Revision: https://phabricator.haskell.org/D4929