[GHC] #13645: whoCreated produces an uninformative stack trace when an exception is raised in a CAF
GHC
ghc-devs at haskell.org
Thu May 4 12:18:09 UTC 2017
#13645: whoCreated produces an uninformative stack trace when an exception is
raised in a CAF
-------------------------------------+-------------------------------------
Reporter: refold | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.0.1
Keywords: | Operating System: Unknown/Multiple
Architecture: | Type of failure: None/Unknown
Unknown/Multiple |
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
Consider the following program:
{{{#!hs
{-# LANGUAGE ScopedTypeVariables #-}
module Main where
import Control.Exception
import GHC.Stack
{-# NOINLINE caf #-}
caf :: [Int]
caf = [1..500]
{-# NOINLINE caf_exc #-}
caf_exc :: Int
caf_exc = caf !! 1000
{-# NOINLINE foo #-}
foo :: Int -> Int
foo 0 = caf_exc
foo n = foo $ n - 1
{-# NOINLINE bar #-}
bar :: Int -> Int
bar n = bar' n
where
bar' 0 = foo n
bar' m = bar' $ m - 1
main :: IO ()
main = print (bar 10) `catch`
\(e :: SomeException) -> do stacktrace <- whoCreated e
print stacktrace
}}}
By default, when built with profiling, `whoCreated` in the example above
produces a quite uninformative stack trace:
{{{#!shell
$ ./caf-nostack
["GHC.List.CAF (<entire-module>)"]
}}}
However, if you run the program with `+RTS -xc`, you'll see that it prints
a stack trace with much more context:
{{{#!shell
$ ./caf-nostack +RTS -xc
*** Exception (reporting due to +RTS -xc): (THUNK_2_0), stack trace:
GHC.List.CAF
--> evaluated by: Main.caf_exc,
called from Main.CAF
--> evaluated by: Main.foo,
called from Main.bar.bar',
called from Main.bar,
called from Main.main,
called from Main.CAF
--> evaluated by: Main.main
["GHC.List.CAF (<entire-module>)"]
}}}
It'd be nice if `whoCreated` produced something closer to the `+RTS -xc`
output in this case.
Cabalised test project: https://github.com/23Skidoo/caf-nostack
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/13645>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list