[GHC] #7411: Exceptions are optimized away in certain situations

GHC ghc-devs at haskell.org
Tue May 8 21:35:14 UTC 2018


#7411: Exceptions are optimized away in certain situations
-------------------------------------+-------------------------------------
        Reporter:  SimonHengel       |                Owner:  tdammers
            Type:  bug               |               Status:  new
        Priority:  high              |            Milestone:  8.6.1
       Component:  Compiler          |              Version:  7.6.1
      Resolution:                    |             Keywords:  seq, deepseq,
                                     |  evaluate, exceptions
Operating System:  Linux             |         Architecture:  x86_64
                                     |  (amd64)
 Type of failure:  Incorrect result  |            Test Case:
  at runtime                         |  simplCore/should_fail/T7411
      Blocked By:                    |             Blocking:
 Related Tickets:  #5129             |  Differential Rev(s):
       Wiki Page:                    |
-------------------------------------+-------------------------------------

Comment (by simonpj):

 Here's what is going on:

 * After a late float-out pass we get this
 {{{
 lvl_s2Yn [Occ=Once]   -- Comes from 'return ()'
   :: GHC.Prim.State# GHC.Prim.RealWorld -> (# GHC.Prim.State#
 GHC.Prim.RealWorld, () #)
 [LclId]
 lvl_s2Yn
   = \ (s_a2z6 [Occ=Once, Dmd=<S,U>]
          :: GHC.Prim.State# GHC.Prim.RealWorld) ->
       (# s_a2z6, GHC.Tuple.() #)

 lvl_s2Yo [Occ=Once] :: GHC.Types.IO ()
 [LclId]  -- Comes from (('a':undefined) `dslist` return ())
 lvl_s2Yo
   = case go_s2WQ lvl_s2Ym of { __DEFAULT ->
     lvl_s2Yn
     `cast` (Sym (GHC.Types.N:IO[0] <()>_R)
             :: (GHC.Prim.State# GHC.Prim.RealWorld
                 -> (# GHC.Prim.State# GHC.Prim.RealWorld, () #) :: *)
                ~R# (GHC.Types.IO () :: *))
     }

 main_s2z7
   = \ (s_a2yI [Occ=Once, Dmd=<S,U>]
          :: GHC.Prim.State# GHC.Prim.RealWorld) ->
       GHC.Prim.seq#
         @ (GHC.Types.IO ()) @ GHC.Prim.RealWorld lvl_s2Yo s_a2yI
 }}}

   So far so good.

 * But then we see that `lvl_s2Yn` has arity 1 (which it does).  And then
 we eta-expand `lvl_s2Yo`, moving the lambda outside the `case go
 lvl_s2Ym`, to get
 {{{
 lvl_s2Yo
   = (\ (eta_B1 [Occ=Once] :: GHC.Prim.State# GHC.Prim.RealWorld) ->
        case go_s2WQ lvl_s2Ym of { () ->
        (lvl_s2Yn `cast` ...) eta_B1
        })
     `cast` ...
 }}}

 * Aargh!  Now `lvl_s2Yo` is a HNF, not bottom as it should be.  And so
 `seq# lvl_s2Y# x` is (correctly) reduced to `x`.

 How to avoid this?  It's the notorious "state hack" that "justifies"
 floating the lambda out. The motivation is functions like this:
 {{{
 f :: [Int] -> IO ()
 f xs = print ys >> print xs
   where
     ys = reverse xs
 }}}
 Without the state hack we get an arity-1 function thus
 {{{
 f = \xs. let ys = reverse xs in
          \s. case print ys s of
                (# s' ,_ #) -> print xs s'
 }}}
 That's signficantly less efficient than an arity-2 function; but that
 penalty may be worth paying if the application `(f xs)` is shared.  For
 example:
 {{{
   let fxs = f [1..100]
   in fxs >> fxs >> fxs
 }}}
 In the arity-1 case we'd reverse `[1..100]` once; in the arity-2 case we'd
 reverse it three times.  In practice this doesn't seem to come up much.

 ------------
 I'm not sure it's worth fixing this.  It doesn't seem to be harming
 anyone, an  it's not clear how to fix it.

 The only fix I can think of (apart from abandoning the state hack) would
 be to restrict the state hack a bit more so that it doesn't apply to an
 arity-zero binding like `lvl_s2Yo` -- but still does apply to `f` above.
 But if we did that, then this minor variant of #7411 would still
 misbehave:
 {{{
 {-# NOINLINE f #-}
 f2 :: Int -> IO ()
 f2 x = ('a':undefined) `dslist` return ()

 main = evaluate (f2 3)
 }}}
 Here I've just given `f` an argument; like `f`above it'll be eta-expanded.
 Morally, it's the same problem as before, but perhaps it just occurs less
 often.

 I'm inclined to focus on other tickets that are causing users actual pain.

 But it's a long time since I tried measuring the perf cost of simply
 switching the state hack off altogether.  Would anyone like to to just try
 that?

-- 
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/7411#comment:26>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list