
On 25/06/2014 15:28, Ömer Sinan Ağacan wrote:
I'm running this program:
{-# LANGUAGE DeriveDataTypeable, ScopedTypeVariables #-} import GHC.Stack import Control.Exception.Base import Data.Typeable
data MyException = MyException deriving (Show, Typeable)
instance Exception MyException
err1 :: IO Integer err1 = {-# SCC error1 #-} err2 >>= return
err2 :: IO Integer err2 = {-# SCC error2 #-} throw MyException
main = print =<< whoCreated =<< catch err1 =<< (\(_ :: MyException) -> return (42 :: Integer))
I'd expect `whoCreated` to return something like [Main.CAF, Main.main, Main.main.\] but instead this is the output:
["Main.CAF (<entire-module>)","Main.err2 (ioerr.hs:14:1-43)","Main.error2 (ioerr.hs:14:27-43)","Main.main (ioerr.hs:16:1-103)","Main.main.\\ (ioerr.hs:16:81-102)"]
This output has two things that look somewhat weird to me. First, I'd expect cost-centre stack to be restored when exception is catched and then program would produce shorter stack trace like I mentioned above.(without err1 or err2 calls)
Second, when no cost-centre restoring is done, I'd expect stack trace to include `Main.err1` and `Main.error1`.
So can anyone explain my why stack trace contains err2 calls but not err1 calls? I think none of error1 and error2 should have been included in the stack trace or both of them should have been included.
I have no idea, but I just want to point out that whoCreated is inherently fragile. If its argument is a thunk (as it might well be) then you'll see the CCS of the thunk, and not the CCS of the value. Optimisation flags can easily change the output you get here. To get more predictable output you could try forcing the value before passing it to whoCreated. Cheers, Simon