[GHC] #12096: Attach stacktrace information to SomeException

#12096: Attach stacktrace information to SomeException -------------------------------------+------------------------------------- Reporter: ndtimofeev | Owner: Type: feature | Status: new request | Priority: normal | Milestone: Component: | Version: 8.0.1 libraries/base | 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: -------------------------------------+------------------------------------- Now (base 4.9.0.0) ErrorCall contain field for stacktrace information and error fills it. If you add field for stacktrace information to SomeException {{{#!hs data SomeException where SomeExceptionWithLocation :: Exception e => String -> e -> SomeException pattern SomeException :: () => Exception e => e -> SomeException pattern SomeException err <- SomeExceptionWithLocation _ err where SomeException err = SomeExceptionWithLocation "" err }}} and will fills it in throw {{{#!hs throw :: (HasCallStack, Exception e) => e -> a throw e = unsafeDupablePerformIO $ do stack <- currentCallStack raise# (CallStackException e $ if stack /= [] then prettyCallStack ?callStack ++ "\n" ++ renderStack stack else prettyCallStack ?callStack) }}} it will be more useful for ghci users. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12096 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12096: Attach stacktrace information to SomeException -------------------------------------+------------------------------------- Reporter: ndtimofeev | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Core Libraries | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * cc: gridaphobe, ekmett (added) * component: libraries/base => Core Libraries -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12096#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12096: Attach stacktrace information to SomeException -------------------------------------+------------------------------------- Reporter: ndtimofeev | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Core Libraries | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by gridaphobe): I'm generally in favor of adding `CallStack`s to exceptions (I've often cursed myself for using exceptions and having no clue where they were thrown). I'm not sure this is the best API though. A few thoughts: 1. I would prefer to not serialize the `CallStack`, i.e. get rid of `prettyCallStack`. Clients might want to inspect the `CallStack` when they catch an exception. 2. I wonder if adding the `CallStack` to `SomeException` is the best move. If we do this, we're kinda limited to adding the stack to `SomeException`s `Show` instance. People (AFAIK) don't usually operate directly on `SomeException`, they use `catch` and co. to unwrap the exception, which means giving up the `CallStack`. On the other hand, expecting users to add `CallStack`s to each exception type is not practical, nor is it clear how we'd wire that into `throw`. Perhaps (2) can be solved by keeping the `CallStack` in `SomeException` and adding a few helper functions, e.g. {{{#!haskell catchWithCallStack :: Exception e => IO a -> (e -> CallStack -> IO a) -> IO a }}} Thanks for the suggestion! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12096#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12096: Attach stacktrace information to SomeException -------------------------------------+------------------------------------- Reporter: ndtimofeev | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Core Libraries | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by ndtimofeev): 1. I just copy `ErrorCall` API and implementation. Also I would like to see both stacktrace (`CallStack` and `CostCentreStack`, not only `CallStack`). 2. Yep, stacktrace information is lost when we catch unwraped exception. It looks like a problem. First: {{{#!hs f = throw (CustomException False) g = f `catch` \err@(CustomException fixable) -> if fixable then makeGood else throw err }}} We only rethrow exception and… change it stacktrace. Now it start from `throw` in `g`, not in `f`. Second: {{{#!hs onException eval handler = eval `catch` (\e@(SomeException _) -> handler
throw e)
f = throw (CustomException False) g = f `onException` makeGood }}} Now exception has to stacktrace. Third: {{{#!hs loop = forever $ threadDelay maxBound main = do tid <- forkIO $ loop `onException` putStrLn "Bang!" threadDelay 1000000 throwTo tid UserException }}} Now `UserException` has absolutely irrelevant stacktrace. I don't know how fix first problem. The second can be fixed something like that: {{{#!hs throw :: (HasCallStack, Exception e) => e -> a throw e | Just (SomeException _) <- cast e = raise# e | otherwise = unsafeDupablePerformIO $ do stack <- currentCallStack raise# (CallStackException e $ if stack /= [] then prettyCallStack ?callStack ++ "\n" ++ renderStack stack else prettyCallStack ?callStack) }}} The third is more complicated. For example we can skip stacktrace information for asynchronous exceptions. But in general, we can't determine this exception synchronous or asynchronous. Perhaps `throwTo` can add to exception extra information. But I do not understand how. {{{#!hs throwTo' :: Exception e => ThreadId -> e -> IO a throwTo' tid = throwTo tid . SomeAsyncException catch' :: Exception e => IO a -> (e -> IO a) -> IO a catch' eval handler = eval `catch` \err@(SomeException _) -> go err handler err where go :: (Exception e, Exception a) => e -> (a -> IO b) -> SomeException -> IO b go ex f origErr | Just v <- cast ex = f v | Just (SomeException inner) <- cast ex = go inner f origErr | Just (SomeAsyncException inner) <- cast ex = go inner f origErr | otherwise = throw origErr }}} Also it will be useful in situation like that: {{{#!hs processCmd = timeout 20000 . postDataAndWaitResponce main = do tasks <- newChan :: IO (Chan (String, MVar (Either SomeEception (Maybe String)))) tid <- forkIO $ forever $ do (cmd, ret) <- readChan tasks try (processCmd cmd) >>= putMVar ret threadDelay 1000000 throwTo tid UserException }}} `UserException` can't kill forked thread because it try catch all (synchronous) exception. If `try (processCmd cmd) >>= putMVar ret` will be masked `timeout` will be broken. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12096#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12096: Attach stacktrace information to SomeException -------------------------------------+------------------------------------- Reporter: ndtimofeev | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Core Libraries | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by ndtimofeev): * Attachment "Exception.hs" added. proof of concept -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12096 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12096: Attach stacktrace information to SomeException -------------------------------------+------------------------------------- Reporter: ndtimofeev | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Core Libraries | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by mnislaih): * cc: mnislaih (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12096#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12096: Attach stacktrace information to SomeException -------------------------------------+------------------------------------- Reporter: ndtimofeev | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Core Libraries | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by ezyang): * cc: ezyang (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12096#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12096: Attach stacktrace information to SomeException -------------------------------------+------------------------------------- Reporter: ndtimofeev | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Core Libraries | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by ezyang): I don't think there is any way to attach a stack trace directly to the `SomeException` data type without breaking code that catches and rethrows exceptions of type `e` (with the constraint `Exception e`). So the not- very-nice conclusion is that we in fact *have* to embed the call stack in every exception type. This doesn't mean that `throw` can't also know how to attach call stacks: for example, the `Exception` type class could be extended with methods for getting and putting the call stack (and the exception instance can even make decisions like whether or not to keep all call stacks around, or just keep the first one, etc). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12096#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12096: Attach stacktrace information to SomeException -------------------------------------+------------------------------------- Reporter: ndtimofeev | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Core Libraries | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by mnislaih): I reached the same conclusion, we have to embed call stacks in every exception type. But I don't think this is incompatible with adding them at the SomeException level. We cannot touch SomeException without breaking all the existing Exception instances, so we introduce a new primitive ancestor SomeExceptionWithCallStack in the hierarchy: {{{ SomeExceptionWithCallStack ^ ^ | | | | SomeException IOError }}} {{{ data SomeExceptionWithCallStack = SomeExceptionWithCallStack Exception [CallStack] data IOError = IOError { ... callStack : [CallStack], ...} class ExceptionWithCallStack e where toExceptionWithCallStack :: e -> SomeExceptionWithCallStack fromExceptionWithCallStack :: SomeExceptionWithCallStack -> Maybe e instance ExceptionWithCallStack SomeException ... instance ExceptionWithCallStack IOError ... }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12096#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12096: Attach stacktrace information to SomeException -------------------------------------+------------------------------------- Reporter: ndtimofeev | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Core Libraries | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by ezyang): So, in my head, I want to minimize the amount of changes to code necessary to take advantage of call stacks. Adding CallStacks to each of the exception types individually means that you have to modify each exception type to contain a CallStack (so, linear in the number of exception types.) Creating a new `SomeExceptionWithCallStack` means that we have to modify all occurrences of catch-rethrow to preserve call stacks (so, linear in the number of catch-rethrows in code everywhere.) I admit that there is a tradeoff here, but the benefits of `SomeExceptionWithCallStack` don't make sense to me. I imagine there are a lot more catch-rethrows than there are exception types, and you will have to go through and fix each one of them. Admittedly, if you get a call stack that is missing info you need, it shouldn't be hard to track down (since the error will have the call stack of the bad rethrow attached :) Perhaps I am not seeing some other hidden costs? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12096#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12096: Attach stacktrace information to SomeException -------------------------------------+------------------------------------- Reporter: ndtimofeev | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Core Libraries | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by mnislaih): Sounds like you are comparing the costs of 1) adding CallStacks to individual exception types vs 2) fixing call-rethrow occurrences to use the `...WithCallStack` variants. And concluding that the cost of 2) is higher, therefore `SomeExceptionWithCallStack` is a more expensive solution. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12096#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12096: Attach stacktrace information to SomeException -------------------------------------+------------------------------------- Reporter: ndtimofeev | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Core Libraries | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by mnislaih): But surely if we had `SomeExceptionWithCallStack` then both 1) and 2) are available options, they are not mutually exclusive, right ? You could choose to apply 1) to IOError and leave the other exception types untouched, applying 2) where viable. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12096#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12096: Attach stacktrace information to SomeException -------------------------------------+------------------------------------- Reporter: ndtimofeev | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Core Libraries | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by mnislaih): The benefit of `SomeExceptionWithCallStack` is that *all* exceptions carry call stacks. Library code could print call stacks on uncaught exception errors regardless of whether the exception type is an instance of SomeExceptionWithCallStack. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12096#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12096: Attach stacktrace information to SomeException -------------------------------------+------------------------------------- Reporter: ndtimofeev | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Core Libraries | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by mnislaih): After thinking a bit more about it, I've realised why the `SomeExceptionWithCallStack` approach doesn't work well with the per- Exception type CallStacks: we end up with two CalltStacks stored in the same exception. Now I understand why C# and F# have special primitives for `rethhrow` .... -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12096#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12096: Attach stacktrace information to SomeException -------------------------------------+------------------------------------- Reporter: ndtimofeev | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Core Libraries | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by gridaphobe): @ezyang are you sure that there are that many explicit catch-rethrows in Haskell code? We certainly have tools (e.g. `catches` and `catchJust`) to avoid having to explicitly rethrow exceptions. And it would be much less work to add the `CallStack` to `SomeException` and update `Control.Exception` '''if''' `catchJust` and co are actually used. Seems like something we could investigate on Hackage before making a decision :) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12096#comment:13 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12096: Attach stacktrace information to SomeException -------------------------------------+------------------------------------- Reporter: ndtimofeev | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Core Libraries | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by ezyang): I know that `catchIO` and then `throwIO` if the `IOError` does not match a predicate is a common idiom. It's somewhat difficult to regex for them but if you grep for `throwIO` with a reference to a variable, there are tons and tons of them. Here are three random ones I picked out: {{{ -- system-fileio removeTree root = do items <- listDirectory root forM_ items $ \item -> Exc.catch (removeFile item) (\exc -> do isDir <- isRealDir item if isDir then removeTree item else Exc.throwIO (exc :: IOError)) -- HsSVN do err <- wrapSvnError =<< _fs_commit_txn conflictPathPtrPtr reposPtr newRevPtr txnPtr poolPtr case err of Nothing -> liftM (Right . fromIntegral) (peek newRevPtr) Just e -> if svnErrCode e == FsConflict then return . Left =<< peekCString =<< peek conflictPathPtrPtr else throwIO e -- DPM (Darcs.Lock.withLock fname (writeIORef ref True >> io)) `catch` (\ (e::SomeException) -> do b <- readIORef ref if b then throwIO e else failIO ("Could not obtain lock " ++ show fname ++ ", aborting.")) }}} I just grepped for `throwIO` and picked out three random examples that looked like they were rethrowing. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12096#comment:14 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12096: Attach stacktrace information to SomeException -------------------------------------+------------------------------------- Reporter: ndtimofeev | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Core Libraries | Version: 8.0.1 Resolution: | Keywords: Exceptions Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by dfeuer): * keywords: => Exceptions -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12096#comment:15 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12096: Attach stacktrace information to SomeException -------------------------------------+------------------------------------- Reporter: ndtimofeev | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Core Libraries | Version: 8.0.1 Resolution: | Keywords: Exceptions Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): For what it's worth, I've collected some rather related thoughts (but in reference to DWARF stack traces) on wiki:Exceptions/StackTraces. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12096#comment:16 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12096: Attach stacktrace information to SomeException -------------------------------------+------------------------------------- Reporter: ndtimofeev | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Core Libraries | Version: 8.0.1 Resolution: | Keywords: Exceptions Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by ezyang): Thanks for the pointer bgamari. It looks like your proposal is essentially the same initially specified in this ticket. Your wiki page does comment that call stacks are preserved if you rethrow SomeException. But this often doesn't happen in practice. For example, the `system-fileio` example above rethrows an `IOError`: oops, call stack lost. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12096#comment:17 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12096: Attach stacktrace information to SomeException -------------------------------------+------------------------------------- Reporter: ndtimofeev | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Core Libraries | Version: 8.0.1 Resolution: | Keywords: Exceptions Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by ndtimofeev): We can substitute `?callStack` in `catch` from actual value to value from caught exception value. {{{#!hs catch' :: Exception e => IO a -> (HasCallStack => e -> IO a) -> IO a catch' eval handler = eval `catch` \err@(SomeExceptionWithStack stack _) -> let ?callStack = stack in case fromException err of Just ex -> handler ex _ -> throw err }}} Now all `throw` called from `catch` handler will be implicit rethrow. It looks like a ugly hack and required Rank2Types. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12096#comment:18 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12096: Attach stacktrace information to SomeException -------------------------------------+------------------------------------- Reporter: ndtimofeev | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Core Libraries | Version: 8.0.1 Resolution: | Keywords: Exceptions Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by gridaphobe): Actually that's not so bad, it's the same trick we use for `GHC.Stack.withFrozenCallStack`. And this should also give us locations for the rethrows, which sounds like a nice touch to me (e.g. maybe you were expecting the exception to be caught and need to figure out why it was rethrown). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12096#comment:19 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12096: Attach stacktrace information to SomeException -------------------------------------+------------------------------------- Reporter: ndtimofeev | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Core Libraries | Version: 8.0.1 Resolution: | Keywords: Exceptions Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonmar): I quite like the idea of adding the call stack to `SomeException` actually. A lot of rethrowing operations already do the right thing, e.g. `catchJust` works: {{{ catchJust p a handler = catch a handler' where handler' e = case p e of Nothing -> throwIO e Just b -> handler b }}} So does `onException`, and the things that use it (`bracket` etc.) {{{ onException :: IO a -> IO b -> IO a onException io what = io `catch` \e -> do _ <- what throwIO (e :: SomeException) }}} So the places that don't work are those places that are using bare `catch` and re-throwing a more specific exception after doing some filtering on it. For those we should recommend using `catchJust` when possible, and perhaps provide alternative APIs that allow more expressive filtering. In the meantime there will be some places that get the wrong call stacks, but too bad - this is a debugging feature and as such doesn't need to be perfect. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12096#comment:20 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12096: Attach stacktrace information to SomeException -------------------------------------+------------------------------------- Reporter: ndtimofeev | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Core Libraries | Version: 8.0.1 Resolution: | Keywords: Exceptions Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by ekmett): Replying to [comment:17 ezyang]:
Your wiki page does comment that call stacks are preserved if you rethrow SomeException. But this often doesn't happen in practice. For example, the `system-fileio` example above rethrows an `IOError`: oops, call stack lost.
Yes, there is no correct way to preserve this information that doesn't require the user signalling intent to us. Is what they are throwing a truly fresh exception or does it derive from one they were given? On the other hand, the very callstack was information you lacked to begin with in the old story. If we extend SomeException you can write code that is compatible with both the old and new story, and you can make a couple of one line tweaks to your code to make it so you can preserve the shiny new callstack information. If we extend _every_ exception type to carry this information then there is no code that has ever been written against the exception hierarchy that can survive the change. Moreover, the Exception class itself then has to provide a means for us to get in and find and replace the callStack in these user definable data types, and the user has to construct an empty callstack to throw their exception in the first place, all of which seems like a messy, invasive, and slow design. If we offer some subset of combinators (subject to bikeshedding) like {{{#!hs throwWithCallStack :: Exception e => e -> CallStack -> a withCallStack :: SomeException -> CallStack -> SomeException rethrow :: SomeException -> a rethrowAs :: Exception => SomeException -> e -> a throwIOWithCallStack, rethrowIO, rethrowIOAs ... catchWithCallStack :: Exception e => IO a -> (e -> CallStack -> IO a) -> IO a ... }}} to the user, then they can fix up these cases as they find them, and in the meantime they only get the callstack up to the last `throw`, which is __still__ more information than they have today. The same scenario involving destroying the source location happens in languages like c++ w/ throw vs rethrow. I personally am sad that extending `SomeException` with the callstack would mean my pretty little prisms into `SomeException` for the various exception types become a (convenient) lie, but I don't think the alternative of making the user decorate all of their exception types with a callstack, mangle every throw so that they include an empty callstack to kickstart the exception, and supply a callstack update function, and change all of their existing handlers, most of which do not rethrow, to deal with an extra argument is a terribly practical alternative. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12096#comment:21 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12096: Attach stacktrace information to SomeException -------------------------------------+------------------------------------- Reporter: ndtimofeev | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Core Libraries | Version: 8.0.1 Resolution: | Keywords: Exceptions Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by ezyang): OK, well, don't let me stop you guys from adding CallStack to SomeException :) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12096#comment:22 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12096: Attach stacktrace information to SomeException -------------------------------------+------------------------------------- Reporter: ndtimofeev | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Core Libraries | Version: 8.0.1 Resolution: | Keywords: Exceptions Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | Exceptions/StackTraces | -------------------------------------+------------------------------------- Changes (by bgamari): * wikipage: => Exceptions/StackTraces -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12096#comment:23 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12096: Attach stacktrace information to SomeException -------------------------------------+------------------------------------- Reporter: ndtimofeev | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Core Libraries | Version: 8.0.1 Resolution: | Keywords: Exceptions Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #13372 | Differential Rev(s): Wiki Page: | Exceptions/StackTraces | -------------------------------------+------------------------------------- Changes (by bgamari): * related: => #13372 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12096#comment:24 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12096: Attach stacktrace information to SomeException -------------------------------------+------------------------------------- Reporter: ndtimofeev | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Core Libraries | Version: 8.0.1 Resolution: | Keywords: Exceptions Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #13372 | Differential Rev(s): Wiki Page: | Exceptions/StackTraces | -------------------------------------+------------------------------------- Changes (by erikd): * cc: erikd (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12096#comment:25 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12096: Attach stacktrace information to SomeException -------------------------------------+------------------------------------- Reporter: ndtimofeev | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Core Libraries | Version: 8.0.1 Resolution: | Keywords: Exceptions Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #13372 | Differential Rev(s): Wiki Page: | Exceptions/StackTraces | -------------------------------------+------------------------------------- Changes (by saurabhnanda): * cc: saurabhnanda (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12096#comment:26 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12096: Attach stacktrace information to SomeException -------------------------------------+------------------------------------- Reporter: ndtimofeev | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Core Libraries | Version: 8.0.1 Resolution: | Keywords: Exceptions Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #13372 | Differential Rev(s): Wiki Page: | Exceptions/StackTraces | -------------------------------------+------------------------------------- Changes (by k-bx): * cc: k-bx (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12096#comment:27 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC