The following program, extracted from the test exceptionsrun001, should exit with exitcode 100. Instead, when compiled with -O1, it never gets past the ioTest and somehow manages to exit with exitcode 0.
{-# LANGUAGE ScopedTypeVariables #-}moduleMainwhereimportControl.ExceptionimportSystem.IO.ErrorimportSystem.Exitmain=doioTestexitWith(ExitFailure100)ioTest::IO()ioTest=(catch(ioError(userError"wibble"))(\(e::IOException)->return())
I think it's reasonable that this should allow the exception to be raised somewhere else (imprecisely):
catch# (\s -> (raise# blah) `seq` blah2) (...) st
because raise# is in the pure world. But raiseIO# is specifically intended to raise an exception precisely at the specified moment, so the new behaviour is unacceptable.
Now I think about this more I'm also worried about
let r = \st -> raiseIO# blah st in catch (\st -> ...(r st)..) handler st
Now that I'm given catch a more aggressive strictness, I'll get a demand C(S) for r; that is, it is definitly called with one argument. And so it is! But the danger is that we'll feed C(S) into r's rhs as the demand of the body, and say that that whole let will definitely diverge (which isn't true).
However, we really want this function to be strict in x:
f x st = catch (\s -> case x of I# x' -> ...) handler st
Getting this strictness was the whole point of the offending commit:
There's something very special about catch: it turns divergence into non-divergence. (The strictness analyser treats divergence and exceptions identically.)
thomie correctly pointed out that this patch did not actually fix the four failing testcases marked in 3b233793. Looks like I'll need to dive a bit deeper.