[GHC] #15226: GHC doesn't know that seq# produces something in WHNF

#15226: GHC doesn't know that seq# produces something in WHNF -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.4.3 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Runtime Unknown/Multiple | performance bug Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- {{{#!hs data Str a = Str !a bar :: Maybe a -> IO (Str (Maybe a)) bar x = do x' <- evaluate x pure (Str x') }}} This compiles to {{{#!hs Test.bar1 = \ (@ a_a3Ld) (x_a3Ah :: Maybe a_a3Ld) (s_i3Nz :: GHC.Prim.State# GHC.Prim.RealWorld) -> case GHC.Prim.seq# @ (Maybe a_a3Ld) @ GHC.Prim.RealWorld x_a3Ah s_i3Nz of { (# ipv_i3NC, ipv1_i3ND #) -> (# ipv_i3NC, Test.$WStr @ (Maybe a_a3Ld) ipv1_i3ND #) } }}} We suspend the application of `$WStr` to `ipv1_i3ND`, when all we actually need to do is apply `Str` directly. We could work around this in `base` by defining {{{#!hs evaluate x = IO $ \s -> case seq# x s of (# s', !x' #) -> (# s', x' #) }}} but that seems more than a little bit silly. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15226 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15226: GHC doesn't know that seq# produces something in WHNF -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.4.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by dfeuer): On the other hand, if there's no way to express that in the demand signature, then I guess changing `base` would be a reasonable alternative.... -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15226#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15226: GHC doesn't know that seq# produces something in WHNF -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.4.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4789 Wiki Page: | -------------------------------------+------------------------------------- Changes (by dfeuer): * status: new => patch * differential: => Phab:D4789 Comment: I've submitted a differential to change `evaluate` to work around the problem, but I don't like it very much. I'd love to have a primitive type of kind `Type -> TYPE UnliftedRep` that only holds things in WHNF; then we could make the primop return something of that type. But we don't have such a beast right now. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15226#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15226: GHC doesn't know that seq# produces something in WHNF -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.4.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4789 Wiki Page: | -------------------------------------+------------------------------------- Comment (by dfeuer): I think the right way for now is probably to stick this in `simplAlt`. When the scrutinee is `seq# x s`, we want to behave the way we would for a strict datacon field. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15226#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15226: GHC doesn't know that seq# produces something in WHNF -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.4.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4796 Wiki Page: | -------------------------------------+------------------------------------- Changes (by dfeuer): * differential: Phab:D4789 => Phab:D4796 Comment: Here's a differential to fix the problem properly. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15226#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15226: GHC doesn't know that seq# produces something in WHNF
-------------------------------------+-------------------------------------
Reporter: dfeuer | Owner: (none)
Type: bug | Status: patch
Priority: normal | Milestone: 8.6.1
Component: Compiler | Version: 8.4.3
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: Runtime | Unknown/Multiple
performance bug | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s): Phab:D4796
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by David Feuer

#15226: GHC doesn't know that seq# produces something in WHNF -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: (none) Type: bug | Status: merge Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.4.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4796 Wiki Page: | -------------------------------------+------------------------------------- Changes (by dfeuer): * status: patch => merge Comment: I think this is likely simple enough to merge. We still don't mark the ''argument'' to `seq#` as evaluated in the case branch: {{{#!hs do _ <- evaluate x pure (Str x) }}} will still think it has to force `x` again. I suspect there are likely users doing such things. I think the fix should be really simple, but I don't know how to do it. We should (I believe) rewrite {{{#!hs case seq# x s of (# s', x' #) -> E }}} to {{{#!hs case seq# x s of (# s', x' #) -> E [x -> x'] }}} In principle, we could do something like that for `spark#` as well, but it's probably better to let threads fizzle than to let users rely on the optimizer to make their parallel code do what they expect. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15226#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15226: GHC doesn't know that seq# produces something in WHNF -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: (none) Type: bug | Status: merge Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.4.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4796 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj):
We should (I believe) rewrite
Yes -- this is a variant of the case binder-swap in `OccurAnal`. See `Note [Binder swap]` in `OccurAnal`. This is the place to do it. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15226#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15226: GHC doesn't know that seq# produces something in WHNF -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: (none) Type: bug | Status: merge Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.4.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4796 Wiki Page: | -------------------------------------+------------------------------------- Comment (by dfeuer): Replying to [comment:7 simonpj]:
We should (I believe) rewrite
Yes -- this is a variant of the case binder-swap in `OccurAnal`. See `Note [Binder swap]` in `OccurAnal`. This is the place to do it.
I eventually found that, but I'm not at all sure how to deal with coercions in that context. We could, for example, have something like {{{#!hs case seq# x a `cast` ... of (# s', x' #) -> ... }}} in which case we have to work out how to rejigger all the coercions. I don't know enough about that machinery yet. In the current `OccurAnal` code, the coercion in the scrutinee is always on a variable, but here it's on a pair containing the variable, so I'm not going to be able to code monkey it. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15226#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15226: GHC doesn't know that seq# produces something in WHNF -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: (none) Type: bug | Status: merge Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.4.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4796 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Good point. A cast would complicate. I suppose that in {{{ case seq# x s |> g of (# s', x' #) -> ... }}} we'd have to have {{{ g :: (# State# t1, t2 #) ~ (# s1, s2 #) }}} where `x :: t2` and `x' :: s2`. So you'd want to transform to {{{ case seq# x s |> g of (# s', x' #) -> let x = x' |> sym (Nth 2 g) }}} because `Nth 2 g :: t2 ~ s2`. (I might not have this exactly right.) This all seems a bit ad-hoc for `seq#` but I don't really see an alternative, sadly. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15226#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15226: GHC doesn't know that seq# produces something in WHNF -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: (none) Type: bug | Status: merge Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.4.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4796 Wiki Page: | -------------------------------------+------------------------------------- Comment (by dfeuer): The key `OccAnal` functions involved seem to be `mkAltEnv` (not sure what this does, but it seems to look for `Var`s when I want to look also for applications of `seq#`) and `wrapAltRHS` (which seems to actually install the `Let` when appropriate), but I don't see how it all fits together. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15226#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15226: GHC doesn't know that seq# produces something in WHNF -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: (none) Type: bug | Status: merge Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.4.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4796 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): If you want to pursue, this I can advise. Whether it's worth the trouble I'm less sure. Do you have an example where it's causing trouble? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15226#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15226: GHC doesn't know that seq# produces something in WHNF -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: (none) Type: bug | Status: merge Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.4.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4796 Wiki Page: | -------------------------------------+------------------------------------- Comment (by dfeuer): I'm also not sure it's worth the trouble, although the current state of affairs seems a bit tricky to document in the Haddocks for `evaluate`. But considering `Control. Parallel.Strategies.rdeepseq`, I realized that even this binder swap, in combination with what I've already done, isn't really quite enough. Suppose we have {{{#!hs let e = x + 3 :: Int in case seq# e s of (# s', e' #) -> E }}} We'd actually like to know that not only `e` and `e'`, but also `x`, are evaluated in `E`, because `e` is strict in `x`. So if we do a binder swap, we should do it for all the variables the scrutinee is strict in that are not already known to be evaluated. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15226#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15226: GHC doesn't know that seq# produces something in WHNF -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: (none) Type: bug | Status: merge Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.4.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4796 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonmar): Is there anything to document? It doesn't affect the semantics of `evaluate`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15226#comment:13 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15226: GHC doesn't know that seq# produces something in WHNF -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: (none) Type: bug | Status: merge Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.4.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4796 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj):
So if we do a binder swap, we should do it for all the variables the scrutinee is strict
This is a bridge too far! Strictness analysis will work this out, I think. Eg that `let e` will turn into a case. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15226#comment:14 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

So if we do a binder swap, we should do it for all the variables the scrutinee is strict
This is a bridge too far! Strictness analysis will work this out, I
#15226: GHC doesn't know that seq# produces something in WHNF -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: (none) Type: bug | Status: merge Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.4.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4796 Wiki Page: | -------------------------------------+------------------------------------- Comment (by dfeuer): Replying to [comment:14 simonpj]: think. Eg that `let e` will turn into a case. I don't think so. `seq#` is intentionally lazy in its argument, to allow explicit ordering in an `IO` context. This seems pretty important in combination with `spark#`, for example. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15226#comment:15 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15226: GHC doesn't know that seq# produces something in WHNF -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: (none) Type: bug | Status: merge Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.4.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4796 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj):
seq# is intentionally lazy in its argument, to allow explicit ordering in an IO context
Hmnm. Can you give an example? Nothing in `seq#`'s documentation says that. It jolly well should! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15226#comment:16 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15226: GHC doesn't know that seq# produces something in WHNF
-------------------------------------+-------------------------------------
Reporter: dfeuer | Owner: (none)
Type: bug | Status: merge
Priority: normal | Milestone: 8.6.1
Component: Compiler | Version: 8.4.3
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: Runtime | Test Case:
performance bug | perf/should_run/T15226, 15226a
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s): Phab:D4796
Wiki Page: |
-------------------------------------+-------------------------------------
Changes (by simonpj):
* testcase: => perf/should_run/T15226, 15226a
Comment:
I believe this is a follow-up patch
{{{
commit 502026fc0a35460c7f04b26a11320723a7bbfdff
Author: David Feuer
---------------------------------------------------------------
502026fc0a35460c7f04b26a11320723a7bbfdff compiler/coreSyn/CoreSyn.hs | 3 ++- testsuite/tests/perf/should_run/{T15226.hs => T15226a.hs} | 5 ++++- testsuite/tests/perf/should_run/all.T | 9 +++++++++ 3 files changed, 15 insertions(+), 2 deletions(-) diff --git a/compiler/coreSyn/CoreSyn.hs b/compiler/coreSyn/CoreSyn.hs index 4dd70b0..50e40d1 100644 --- a/compiler/coreSyn/CoreSyn.hs +++ b/compiler/coreSyn/CoreSyn.hs @@ -2046,10 +2046,11 @@ collectArgs expr go e as = (e, as) -- | Attempt to remove the last N arguments of a function call. --- Strip off any ticks encountered along the way and any ticks +-- Strip off any ticks or coercions encountered along the way and any -- at the end. stripNArgs :: Word -> Expr a -> Maybe (Expr a) stripNArgs !n (Tick _ e) = stripNArgs n e +stripNArgs n (Cast f _) = stripNArgs n f stripNArgs 0 e = Just e stripNArgs n (App f _) = stripNArgs (n - 1) f stripNArgs _ _ = Nothing diff --git a/testsuite/tests/perf/should_run/T15226.hs b/testsuite/tests/perf/should_run/T15226a.hs similarity index 89% copy from testsuite/tests/perf/should_run/T15226.hs copy to testsuite/tests/perf/should_run/T15226a.hs index 4c09114..6e9a1db 100644 --- a/testsuite/tests/perf/should_run/T15226.hs +++ b/testsuite/tests/perf/should_run/T15226a.hs @@ -3,6 +3,7 @@ import Control.Exception (evaluate) -- Just in case Prelude.repeat changes for some reason. import Prelude hiding (repeat) +import Data.Coerce -- We want to be sure that the compiler *doesn't* know that -- all the elements of the list are in WHNF, because if it @@ -12,11 +13,13 @@ repeat a = res where res = a : res {-# NOINLINE repeat #-} -- Belt *and* suspenders +newtype Foo = Foo Int + silly :: [Int] -> IO () silly = foldr go (pure ()) where go x r = do - x' <- evaluate x + x' <- (coerce (evaluate :: Foo -> IO Foo) :: Int -> IO Int) x evaluate (x' + 3) -- GHC should know that x' has been evaluated, -- so this calculation will be erased entirely. -- Otherwise, we'll create a thunk to pass to diff --git a/testsuite/tests/perf/should_run/all.T b/testsuite/tests/perf/should_run/all.T index b248dd5..0e7996ef 100644 --- a/testsuite/tests/perf/should_run/all.T +++ b/testsuite/tests/perf/should_run/all.T @@ -584,3 +584,12 @@ test('T15226', only_ways(['normal'])], compile_and_run, ['-O']) + +test('T15226a', + [stats_num_field('bytes allocated', + [ (wordsize(64), 41040, 5) ]), + # 2018-06-06 41040 Look through casts for seq# + # initial 400041040 + only_ways(['normal'])], + compile_and_run, + ['-O']) }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15226#comment:17 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15226: GHC doesn't know that seq# produces something in WHNF -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.4.3 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Runtime | Test Case: performance bug | perf/should_run/T15226, 15226a Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4796 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed Comment: This is in 8.6. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15226#comment:18 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

seq# is intentionally lazy in its argument, to allow explicit ordering in an IO context
Hmnm. Can you give an example? Nothing in `seq#`'s documentation says
#15226: GHC doesn't know that seq# produces something in WHNF -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.4.3 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Runtime | Test Case: performance bug | perf/should_run/T15226, 15226a Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4796 Wiki Page: | -------------------------------------+------------------------------------- Comment (by dfeuer): Replying to [comment:16 simonpj]: that. It jolly well should! Considering `seq#` strict can be rather bad, I believe. If we turn `.... seq# x s` into `case x of x' {DEFAULT__ -> .... seq# x' s}` then we'll see that `x'` is evaluated and erase the `seq#`. That sort of thing is the very sort of trouble `seq#` was intended to avoid. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15226#comment:19 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15226: GHC doesn't know that seq# produces something in WHNF -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.4.3 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Runtime | Test Case: performance bug | perf/should_run/T15226, 15226a Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4796 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj):
Considering seq# strict can be rather bad, I believe.
I'm not sure about that. First, let's remember (I always forget this) that `seq#` has type {{{ seq# ::a -> State# s -> (# State# s, a #) }}} That is, it involves the IO monad. It's used to implement {{{ evaluate :: a -> IO a evaluate a = IO $ \s -> seq# a s -- NB. see #2273, #5129 }}} See Trac #5129. Now consider {{{ \s. let x = blah in let y = x+1 in case seq# x s of (# s', x' #) -> ... }}} It seems fine to me transform this to {{{ \x. case blah of x -> let y = x+1 in case seq# x s of (# s', x' #) -> ... }}} What if the `seq#` is after some other IO operations thus: {{{ \s. let x = blah in case f s of (# s1, r #) -> case seq# x s of (# s2, x' #) -> ...... }}} Now you might worry that `x` might be evaluated (and throw an exception) before `f` gets a chance to run. But it doesn't: there's a hack in the strictness analyser (see `See Note [IO hack in the demand analyser]` in `DmdAnal`) that will make `x`'s binding lazy; in effect the strictness analyser treats the `case f s of ...` as if it had an extra invisible alternative not mentioning `x`. It's not that important. But I think that `seq#` can safely be strict in `x`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15226#comment:20 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15226: GHC doesn't know that seq# produces something in WHNF -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.4.3 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Runtime | Test Case: performance bug | perf/should_run/T15226, 15226a Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4796 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): I'm going to re-open this because there are two loose ends: * Should `seq#` be strict? See comment:10 * Is it worth doing the "binder-swap" thing? See comment:6 and following. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15226#comment:21 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15226: GHC doesn't know that seq# produces something in WHNF -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.4.3 Resolution: fixed | Keywords: Exceptions Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Runtime | Test Case: performance bug | perf/should_run/T15226, 15226a Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4796 Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * keywords: => Exceptions -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15226#comment:22 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15226: GHC doesn't know that seq# produces something in WHNF -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.4.3 Resolution: fixed | Keywords: Exceptions, | DemandAnalysis Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Runtime | Test Case: performance bug | perf/should_run/T15226, 15226a Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4796 Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * keywords: Exceptions => Exceptions, DemandAnalysis -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15226#comment:23 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC