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

GHC ghc-devs at haskell.org
Thu Jun 28 09:44:52 UTC 2018


#7411: Exceptions are optimized away in certain situations
-------------------------------------+-------------------------------------
        Reporter:  SimonHengel       |                Owner:  tdammers
            Type:  bug               |               Status:  new
        Priority:  high              |            Milestone:  8.8.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 #15225      |  Differential Rev(s):
       Wiki Page:                    |
-------------------------------------+-------------------------------------

Comment (by tdammers):

 Replying to [comment:44 simonpj]:

 > * As I wrote above, the motivation for the state hack is functions lie
 > {{{
 > f :: [Int] -> IO ()
 > f xs = print ys >> print xs
 >   where
 >     ys = reverse xs
 >
 > test 0 = return ()
 > test n = f [1,n] >> test (n-1)
 > }}}
 >   which I expected to be much less efficient without the state hack.
 Would it be worth trying to demonstrate a program that does get worse in
 this way?  I'm still amazed at how good the results are!

 OK, I did some experimenting, and it seems that the state hack makes
 absolutely no difference for such programs. Specifically, I used the
 following fully-fledged example program:

 {{{#!hs
 module Main where

 import System.Environment
 import System.IO

 f :: Handle -> [Int] -> IO ()
 f h xs = hPrint h ys >> hPrint h xs
   where
       ys = reverse xs

 test :: Int -> Handle -> IO ()
 test 0 h = return ()
 test n h = f h [1,n] >> test (n-1) h

 main = do
   args <- getArgs
   case args of
     x:y:_ -> withFile y WriteMode $ test (read x)
     x:_ -> test (read x) stdout
     _ -> test 0 stdout
 }}}

 This allows us to pass an arbitrary number of rounds to test on the
 command line, as well as an output file; passing `/dev/null` makes it
 easier to run the whole thing through `time`. Now given two GHC builds in
 `ghc-prof` (normal profiling build) and `ghc-prof-nsh` (GHC and boot libs
 built with `-fno-state-hack`), and with our example program in `bad-
 ex.hs`, I can run the following session:

 {{{
 tobias at zoidberg:~/well-typed/devel/ghc-7411/ > ./ghc-prof/inplace/bin/ghc-
 stage2 bad-ex.hs -fforce-recomp -O2 && time ./bad-ex 50000000 /dev/null
 [1 of 1] Compiling Main             ( bad-ex.hs, bad-ex.o )
 Linking bad-ex ...
 ./bad-ex 50000000 /dev/null  53.50s user 0.20s system 99% cpu 53.713 total
 tobias at zoidberg:~/well-typed/devel/ghc-7411/ > ./ghc-prof-nsh/inplace/bin
 /ghc-stage2 bad-ex.hs -fforce-recomp -fno-state-hack -O2 && time ./bad-ex
 50000000 /dev/null
 [1 of 1] Compiling Main             ( bad-ex.hs, bad-ex.o )
 Linking bad-ex ...
 ./bad-ex 50000000 /dev/null  52.75s user 0.19s system 99% cpu 52.956 total
 }}}

 Which suggests that even for a program that is presumably about as bad as
 it gets, the state hack doesn't make a difference for the better.

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


More information about the ghc-tickets mailing list