[ghc-steering-committee] [ghc-proposals/ghc-proposals] Decorate exceptions with backtrace information (#330)

Simon Peyton Jones simon.peytonjones at gmail.com
Tue Nov 29 11:06:30 UTC 2022


Vlad

Thank you for such a thorough job!  You are an example to us all.

Simon

On Tue, 29 Nov 2022 at 10:56, Vladislav Zavialov <notifications at github.com>
wrote:

> Hi @bgamari <https://github.com/bgamari>! I have finished another round
> of review and identified a few potential improvements.
>
>    1.
>
>    *Proposal structure.* At the moment, the "Proposed Change
>    Specification" section contains a lot of information in addition to the
>    specification itself. It's mixed with exposition and
>    implementation-specific code snippets. Instead, I expect to see a concise
>    list (bulleted or numbered) of proposed changes, as seen from the end-user
>    perspective. Undoubtedly, the rest of the prose is also valuable, so I ask
>    you not to remove it but to distribute it across other sections of the
>    proposal text.
>    2.
>
>    *Make ExceptionContext opaque.* The proposal define ExceptionContext
>    as a wrapper around [SomeExceptionAnnotation], but should we expose
>    this fact to our users? What if we decide to store additional information
>    there? I believe it would be best not to export the data constructor to
>    allow for future changes.
>    3.
>
>    *Remove the Semigroup instance for ExceptionContext*. The annotations
>    are stored in a list, so (<>) is O(n), and that's not good.
>    Furthermore, I can't think of a use case for appending annotations from
>    different exceptions, so there's a simple way to address this: do not
>    define Semigroup or Monoid instances.
>    4.
>
>    *Semantics of ExceptionContext.* The list of SomeExceptionAnnotation
>    is ordered, so we ought to define how users can interpret this order. What
>    does it mean for one annotation to come before another? Here's an idea:
>    introduce an operation similar to checkpoint
>    <https://hackage.haskell.org/package/annotated-exception-0.2.0.4/docs/Control-Exception-Annotated.html#v:checkpoint>
>    from annotated-exceptions:
>
>    annotateIO :: ExceptionAnnotation a => a -> IO r -> IO r
>
>    The order of SomeExceptionAnnotation would reflect the nesting of
>    calls to annotateIO, reflecting the call stack in its own way
>    (separately from the collected backtraces).
>    5.
>
>    *Group backtraces in a record.* If we say that a single element in
>    SomeExceptionAnnotation corresponds to a call to annotateIO, it is
>    somewhat strange to add multiple annotations for a single event of
>    collecting backtraces. After all, what would it mean for the
>    HasCallStack backtraces to come before the CostCentre backtrace or
>    vice versa? So introduce a record to store them together:
>
>      data Backtraces =
>        Backtraces {
>          costCentreBacktrace :: Maybe (Ptr CostCentreStack),
>          hasCallStackBacktrace :: Maybe GHC.Stack.CallStack,
>          executionBacktrace :: Maybe [GHC.ExecutionStack.Location],
>          ipeBacktrace :: Maybe [StackEntry]
>       }
>
>    (I refine this idea in the next suggestion)
>    6.
>
>    *Encode the Backtraces record with GADTs*. The record type Backtraces
>    that I suggest in the previous point introduces a slightly annoying form of
>    code duplication. The proposal already has an enumeration of backtrace
>    mechanisms:
>
>    data BacktraceMechanism
>       = CostCenterBacktraceMech
>       | ExecutionStackBacktraceMech
>       | IPEBacktraceMech
>       | HasCallStackBacktraceMech
>
>    And in the record, we have a field per mechanism, each wrapped in a
>    Maybe. Fortunately, there is an encoding that removes this
>    duplication. Let us index BacktraceMechanism by the representation
>    type of the backtrace:
>
>    data BacktraceMechanism a where
>      CostCentreBacktrace   :: BacktraceMechanism (Ptr CostCentreStack)
>      HasCallStackBacktrace :: BacktraceMechanism GHC.Stack.CallStack
>      ExecutionBacktrace    :: BacktraceMechanism [GHC.ExecutionStack.Location]
>      IPEBacktrace          :: BacktraceMechanism [StackEntry]
>
>    Now we can encode the set of enabled mechanisms as a function to Bool
>    and the record of collected backtraces as a function to Maybe a.
>    Something along the lines of:
>
>    type EnabledBacktraceMechanisms = forall a. BacktraceMechanism a -> Booltype Backtraces = forall a. BacktraceMechanism a -> Maybe a
>
>    This isn't as low-tech as a an enum and a record, and I realize that
>    low-tech solutions are appealing in their own way, but in this particular
>    case, I find that GADTs offer a more elegant encoding.
>    7.
>
>    *Hide the implicit parameter behind a synonym*. We choose to pass
>    around the exception context as an implicit parameter, but this should be
>    hidden from the end user. This is the way it's done with HasCallStack,
>    where documentation clearly states:
>
>    NOTE: The implicit parameter ?callStack :: CallStack is an
>    implementation
>    detail and *should not* be considered part of the CallStack API, we may
>    decide to change the implementation in the future.
>
>    Let's do the same and introduce a synonym for exception contexts:
>
>    type HasExceptionContext = (?exceptionContext :: ExceptionContext)
>
>    8.
>
>    *Preserve backtraces on rethrowing*. The way the proposal is currently
>    written, when an exception is caught and rethrown, its old backtrace is
>    dropped and a new one is constructed. This is very bad, because rethrowing
>    happens all the time (e.g. in bracket)! But it is not hard to fix:
>    catch should provide the context to the handler as an implicit
>    parameter, and throw should make use of it:
>
>    catch :: Exception e => IO a -> (HasExceptionContext => e -> IO a) -> IO athrowIO :: (HasExceptionContext, Exception e) => e -> IO a
>
>    What about uses of throwIO where HasExceptionContext has not been
>    provided by catch? Easy: default to an empty context. It shouldn't be
>    hard to add this special case to the solver, since HasCallStack has
>    already set a precedent.
>    9.
>
>    *Get rid of toExceptionWithContext*. The proposal introduces a new
>    method to Exception:
>
>    toException :: Exception e => e -> SomeException                                 -- oldtoExceptionWithContext :: Exception e => e -> ExceptionContext -> SomeException  -- new
>
>    But if we are passing the context as a constraint, then we could
>    simply add it to the original method:
>
>    toException :: (HasExceptionContext, Exception e) => e -> SomeException
>
>    There is no need for two methods this way.
>    10.
>
>    *Improvements to throwIONoBacktrace*. Currently the proposal defines
>    NoBacktrace variants of throw and throwIO:
>
>    throwNoBacktrace   :: forall e a. (Exception e) => e -> athrowIONoBacktrace :: forall e a. (Exception e) => e -> a
>
>    The idea is to allow users to opt out of backtraces for
>    non-exceptional control flow. But the problem is that this choice is not
>    recorded anywhere in the exception, so when the exception is caught and
>    rethrown, it will have unwanted backtraces added to it.
>
>    One solution is to add a Bool flag to ExceptionContext to record the
>    choice of not collecting the backtraces, so that they are not collected
>    when the exception is rethrown. In fact, we could avoid the duplication of
>    throw and throwIO this way:
>
>    backtracesEnabled :: HasExceptionContext => BoolenableBacktraces, disableBacktraces :: (HasExceptionContext => r) -> (HasExceptionContext => r)
>    throw :: (HasExceptionContext, Exception e) => e -> IO athrowIO :: (HasExceptionContext, Exception e) => e -> IO a
>
>    throw and throwIO can check for backtracesEnabled before calling
>    collectBacktraces. The users would write something along the lines of:
>
>    disableBacktraces $
>      throwIO MyControlFlowException
>
>    And the choice to disable backtraces would be carried along the
>    exception in its context.
>
> Hopefully, I have not missed anything. In the process of writing this
> review, I took a stab at rewriting the "Proposed Change Specification"
> section in accordance with all of the suggestions above, mainly to convince
> myself that the combination of those suggestions forms a coherent design.
> You can find it here:
> https://gist.github.com/int-index/750c6c292eb8266729adc61a5812a581. If
> you agree with my comments, feel free to incorporate the updated
> specification (or parts of it) into the proposal.
>
> Thank you!
>
>> Reply to this email directly, view it on GitHub
> <https://github.com/ghc-proposals/ghc-proposals/pull/330#issuecomment-1330446106>,
> or unsubscribe
> <https://github.com/notifications/unsubscribe-auth/AAEOY6ZVMSEXYJ6E3PRAMG3WKXOPHANCNFSM4M3U4KSA>
> .
> You are receiving this because you are subscribed to this thread.Message
> ID: <ghc-proposals/ghc-proposals/pull/330/c1330446106 at github.com>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-steering-committee/attachments/20221129/5696134c/attachment.html>


More information about the ghc-steering-committee mailing list