haskell / core-libraries-committee

95 stars 16 forks source link

Exception backtrace proposal: Part 4: Rethrowing #202

Closed bgamari closed 2 months ago

bgamari commented 1 year ago

Tracking ticket: #164

This proposal attempts to summarise the interface design of the exception annotation scheme proposed in GHC Proposal #330. Specifically, this proposal covers the changes described in section 2.6.

Note that the GHC Proposal is free-standing; no reading of the discussion which lead to its current accepted state should be necessary to understand its contents. Consequently, to avoid repetition I will refer back to the GHC Proposal instead of repeating myself here. I will, however, attempt to give some color to the interfaces by providing typical usage examples where necessary. However, the GHC Proposal is to be considered the canonical definition of the interfaces; in particular, section 2 and its subsections precisely captures the changes proposed in base.

Preserving context across rethrowing

A common pattern in Haskell applications is to catch an exception and later rethrow it (or a value derived from it) in the handler. However, this pattern defeats our annotation mechanism as context of the original exception will not be propagated to the rethrown exception. In this proposal we address this weakness by teaching catch and similar operations to augment exceptions thrown from handlers with the handled exception (and its context).

Specifically, we propose to introduce a new ExceptionAnnotation (section 2.6):

newtype WhileHandling = WhileHandling SomeException

instance ExceptionAnnotation WhileHandling

We then modify catch to annotate exceptions thrown from the handler with a WhileHandling containing the handled exception:

catch :: Exception e => IO a -> (e -> IO a) -> IO a
catch (IO io) handler = IO $ catch# io handler'
 where
   handler' e =
     case fromException e of
       Just e' -> unIO (annotateIO (WhileHandling e) (handler e'))
       Nothing -> raiseIO# e

We then introduce a catchNoAnnotation exposing the old semantics of catch for cases where this is desired.

Migration

This change has no effect on program semantics modulo ExceptionContext. However, it will cause a slight increase in allocations when catch'ing exceptions.

parsonsmatt commented 1 year ago

WhileHandling is going to make it way harder to get a complete picture of the annotations present on an exception. The design of annotated-exception stores a [Annotation], and then I do some hacky thing where I merge CallStacks together. The result is that you get all the annotations, easy peasy - answering the question "What annotations are present on this exception?" is trivial, you look at the list.

With this, we now have an indirection - we need to dig into the ExceptionAnnotation context, then look for a WhileHandling, dig into the SomeException, and now we have the second level of annotations.

getAllAnnotations :: SomeException -> [SomeExceptionAnnotation]
getAllAnnotations se = 
  let this = getAllExceptionAnnotation $ someExceptionContext se 
       causedBys = mapMaybe (\ (SomeExceptionAnnotation ann) -> cast ann :: Maybe WhileHandling) this
       otherContexts = concatMap ( \(WhileHandling someException) -> someExceptionContext someException) causeBys
   in this <> otherContexts

I'm not convinced this holds up if there are other exception wrapper types, or if exception hierarchies are used. I anticipate that this will lose annotations if you don't know, up front, all of the casts that you need to do to dig around and find the annotations.

bgamari commented 1 year ago

@parsonsmatt, I'm a bit unclear on what concretely you are concerned about. Are you worried that there might be exceptions (and therefore ExceptionContexts) buried in annotations other than WhileHandling? If so, it seems that this problem is far more general than WhileHandling; rather this is inherent in the dynamically-typed nature of annotations.

parsonsmatt commented 10 months ago

The design of annotated-exception right now has the annotations all in a flat list. There's literally no logic for finding the annotatations - they're all present, all the time, very easily.

The only occasion where we actually do have hidden annotations is when we've got a "catch all" exception wrapper and the developer expliciltly hides annotations. As an example, we have this in our codebase:

data ClientError 
    = InvariantViolated Text 
    | {- other cases -}
    | DatabaseError SomeException

The way this DatabaseError is used is something like this:

clientDB :: DB a -> AppM a
clientDB action = 
  runDB action `catches` 
    [ Handler \(e :: ClientError) -> throwWithCallStack e
    , Handler \(other :: SomeException) -> throwWithCallStack (DatabaseError other)
    ]

This is "safe" because catches in annotated-exception inspects the type of these, and if you provide a handler that's not an AnnotatedException, it'll inject another handler that's on AnnotatedException e, and reattach the exception context - so the above really expands to:

clientDB :: DB a -> AppM a
clientDB action = 
  runDB action `catches` 
    [  Handler \(AnnotatedException anns (e :: ClientError) -> 
        checkpointMany anns $ throwWithCallStack e
    , Handler \(e :: ClientError) -> throwWithCallStack e
    , Handler \(AnnotatedException anns (other :: SomeException) -> 
        checkpointMany anns $ throwWithCallstack other 
    , Handler \(other :: SomeException) -> throwWithCallStack (DatabaseError other)
    ]

You can defeat this safeguarding by manually catching AnnotatedException and then manually stuffing it into a SomeException.

If annotated-exception weren't careful to re-attach the context when throwing, then we'd have a top-level thing like:

AnnotatedException
    { annotations = 
        [ Annotation @CallStack ...
        ]
    , exception = 
        DatabaseError 
            (SomeException 
                (AnnotatedException
                    { annotations = 
                        [ Annotation @CallStack ...
                        , Annotation @SomethingElse ...
                        , {- more hidden annotations -}
                        ]
                    , exception = 
                        TheActualProblem
                    }
                )
            )
    }

Now, we can't just fold over the [Annotation] on the top-level. We have to fold over the annotations, then dig into the exception type if it is a wrapper. If it is a wrapper, (or contains a wrapper somewhere), then we need to unpack any possible annotations from there.

So the design of annotated-exception tries, as much as possible, to ensure that there's only one level of annotations, and that's the very top level. Naturally we can't stop the user from doing something that defeats that entirely, but the result of this is that we almost never lose or drop annotations.

This ends up being a really nice property in our app, because we just catch the final AnnotatedException, fold over the [Annotation] to modify our error report, and away we go. There's no need to dig through all the various dynamic type wrappers, and we don't have to recursively dig through other annotations to find them.

The design proposed here will double the inconvenience of this sort of digging by forcing you to dig through not just any possible exception types, but also the CausedBy wrapper, which itself has a SomeException, which may have it's own CausedBy annotations in addition to it's own wrapper exception.


To be a bit more concise:

OK, that was still too verbose. Let me try and distill further:

bgamari commented 10 months ago

@parsonsmatt perhaps it alleviate your concern if we introduced another method to Exception:

class Exception a where
    nestedExceptions :: a -> [SomeException]
    nestedExceptions _ = []

This would allow us to preserve the clear semantics of annotations while also enabling reconstruction of all relevant annotations from an exception.

parsonsmatt commented 10 months ago

That does help, yes. I still think it's valuable to provide a function getAllAnnotations :: SomeException -> [SomeAnnotation] that doesn't require end users doing anything other than writing their instancs correctly. So that may mean we need a similar method on IsAnnotation

Bodigrim commented 9 months ago

@bgamari @parsonsmatt did you converge to a final proposal which we can vote on?

michaelpj commented 9 months ago

I just wanted to reiterate that this is a very well-established approach taken by Java, which I think provides evidence that the inconvenience is not so great.

michaelpj commented 9 months ago

Additionally, merging annotations seems hard in general. I find this concerning:

this provides us with a single complete CallStack

I don't see how this can be correct? The exception thrown from the handler and the exception that was originally caught may have wildly different call stacks. If we want to give people the full picture of what happened I think we need to present those separately.

michaelpj commented 9 months ago

Does nestedExceptions even need to be a class method? Isn't it enough to just go through the WhileHandlings?

bgamari commented 9 months ago

Does nestedExceptions even need to be a class method? Isn't it enough to just go through the WhileHandlings?

I think @parsonsmatt's concern applies to a fairly broad spectrum of cases. For instance, consider Network.HTTP.Client.HttpException, which may hide exceptions (and possibly their annotations).

michaelpj commented 9 months ago

Ah yes, indeed, we would expect other mechanism similar to catch to use other mechanisms for storing exception "causes". I do think the Java approach there is unsatisfying, in that they have Throwable getCause() on exceptions, but this makes a somewhat unjustified assumption that there is a single such exception and that it is a "cause".

bgamari commented 9 months ago

At the moment I am leaning towards addressing @parsonsmatt's concern with the following additions:

class ExceptionAnnotation a where
    ...
    -- | Extract any exceptions nested within an annotation.
    exceptionAnnotationNestedExceptions :: a -> [SomeException]

class Exception a where
    ...
    -- | Extract any exceptions nested within an exception.
    nestedExceptions :: a -> [SomeException]

flattenAnnotations :: Exception a -> [SomeExceptionAnnotation]
flattenAnnotations e = concat
    [ exceptionAnnotations e
    , concatMap flattenAnnotations (concatMap (\(SomeExceptionAnnotation ann) -> exceptionAnnotationNestedExceptions ann) (exceptionAnnotations e))
    , concatMap flattenAnnotations (nestedExceptions e)
    ]

However, there is a considerable design space and these additions seem a bit orthogonal to the simple interface described in in this proposal. Consequently, I will open a new proposal for this.

Consequently, I would like to submit this to the CLC for a vote.

bgamari commented 9 months ago

I have opened https://github.com/haskell/core-libraries-committee/issues/250 with the above proposal.

parsonsmatt commented 9 months ago

Additionally, merging annotations seems hard in general. I find this concerning:

this provides us with a single complete CallStack

I don't see how this can be correct? The exception thrown from the handler and the exception that was originally caught may have wildly different call stacks. If we want to give people the full picture of what happened I think we need to present those separately.

The callstacks would have some divergence, but the original exception's callstack is likely more important.

foo = 
  bar `catch` conditionallyRethrow

The callstack up to foo will be the same. Then we go down the bar callstack, throw an exception, and hit catch. Then conditionallyRethrow starts it's own callstack, which (in my experience) is almost always one or maybe two frames.

foo = 
  bar `catch` \(e :: IOException ) -> 
    if quux e then pure 0 else throwIO FooException

In this case, having the callstacks merged is vastly better than having a separate CallStack for FooException, which gets rendered, and forgets everything that happened in bar (unless you reconstruct it by digging through the other annotations and WhileHandling etc), and then if you do reconstruct it, you have to repeat the calls up to foo anyway!

The machinery in #250 would allow a libray author to write such a function, providing that all of the exception wrapper types have been updated and properly written. With a flat exception annotation list, we start with everything we need. With a nested structure, we start with very little, and need to do more work through the ecosystem to bring things into compliance, and we need to tell folks to write their own methods of nestedExceptions et al.

So I think there's significant extra work imposed on the whole ecosystem with #250, and concordant risk that exceptions won't implement these methods, and we'll drop information on the floor and make it harder to recover.

If we accumulate exception annotations on the top level, then we get deep annotations and callstacks immediately when the feature releases, for all library versions. If we do the approach in #250 then we don't get this information usefully until we release the GHC with this, then we need to update all libraries that have exception wrappers (with CPP so it's backwards compatible), and then we only get nice information when every library in the chain has been updated.


For conciseness:

michaelpj commented 9 months ago

In this case, having the callstacks merged is vastly better than having a separate CallStack for FooException, which gets rendered, and forgets everything that happened in bar (unless you reconstruct it by digging through the other annotations and WhileHandling etc), and then if you do reconstruct it, you have to repeat the calls up to foo anyway!

You can just... render it? I don't see why we wouldn't get good rendering by default. e.g. consider the following Java stack trace I found on the internet:

StudentException: Error finding students
        at StudentManager.findStudents(StudentManager.java:13)
        at StudentProgram.main(StudentProgram.java:9)
Caused by: DAOException: Error querying students from database
        at StudentDAO.list(StudentDAO.java:11)
        at StudentManager.findStudents(StudentManager.java:11)
        ... 
Caused by: java.sql.SQLException: Syntax Error
        at DatabaseUtils.executeQuery(DatabaseUtils.java:5)
        at StudentDAO.list(StudentDAO.java:8)
        ... 

This has all the information, without showing anything misleading. I do think that a requirement should be that we get default rendering at least as good as this for the WhileHandling annotation. If what we're actually going to get is just the first stack trace then indeed that's no good

Is your objection that nestedAnnotations is too generic, and so we don't have a single notion of "cause" like Java exceptions do which we can lean on to get good rendering?

Bodigrim commented 9 months ago

@bgamari @parsonsmatt @michaelpj please signal when you converge to a consensus on this.

bgamari commented 9 months ago

Is your objection that nestedAnnotations is too generic, and so we don't have a single notion of "cause" like Java exceptions do which we can lean on to get good rendering?

@parsonsmatt it would be great to have a response to @michaelpj's question. It's hard to know how to amend the proposal without a clear picture of what use-case we are designing for.

Ultimately, I suspect that at this point this final part of the exception backtrace series will likely be deferred to GHC 9.12; it's simply too late in the release cycle to comfortably come up with a suitable design and implement. It is nice that the proposals are now modular enough to allow this sort of deferral.

Bodigrim commented 9 months ago

@parsonsmatt just a gentle reminder that it would be nice to find a conclusion here.

parsonsmatt commented 9 months ago

Is your objection that nestedAnnotations is too generic, and so we don't have a single notion of "cause" like Java exceptions do which we can lean on to get good rendering?

No, the objection is that it requires all authors of annotations and exceptions to properly implement a method, where the obvious/easy default is to drop the information on the floor.

My concern is with losing information, or hiding information, or just generally making it much harder to find and use the information in a useful way. Keeping the annotations in a top-level property and not nesting them accomplishes this very nicely. Doing anything else is guaranteed to lose information and make things harder.

nestedException _ = [] is particularly troublesome. It means that you need to opt-in to providing this behavior, which can only be done on certain library versions (when the library author actually releases a new version, along with the necessary CPP to keep it backwards compatible).

If we just preserve annotations in the top-level SomeException, then all users immediately get a full picture on day 1 of this releasing. If we require all libraries to upgrade, and then wait to use all the new libraries, then we're going to have a significantly longer and more error-prone adoption of this.

As a case study, we use annotated-exception which does what I suggest. There are no issues caused by having a single top-level list of annotations, and the library tries really hard to preserve that guarantee. The main problem is that the design can't prevent more information to be lost - people are used to these two definitions being equivalent:

handle0 = 
  action `catch` handler

handle1 = 
  eresult <- try action
  case result of
    Left err -> handler err
    Right a -> pure a

But with annotated-exception, you actually lose the annotations when you try, unless you specifically try @(AnnotatedException e) instead of try @e. This has been a problem, where using the wrong exception handling strategy results in lost annotations which makes it harder to diagnose/debug/understand runtime errors.

So all of the experience we've had with annotated-exception in our codebase has been positive, with the exception of sometimes losing annotations due to programmer error. This proposal adds significant surface area for programmer error to lose information.

adamgundry commented 9 months ago

@parsonsmatt I'm struggling to understand your position, unfortunately. You make good arguments against #250, namely that adding a nestedException member to the Exception class with a default implementation basically guarantees it is "liable to be incorrect for existing exception types" (as @bgamari noted but perhaps could have emphasized more). But I'm not sure exactly what you are arguing for instead.

One could imagine changing catch to copy/merge the annotations from the rethrown exception, as well as adding a WhileHandling annotation, but it seems like that discards information (because you can no longer easily distinguish the original call stack from the call stack at the rethrow site) and I don't see how you can get the correct output from displayException (how do you avoid rendering the original call stack twice, unless you get rid of WhileHandling altogether?).

The original proposal allows displayException to simply do the right thing (along the lines of https://github.com/haskell/core-libraries-committee/issues/202#issuecomment-1930365274). I can see that it could be difficult to write some kind of alternative rendering of exceptions that works for arbitrary wrapper types, but do you have a particular use case of that nature in mind?

parsonsmatt commented 9 months ago

In annotated-exception, I have addCallStackToAnnotations, which calls mergeCallStack, which combines two CallStacks and removes duplicates.

catch delegates to catches, which delegates to checkpointMany, which adds the annotations back onto the thrown exception, including calling addCallStackToException with the callStack from HasCallStack.

In this design, I believe we'd just grab the annotations from the SomeException we are catching and stuff them as annotations into any rethrown exceptions.

catch :: Exception e => IO a -> (e -> IO a) -> IO a
catch (IO io) handler = IO $ catch# io handler'
 where
   handler' e =
     case fromException e of
       Just e' -> unIO (annotateManyIO (exceptionAnnotations e) (handler e'))
       Nothing -> raiseIO# e

I think I can distill this down to a few questions, most of which are orthogonal:

  1. Do we include a WhileHandling annotation in catch? a. If so, do we want to do anything to avoid duplication? ie catch action throwIO would include a WhileHandling, even though the exception is the same.
  2. Do we combine annotations in catch? a. If not, we almost certainly want to use a WhileHandling annotation to cover that
  3. Do we merge callstacks? Or do we keep them separate? a. If we keep them separate, do we want to deduplicate them in some way?
  4. Should catch also annotate with the current callstack? Should annotateIO?

My answers:

  1. Sure, WhileHandling seems useful. I wonder if it makes sense to worry about duplication - but then, we don't have Eq for exceptions generally, so we'd either need to use the show representation or the type, and both of those aren't ideal. Duplicating an exception into the WhileHandling may lead to extraneous information for simple rethrows, and might blow up memory usage if we are doing catch in a loop.
  2. I think we should combine annotations - whenever we catch, the handler should re-attach any annotations to whatever exception is thrown. Otherwise, we risk losing valuable nformation.
  3. We've seen a lot of benefit from keeping the CallStack merged and deduplicated with annotated-exception. It's relatively straightforward to read and interpret them.
  4. Yes and yes. catch is in a great position to enrich exceptions with location information. annotateIO similarly - who wouldn't want callsite information on that?
michaelpj commented 9 months ago

We've seen a lot of benefit from keeping the CallStack merged and deduplicated with annotated-exception. It's relatively straightforward to read and interpret them.

Do you have an example of this? I'm really struggling to see how a merged call stacks can be anything other than incorrect, versus the Java approach of keeping the two call stacks from the two throws clearly separate and labelled.

Bodigrim commented 6 months ago

Folks, what's the conclusion on this? Shall we wait until GHC 9.10 is out and battle-tested for a while before continuing the discussion? If that's the sentiment, I'll close this as dormant to reopen once there is more user experience.

We can also just vote as is. Consensus is not a requirement, however it would be a pity to have the proposal defeated because of a minor disagreement. I cannot quite read the room at the moment.

CC @parsonsmatt @bgamari

bgamari commented 6 months ago

Folks, what's the conclusion on this? Shall we wait until GHC 9.10 is out and battle-tested for a while before continuing the discussion? If that's the sentiment, I'll close this as dormant to reopen once there is more user experience.

Yes, this is roughly where I fall. I think it's hard to say at the moment what the right course of action is here. I hope to have a blog post out shortly after the release describing the exception backtrace work, which might spur more discussion.

Bodigrim commented 6 months ago

Thanks, @bgamari, let me make it as dormant then. Feel free to reopen later on.

edsko commented 4 months ago

If I understand the discussion correctly, the question is essentially whether we want a hierarchical structure (WhileHandling) versus a flat structure (in the style of annotated-exception). I can see the benefits of the flat structure:

  1. In some pathological scenarios the hierarchical structure might be very large (it reminds me of the horrors of running real code with +RTS -xc).
  2. In the case where the same exception is caught and then rethrown we could get quite a bit of duplication. For example, we probably want to be careful in the definition of bracket and friends, and avoid adding unnecessary WhileHandling annotations there. (This is not a new observation, however: onException is already redefined in terms of NoBacktrace -- although NoBacktrace is not exported in base , unclear why. An oversight?)
  3. In cases where we want to process the annotations in code (as opposed to have a human looking at the result of displayException), or perhaps extract a specific type of annotations (a valid use case, ExceptionAnnotation has Typeable as a superclass constraint for a reason) then that might be difficult unless we have some way of getting nested exceptions (which comes with its own difficulties, as discussed above).

I am nonetheless in favour of the original proposal: it feels like flattening loses information, and in difficult debugging scenarios, I might want to trace the exact path of how an exception was raised, including all the individual callstacks of each handler: I share @michaelpj 's concern that merging CallStacks is not in general a very meaningful combination.

Moreover, I think the flattened form can easily be obtained from the hierarchical one, simply by walking the WhileHandling tree, as Michael points out. There was some discussion on this specific point above, which I will come back to in a separate comment.

We are planning to talk about the new exception infrastructure (annotations and backtraces) in the upcoming episode of the Haskell Unfolder next Wednesday (July 17th, 18:30 UTC, live-streamed on YouTube). I will mention the the problem of preserving annotations, and point to this ticket; perhaps this will generate some more interest and discussion.

edsko commented 4 months ago

On the topic of flattening the hierarchical structure: the claim is that we can simply flatten the hierarchy by walking over WhileHandling. I think this claim is correct. Consider a setup like this (where NestException is meant to be a canonical example of the kind of thing that HttpException does, as in @bgamari 's example):

data OriginalException = OriginalException
  deriving stock (Show, Generic)
  deriving anyclass (Exception, PrettyVal)

data NestSomeException = NestSomeException SomeException
  deriving stock (Show, Generic)
  deriving anyclass (Exception, PrettyVal)

data Annotation = Annotation String
  deriving stock (Show, Generic)
  deriving anyclass (ExceptionAnnotation, PrettyVal)

throwOriginal :: IO ()
throwOriginal =
    annotateIO (Annotation "hi") $
      throwIO OriginalException

rethrowNested1 :: IO ()
rethrowNested1 =
    throwOriginal `catch202` \e@OriginalException ->
      throwIO $ NestSomeException (toException e)

rethrowNested2 :: IO ()
rethrowNested2 =
    throwOriginal `catchFlat` \e@OriginalException ->
      throwIO $ NestSomeException (toException e)

where catch202 is catch as proposed originally in this ticket, and catchFlat is an alternative definition that merges contexts; perhaps something like this:

catchFlat :: forall e a. Exception e => IO a -> (e -> IO a) -> IO a
catchFlat io handler = catch io handler'
  where
    handler' :: SomeException-> IO a
    handler' e =
        case fromException e of
          Just e' -> catch (handler e') (handleRethrows (someExceptionContext e))
          Nothing -> throwIO $ NoBacktrace e

    handleRethrows :: ExceptionContext -> SomeException -> IO a
    handleRethrows origCtxt e@(SomeException e') =
        throwIO $ NoBacktrace $
          ExceptionWithContext (origCtxt <> someExceptionContext e) e'

Then with the hierarchical approach, we get something like

SomeException
  { someExceptionContext =
      ExceptionContext
        [ WhileHandling
            SomeException
              { someExceptionContext =
                  ExceptionContext
                    [ Annotation hi
                    ,  <backtrace to throwIO in throwOriginal>
                    ]
              , fromException = OriginalException
              }
        , <backtrace to throwIO in rethrowNested1>
        ]
  , fromException =
      NestSomeException
        SomeException
          { someExceptionContext = ExceptionContext []
          , fromException = OriginalException
          }
  }

whereas with the flat approach we get something like

SomeException
  { someExceptionContext =
      ExceptionContext
        [ Annotation hi
        , <backtrace to throwIO in throwOriginal>
        , <backtrace to throwIO in rethrowNested2>
        ]
  , fromException =
      NestSomeException
        SomeException
          { someExceptionContext = ExceptionContext []
          , fromException = OriginalException
          }
  }

It is of course true, as @bgamari points out, that this does not solve the general problem of other ways of nesting exceptions. For example, if some library bypasses catch altogether in favour or one that does not manipulate the context at all

rethrowNested3 :: IO ()
rethrowNested3 = 
    throwOriginal `catchExceptionNoAnnotation` \e ->
      throwIO $ NestSomeException e

then we might end up with something like

SomeException
  { someExceptionContext =
      ExceptionContext
        [ <backtrace to throwIO in rethrowNested3>
        ]
  , fromException =
      NestSomeException
        SomeException
          { someExceptionContext =
              ExceptionContext
                [ Annotation hi
                , <backtrace to throwIO in throwOriginal>
                ]
          , fromException = OriginalException
          }
  }

for which it is indeed harder to extract all (nested) annotations; but this is true for both the hierarchical and the flat approach.

So I think the problem of getting nested exceptions should be considered to be an orthogonal concern, independent from the WhileHandling proposal.

(The above experiment is available in the GitHub repo for the Haskell Unfolder, episode 29).

mpickering commented 2 months ago

@edsko There appear to be two definitions of onException.

The one in GHC.Internal.IO is defined as:

334 onException :: IO a -> IO b -> IO a                                             
335 onException io what = io `catchException` \e -> do                              
336     _ <- what                                                                   
337     throwIO $ NoBacktrace (e :: SomeException) 

but in GHC.Internal.Control.Exception.Base as:

191 -- | Like 'finally', but only performs the final action if there was an         
192 -- exception raised by the computation.                                         
193 onException :: IO a -> IO b -> IO a                                              
194 onException io what = io `catch` \e -> do _ <- what                             
195                                           throwIO (e :: SomeException) 

So if you use bracket from Control.Exception.Base then you get different behaviour than if you use it from GHC.IO.

mpickering commented 2 months ago

@Bodigrim @haskell/core-language-committee

I think the backtrace mechanism is severely hindered by the lack of a rethrowing mechanism, please can we make progress with this proposal?

At the moment if you have any kind of error handling in your application which uses bracket, try or onException then you will routinely lose any annotations (unless you include the location explicitly in the error)

For example:

module Main where

import System.Directory
import Control.Exception
import System.OsPath
import GHC.Internal.Foreign.C.String.Encoding
import GHC.Internal.IO.Encoding

data E = E deriving Show

instance Exception E

f1 :: FilePath
f1 = throw E

main = do
  f <- getForeignEncoding
  let y1 :: FilePath
      y1 = throw E
  -- Prints a call stack
  --print y1
  -- Doesn't print a call stack, annotation is discarded
  print =<< getModificationTime f1

getModificationTime is a function from directory, which eventually calls withCString which is implemented in terms of bracket which is implemented in terms of onException, which rethrows exceptions losing the annotation.

It is of principle importance that base is modified as all exception handling utilities must propagate exceptions

Are we all in agreement that rethrowing is important for base functions? If we are then please can the disagreements be mediated and a fix to the base libraries prioritised?


For me personally, I prefer the extra structure which WhileHandling approach takes, which seems to be the consensus on this issue. Merging call stacks seems to be incorrect behaviour to me.

In any case, if there is a counter-proposal it should also be implemented and put a CLC vote as this is an important issue to fix! However, if there isn't a counter-proposal which is implemented then I think the CLC should vote on the WhileHandling approach as described in this issue and already implemented in the original patch.

Kleidukos commented 2 months ago

@mpickering I think the CLC is waiting on this: https://github.com/haskell/core-libraries-committee/issues/202#issuecomment-2098815766

Bodigrim commented 2 months ago

As @Kleidukos says, the original proposer agreed to close the proposal as dormant. It's up to a proposer to drive the process, argue in favour of the proposal and eventually ask for a vote. I'm happy to reopen once @bgamari gains enough confidence in the proposed approach to push for it or if any of GHC developers feels sufficiently confident and wishes to take over (please say so if this is the case).

parsonsmatt commented 2 months ago

I think my qualms were the only thing holding this up, and it seems like I'm alone in thinking that way, so I'm happy to defer to consensus of other people on this. I'd +1 as-is now.

Bodigrim commented 2 months ago

@mpickering would you like to take over and, if everything in the top post is up-to-date, trigger a vote?

edsko commented 2 months ago

@parsonsmatt I am curious if you think my analysis at https://github.com/haskell/core-libraries-committee/issues/202#issuecomment-2225486157 that the representation you prefer is derivable from the proposal as it stands is correct, or whether I missed something?

bgamari commented 2 months ago

@Bodigrim I would like to trigger a vote.

parsonsmatt commented 2 months ago

@parsonsmatt I am curious if you think my analysis at #202 (comment) that the representation you prefer is derivable from the proposal as it stands is correct, or whether I missed something?

The problem is accessing the information, not capturing it. I think that - with the new methods on the Exception and Annotation classes introduced in this proposal - those concerns are mostly dealt with.

The central issue is: "I want a function flattenAllAnnotations :: SomeException -> [SomeAnnotation] with the property that all of the hidden annotations are returned in that list, and nothing is lost or forgotten." The dynamically typed nature of how we're storing the information makes retrieval more difficult. So, unlike normal Haskell, where more structure makes things easier to store and access, we actually have a situation where adding more structure makes things more difficult to access, since the stucture is hidden in dynamic casts.

I think the trade-off that we're looking at is something like:

My preference is for the former, but I don't want to hold this up since it seems others prefer the latter.

Bodigrim commented 2 months ago

Dear CLC members, let's vote on the proposal to preserve exception context across rethrowing as described in https://github.com/haskell/core-libraries-committee/issues/202#issue-1870318062. See also https://github.com/haskell/core-libraries-committee/issues/202#issuecomment-2326358001 for a motivational example.

@tomjaguarpaw @hasufell @mixphix @velveteer @angerman @parsonsmatt


+1 from me, I'm convinced by the discussion above.

parsonsmatt commented 2 months ago

+1

mixphix commented 2 months ago

+1

velveteer commented 2 months ago

+1

tomjaguarpaw commented 2 months ago

+1


To get this kind of behaviour we have two options

The upside of the first option is that one gets the benefit of reannotation in one's dependencies even if those dependencies weren't implemented with it in mind. I'm normally not keep on these kinds of "opt out" changes where we force people's code to become "better", but in this case, because the struggles to understand exception provenance are a significant impediment to adoption of Haskell, I think it's worth it.

Side question: normally we vote on specific MRs. Are we not doing that for this series of proposals, or have a missed an MR somewhere? ("Ctrl-F gitlab" on this page returns nothing, as does "Ctrl-F MR").

Bodigrim commented 2 months ago

Thanks all, that's enough votes to approve.

Side question: normally we vote on specific MRs. Are we not doing that for this series of proposals, or have a missed an MR somewhere?

Historically we voted on exception backtrace proposals without MRs, yes.

adamgundry commented 1 month ago

This has been implemented: https://gitlab.haskell.org/ghc/ghc/-/merge_requests/13302