bugsnag-haskell-0.0.3.1: Bugsnag error reporter for Haskell

Safe HaskellNone
LanguageHaskell2010

Network.Bugsnag.BeforeNotify

Contents

Synopsis

Documentation

Modifying the Exception

updateException :: (BugsnagException -> BugsnagException) -> BeforeNotify Source #

Modify just the Exception part of an Event

This may be used to set more specific information for exception types in scope in your application:

notifyBugsnagWith (updateException forSqlError) settings ex

forSqlError :: BugsnagException -> BugsnagException
forSqlError ex =
    case fromException =<< beOriginalException ex of
        Just SqlError{..} -> ex
            { beErrorClass = "SqlError-" <> sqlErrorCode
            , beMessage = Just sqlErrorMessage
            }
        _ -> ex

updateStackFrames :: (BugsnagStackFrame -> BugsnagStackFrame) -> BeforeNotify Source #

Apply a function to each BugsnagStackFrame in the Exception

filterStackFrames :: (BugsnagStackFrame -> Bool) -> BeforeNotify Source #

Filter out StackFrames matching a predicate

setStackFramesCode :: CodeIndex -> BeforeNotify Source #

Set bsfCode using the given index

setStackFramesInProject :: (FilePath -> Bool) -> BeforeNotify Source #

Set bsIsInProject using the given predicate, applied to the Filename

Modifying the Event

updateEventFromException :: (BugsnagException -> BeforeNotify) -> BeforeNotify Source #

Update the BugsnagEvent based on its BugsnagException

Use this instead of updateException if you want to do other things to the Event, such as set its beGroupingHash based on the Exception.

updateEventFromOriginalException :: Exception e => (e -> BeforeNotify) -> BeforeNotify Source #

Update the BugsnagEvent based on the original exception

This allows updating the Event after casting to an exception type that this library doesn't know about (e.g. SqlError). Because the result of your function is itself a BeforeNotify, you can (and should) use other helpers:

myBeforeNotify =
    defaultBeforeNotify
        . updateEventFromOriginalException asSqlError
        . updateEventFromOriginalException asHttpError
        . -- ...

asSqlError :: SqlError -> BeforeNotify
asSqlError SqlError{..} =
    setGroupingHash sqlErrorCode . updateException $ ex -> ex
        { beErrorClass = sqlErrorCode
        , beMessage = sqlErrorMessage
        }

If there is no original exception, or the cast fails, the event is unchanged.

updateEventFromSession :: BugsnagSession -> BeforeNotify Source #

Update the Event's Context and User from the Session

updateEventFromWaiRequest :: Request -> BeforeNotify Source #

Set the events BugsnagEvent and BugsnagDevice

This function redacts the following Request headers:

  • Authorization
  • Cookie
  • X-XSRF-TOKEN (CSRF token header used by Yesod)

To avoid this, use updateEventFromWaiRequestUnredacted.

Modifying the Request

redactRequestHeaders :: [HeaderName] -> BeforeNotify Source #

Redact the given request headers

Headers like Authorization may contain information you don't want to report to Bugsnag.

redactRequestHeaders ["Authorization", "Cookie"]

Simple setters

setStacktrace :: [BugsnagStackFrame] -> BeforeNotify Source #

Set the stacktrace on the reported exception

notifyBugsnagWith (setStacktrace [$(currentStackFrame) "myFunc"]) ...

Setting severity