[Git][ghc/ghc][wip/T13380] Fix #13380 and #17676

Sebastian Graf gitlab at gitlab.haskell.org
Wed Mar 25 13:28:35 UTC 2020



Sebastian Graf pushed to branch wip/T13380 at Glasgow Haskell Compiler / GHC


Commits:
c07e8396 by Sebastian Graf at 2020-03-25T13:57:15+01:00
Fix #13380 and #17676

By

1. Changing `raiseIO#` to have topDiv
2. Give it special treatment in `Simplifier.Util.mkArgInfo`, treating it
   as if it had `botDiv`, to recover dead code elimination.

This is the first commit of the plan outlined in
https://gitlab.haskell.org/ghc/ghc/-/merge_requests/2525#note_260886.

- - - - -


5 changed files:

- compiler/GHC/Core/Op/Simplify/Utils.hs
- compiler/basicTypes/Demand.hs
- compiler/prelude/primops.txt.pp
- + testsuite/tests/stranal/should_run/T17676.hs
- testsuite/tests/stranal/should_run/all.T


Changes:

=====================================
compiler/GHC/Core/Op/Simplify/Utils.hs
=====================================
@@ -55,6 +55,7 @@ import Name
 import Id
 import IdInfo
 import Var
+import PrimOp
 import Demand
 import GHC.Core.Op.Simplify.Monad
 import GHC.Core.Type     hiding( substTy )
@@ -500,7 +501,9 @@ mkArgInfo env fun rules n_val_args call_cont
                         -- calls to error.  But now we are more careful about
                         -- inlining lone variables, so it's ok
                         -- (see GHC.Core.Op.Simplify.Utils.analyseCont)
-                   if isBotDiv result_info then
+                        -- See Note [Precise exceptions and strictness analysis] in Demand.hs
+                        -- for the special case on raiseIO#
+                   if isBotDiv result_info || isPrimOpId_maybe fun == Just RaiseIOOp then
                         map isStrictDmd demands         -- Finite => result is bottom
                    else
                         map isStrictDmd demands ++ vanilla_stricts


=====================================
compiler/basicTypes/Demand.hs
=====================================
@@ -932,6 +932,28 @@ instance Outputable Divergence where
   ppr Diverges      = char 'b'
   ppr Dunno         = empty
 
+{- Note [Precise exceptions and strictness analysis]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+raiseIO# needs to be a primop (rather than defining it in terms of raise#),
+because exceptions raised by it are considered  *precise* - we don't want the
+strictness analyser turning one kind of bottom into another, as it is allowed
+to do in pure code.
+
+This means that raiseIO# is lazy in its free variables, see the following
+example from #13380 (similarly #17676):
+    f x y | x>0       = raiseIO Exc
+          | y>0       = return 1
+          | otherwise = return 2
+ at f@ strict in @y@? One might be tempted to say yes! But that plays fast and
+loose with the precise exception; after optimisation, @f 42 (error "boom")@
+turns from throwing the precise @Exc@ to throwing the imprecise user error
+"boom". So, the @defaultDmd@ of @raiseIO#@ should be lazy (@topDmd@), which can
+be achieved by giving it @topDiv at .
+But then the simplifier fails to drop a lot of dead code, hence we have special
+treatment for raiseIO# in @Simplifier.Utils.mkArgInfo at .
+-}
+
+
 ------------------------------------------------------------------------
 -- Combined demand result                                             --
 ------------------------------------------------------------------------


=====================================
compiler/prelude/primops.txt.pp
=====================================
@@ -2644,27 +2644,12 @@ primop  RaiseOverflowOp "raiseOverflow#" GenPrimOp
    out_of_line = True
    has_side_effects = True
 
--- raiseIO# needs to be a primop, because exceptions in the IO monad
--- must be *precise* - we don't want the strictness analyser turning
--- one kind of bottom into another, as it is allowed to do in pure code.
---
--- But we *do* want to know that it returns bottom after
--- being applied to two arguments, so that this function is strict in y
---     f x y | x>0       = raiseIO blah
---           | y>0       = return 1
---           | otherwise = return 2
---
--- TODO Check that the above notes on @f@ are valid. The function successfully
--- produces an IO exception when compiled without optimization. If we analyze
--- it as strict in @y@, won't we change that behavior under optimization?
--- I thought the rule was that it was okay to replace one valid imprecise
--- exception with another, but not to replace a precise exception with
--- an imprecise one (dfeuer, 2017-03-05).
-
 primop  RaiseIOOp "raiseIO#" GenPrimOp
    a -> State# RealWorld -> (# State# RealWorld, b #)
    with
-   strictness  = { \ _arity -> mkClosedStrictSig [topDmd, topDmd] botDiv }
+   -- See Note [Precise exceptions and strictness analysis] in Demand.hs
+   -- for why we give it topDiv
+   -- strictness  = { \ _arity -> mkClosedStrictSig [topDmd, topDmd] topDiv }
    out_of_line = True
    has_side_effects = True
 


=====================================
testsuite/tests/stranal/should_run/T17676.hs
=====================================
@@ -0,0 +1,18 @@
+{-# LANGUAGE ScopedTypeVariables #-}
+import Data.IORef
+import Control.Exception
+import Control.Monad
+
+data Exc = Exc deriving Show
+
+instance Exception Exc
+
+-- Recursive instead of NOINLINE because of #17673
+f :: Int -> Int -> IO ()
+f 0 x = do
+  let true = sum [0..4] == 10
+  when true $ throwIO Exc
+  x `seq` return ()
+f n x = f (n-1) (x+1)
+
+main = f 1 (error "expensive computation") `catch` \(_ :: Exc) -> return ()


=====================================
testsuite/tests/stranal/should_run/all.T
=====================================
@@ -19,7 +19,8 @@ test('T11076', normal, multimod_compile_and_run, ['T11076.hs', 'T11076_prim.cmm'
 test('T11555a', normal, compile_and_run, [''])
 test('T12368', exit_code(1), compile_and_run, [''])
 test('T12368a', exit_code(1), compile_and_run, [''])
-test('T13380', [expect_broken(13380), exit_code(1)], compile_and_run, [''])
+test('T13380', exit_code(1), compile_and_run, [''])
 test('T14171', [expect_broken(14171), exit_code(1)], compile_and_run, [''])
 test('T14290', normal, compile_and_run, [''])
 test('T14285', normal, multimod_compile_and_run, ['T14285', ''])
+test('T17676', normal, compile_and_run, [''])



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/c07e839635b873aeff80d8207c902f196b86ec8c

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/c07e839635b873aeff80d8207c902f196b86ec8c
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20200325/88a16a16/attachment-0001.html>


More information about the ghc-commits mailing list