[GHC] #13227: Loss of full laziness in mapFB

#13227: Loss of full laziness in mapFB
-------------------------------------+-------------------------------------
Reporter: simonpj | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.0.1
Keywords: | Operating System: Unknown/Multiple
Architecture: | Type of failure: None/Unknown
Unknown/Multiple |
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
I've just discovered this
{{{
g4 x expensive ys = let h = \7 -> y + expensive x
in map h ys
}}}
Of course we'd expect the `(expensive x)` call to be floated out of the
`\y`-abstraction, so that it is only done once.
But it isn't! Here's the simplified core with -O:
{{{
g4 = \ (@ b_aPG)
(@ p_atr)
($dNum_aPP :: Num b)
(x_arW :: p)
(expensive_arX :: p -> b)
(ys_arY :: [b]) ->
map @ b @ b
(\ (y_as0 [OS=ProbOneShot] :: b) ->
+ @ b $dNum_aPP y_as0 (expensive_arX x_arW))
ys_arY
}}}
Yikes! What is happening?
Answer: look at that suspicious `ProbOneShot` on the `\y` above. Read
`Note [Computing one-shot info, and ProbOneShot]` in `Demand.hs`.
When `FloatOut` runs we have
{{{
g4 = \ (@ b_aPL)
(@ p_atw)
($dNum_aPU :: Num b)
(x_as1 :: p)
(expensive_as2 :: p -> b)
(ys_as3 :: [b]) ->
GHC.Base.build @ b
(\ (@ b1_aQs)
(c_aQt [OS=OneShot] :: b -> b1 -> b1)
(n_aQu [OS=OneShot] :: b1) ->
GHC.Base.foldr @ b @ b1
(GHC.Base.mapFB @ b @ b1 @ b
c_aQt
(\ (y_as5 [OS=ProbOneShot] :: b) ->
+ @ b $dNum_aPU y_as5 (expensive_as2 x_as1)))
n_aQu
ys_as3)
}}}
Why is the `\y` marked `ProbOneShot`? Because the occurrence analyser
marked it so, based on the cardinality info from `mapFB`, even though
`mapFB` was not saturated.
So `Demand.argsOneShots` makes a deliberate choice to play risky, and that
choice backfires badly for use of `map`. Not good!
The offending commit, which introduced this behaviour, is (I think)
{{{
commit 80989de947dc7edb55999456d1c1e8c337efc951
Author: Simon Peyton Jones

#13227: Loss of full laziness in mapFB -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by nomeata): * cc: nomeata (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13227#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13227: Loss of full laziness in mapFB -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by nomeata): That reminds me of a question that I had a long time: What is the precise semantics of `ProbOneShot`? I only understand `OneShot`… I read `Note [Computing one-shot info, and ProbOneShot]` and it seems that the compiler is acting according to plan (marking this partial application as `ProbOneShot`, and then not floating the expression out). Are you saying that the plan as described in the note might be bogus, or is the implementation not doing what it should? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13227#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13227: Loss of full laziness in mapFB -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): I'm saying that the plan is counter-productive in this case. Step 1: remove `ProbOneShot` and see what, if anything, gets worse. It's a very local change. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13227#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13227: Loss of full laziness in mapFB
-------------------------------------+-------------------------------------
Reporter: simonpj | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.0.1
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Joachim Breitner

#13227: Loss of full laziness in mapFB -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by nomeata): Step 1 happening on branch `wip/T13227`. Let’s see what perf.haskell.org will have to say on that. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13227#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13227: Loss of full laziness in mapFB -------------------------------------+------------------------------------- Reporter: simonpj | Owner: nomeata Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * owner: => nomeata Comment: Great, thanks! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13227#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13227: Loss of full laziness in mapFB -------------------------------------+------------------------------------- Reporter: simonpj | Owner: nomeata Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by nomeata): Looks like a clear win. According to perf.haskell.org (which does run nofib!), the only significant changes are time improvements of 3.5% for cacheprof and k-nucleotide: https://perf.haskell.org/ghc/#revision/4c5af213a9fff60ca8de2ed9f5ae28955d21b... These might be spurious, as allocations do not change. But even if really nothing changes, as this is a simplifying commit, from this point of view there is no reason not do it. And I’d be happy to get rid of this rather squishy notion of “probably” one-shot. I will prepare a DR for review. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13227#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13227: Loss of full laziness in mapFB -------------------------------------+------------------------------------- Reporter: simonpj | Owner: nomeata Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3067 Wiki Page: | -------------------------------------+------------------------------------- Changes (by nomeata): * status: new => patch * differential: => Phab:D3067 Comment: DR at Phab:D3067 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13227#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13227: Loss of full laziness in mapFB -------------------------------------+------------------------------------- Reporter: simonpj | Owner: nomeata Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3067 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Joachim, I have resurrected from my hind-brain what was, perhaps, the original issue. Consider something like {{{ recover (f (\x. blah)) bloo }}} where `recover` :: (Exception -> IO a) -> IO a -> IO a` is some kind of exception handling. And `f` is something like {{{ f :: (Exception -> a) -> Exception -> IO a f g exn = return (g exn) }}} Now, is the `\x` one-shot or not? Well, if `f` is applied to three args (the exception and the state token, then it'll call `g` exactly once`, so yes the `\x` will be one shot. And hence there is no point floating a thunk out of `blah`. Indeed doing so is positively harmful because it adds allocation before calling `recover`, and that allocation is only used on the cold (exception-handling) path. And yet with your change, we won't recognise that, because the call to `f` is not syntactically saturated. Moreover, the occurrence analyser is the '''only''' place where one-shot info is added to lambdas. See your patch in #11770. (I'd like this fact to be more clearly called out... I had to re-discover it today. It is stated in `Note [Use one-shot information]` but not very loudly.) So we might ask 1. Does this matter? Does it actually occur in practice? Your measurements suggest not. 2. Would be easy to fix? I think it might be. Concerning (2), look at the call to `argsOneShots` in `occAnalApp`. We pass `n_val_args` to `argsOneShots`. Consider something like {{{ f (g (\y.e)) }}} and suppose * `f` has a strictness sigature like `C1(L)`, saying that it calls its argument at most once * `g` has a strictness signature like `C1(L)L`, saying that when applied to two args it calls its first arg at most once. Then when we are doing `occAnalApp` for `g (\y.e)` we will have `[NoOneShot]` in the `occ_one_shots` field of `OccEnv`... that comes from `f` which guarantees to call its arg once. So I think we can just add the length of `occ_one_shots` to `n_val_args` before passing to `argsOneShots`. And that is so easy it'd be worth doing. Here's a concrete test case {{{ w :: (Int -> a) -> a w g = g 1 {-# NOINLINE w #-} f :: (Int -> Bool) -> a -> [Bool] f g _ = [g 1, True, False] {-# NOINLINE f #-} h xs = w (f (\y -> null (reverse xs))) }}} You'll see that `null (reverse xs)` is floated out -- and it should not be. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13227#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13227: Loss of full laziness in mapFB
-------------------------------------+-------------------------------------
Reporter: simonpj | Owner: nomeata
Type: bug | Status: patch
Priority: normal | Milestone:
Component: Compiler | Version: 8.0.1
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s): Phab:D3067
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Joachim Breitner

#13227: Loss of full laziness in mapFB -------------------------------------+------------------------------------- Reporter: simonpj | Owner: nomeata Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3067 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Will you pursue comment:9? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13227#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13227: Loss of full laziness in mapFB -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3067 Wiki Page: | -------------------------------------+------------------------------------- Changes (by nomeata): * status: patch => new * owner: nomeata => Comment:
According to perf.haskell.org (which does run nofib!), the only significant changes are time improvements of 3.5% for cacheprof and k-nucleotid.
Indeed, these improvements (with -2.7% resp. -4.16% for the final commit) seem to be genuine, and not just flaky measurements. :-)
Will you pursue comment:9?
Will give it a shot. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13227#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13227: Loss of full laziness in mapFB -------------------------------------+------------------------------------- Reporter: simonpj | Owner: nomeata Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3067 Wiki Page: | -------------------------------------+------------------------------------- Changes (by nomeata): * owner: => nomeata -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13227#comment:13 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13227: Loss of full laziness in mapFB -------------------------------------+------------------------------------- Reporter: simonpj | Owner: nomeata Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3067 Wiki Page: | -------------------------------------+------------------------------------- Comment (by nomeata): I gave it a shot, but something is clearly still wrong, I get huge regressions in performance tests. I will try counting only the length of the `OneShot` prefix of `occ_one_shots` (which seems to make more sense to me). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13227#comment:14 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13227: Loss of full laziness in mapFB -------------------------------------+------------------------------------- Reporter: simonpj | Owner: nomeata Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3067 Wiki Page: | -------------------------------------+------------------------------------- Comment (by nomeata): Results are back: https://perf.haskell.org/ghc/#compare/54b9b064fc7960a4dbad387481bc3a6496cc39... (not sure how stable that link is given that this is a rebasing branch) With only adding `length (takeWhile isOneShotInfo (occ_one_shots env))`, nofib allocations are stable. This suggests that this is a sane thing to do, i.e. we do not duplicate any work. Binary sizes go down by -0.7% throughout the bank, so there is relevant effect. We get a run-time performance loss in `binary-trees` by 9%. `binary-trees` benefited strongly from Join Point, so my blind guess is that in some instance here, floating out is beneficial as it turned something into a join point. Morally, the code is what we want (it makes the analysis more precise). I guess we should check out the performance fall out in `binary-tree`, though… You can have a look at the code at Phab:D3089. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13227#comment:15 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13227: Loss of full laziness in mapFB -------------------------------------+------------------------------------- Reporter: simonpj | Owner: nomeata Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3067 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj):
With only adding length (takeWhile isOneShotInfo (occ_one_shots env))
Yes that's right. Sorry. If we commit this we need a serious Note. I like binary size decreases! It would be good to understand `binary_tree`; although I have no idea how to investigate runtime changes.... -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13227#comment:16 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13227: Loss of full laziness in mapFB -------------------------------------+------------------------------------- Reporter: simonpj | Owner: nomeata Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3067 Wiki Page: | -------------------------------------+------------------------------------- Comment (by rwbarton): Also, what about those haddock allocation regressions? Any idea what that could be about? Rather curious. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13227#comment:17 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13227: Loss of full laziness in mapFB -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Joachim | Breitner Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3067 Wiki Page: | -------------------------------------+------------------------------------- Changes (by Joachim Breitner): * status: new => closed * resolution: => fixed Comment: Phab:D3089 has landed as changeset:a1980ecb5626ec85fc14fbd217e2d16c7d50a120. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13227#comment:18 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13227: Loss of full laziness in mapFB -------------------------------------+------------------------------------- Reporter: simonpj | Owner: nomeata Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3067 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Joachim, could you add the test case in comment:9 as a regression test? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13227#comment:19 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13227: Loss of full laziness in mapFB -------------------------------------+------------------------------------- Reporter: simonpj | Owner: nomeata Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3067 Wiki Page: | -------------------------------------+------------------------------------- Comment (by nomeata): In fact, I tried doing that right when you posted comment:9. I tried to modify so that unwanted floating would be detectable in the output by some carefully placed `trace`, but I did not manage that. (I dislike tests that grep in `-ddump-simpl`, they are too fragile.) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13227#comment:20 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13227: Loss of full laziness in mapFB -------------------------------------+------------------------------------- Reporter: simonpj | Owner: nomeata Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3067 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): I fixed a small bug in the new one-shot stuff, in this patch {{{ commit fc9d152b058f21ab03986ea722d0c94688b9969f Author: Simon Peyton Jones < simonpj@microsoft.com > Date: Thu Feb 16 09:41:55 2017 +0000 Comments and tiny refactor only }}} Here's the critical bit {{{ --- a/compiler/simplCore/OccurAnal.hs +++ b/compiler/simplCore/OccurAnal.hs @@ -1867,17 +1867,17 @@ occAnalApp env (Var fun, args, ticks) -- This is the *whole point* of the isRhsEnv predicate -- See Note [Arguments of let-bound constructors] - n_val_args = valArgCount args + length (takeWhile isOneShotInfo (occ_one_shots env)) - -- See Note [Sources of one-shot information], bullet point A' - + n_val_args = valArgCount args n_args = length args fun_uds = mkOneOcc env fun (n_val_args > 0) n_args is_exp = isExpandableApp fun n_val_args -- See Note [CONLIKE pragma] in BasicTypes -- The definition of is_exp should match that in Simplify.prepareRhs - one_shots = argsOneShots (idStrictness fun) n_val_args - -- See Note [Sources of one-shot information] + one_shots = argsOneShots (idStrictness fun) guaranteed_val_args + guaranteed_val_args = n_val_args + length (takeWhile isOneShotInfo + (occ_one_shots env)) + -- See Note [Sources of one-shot information], bullet point A'] }}} Notice that `guaranteed_val_args` should be used only for the call to `argOneShots`, not in the calls to `isExpandableApp` or `mkOneOcc`. I thoght this was just cleanup. For example, `is_exp` only matters if `isRhsEnv` is true; and in that case I think `occ_one_shots` is empty (see `rhsCtxt`); so I doubt the change to `is_exp` makes any difference at all. Nevertheless it does: we observed a 7% reduction in allocation for `haddock.base` and `haddock.Cabal` after this one patch. Bonkers! I have no idea why. But I'm just recording it here. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13227#comment:21 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13227: Loss of full laziness in mapFB -------------------------------------+------------------------------------- Reporter: simonpj | Owner: nomeata Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3067 Wiki Page: | -------------------------------------+------------------------------------- Comment (by rwbarton): I can't quite tell from the discussion whether you are already aware of this, but just in case: The gains in Haddock performance from "Comments and tiny refactor only" (https://perf.haskell.org/ghc/#revision/fc9d152b058f21ab03986ea722d0c94688b99...) seem to be undoing the losses of "Improve the Occurrence Analyzer’s handling of one-shot functions" (https://perf.haskell.org/ghc/#revision/a1980ecb5626ec85fc14fbd217e2d16c7d50a...). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13227#comment:22 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13227: Loss of full laziness in mapFB -------------------------------------+------------------------------------- Reporter: simonpj | Owner: nomeata Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3067 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): OK that's good! I still don't know ''why'' the effect is so large; but there was a definite bug, now fixed by the "tiny refactor". Which was not as tiny as I thought. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13227#comment:23 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC