Safe Haskell | None |
---|
Utilities for notifying Airbrake of errors. An Error
type is
provided; you can convert any instance of Exception
to an Error
using toError
, which uses the exception's Typeable
instance.
Airbrake requires a stack trace for any reported exception, but stack
trace information isn't readily available for Haskell exceptions.
notifyQ
and notifyReqQ
are provided for the purpose of providing the
current file position as the stack trace.
- notify :: (MonadBaseControl IO m, MonadIO m, MonadThrow m) => AirbrakeConf -> Error -> Locations -> m ()
- notifyReq :: (MonadBaseControl IO m, MonadIO m, MonadThrow m, WebRequest req) => AirbrakeConf -> req -> Error -> Locations -> m ()
- notifyQ :: Q Exp
- notifyReqQ :: Q Exp
- data NonEmpty a = a :| [a]
- type Location = (FilePath, Int)
- type Locations = NonEmpty Location
- toError :: Exception e => e -> Error
- data Error = Error {}
- type APIKey = String
- type Environment = String
- airbrakeConf :: APIKey -> Environment -> AirbrakeConf
- defaultApiEndpoint :: String
- data AirbrakeConf = AirbrakeConf {}
- data Server = Server {}
- module Airbrake.Credentials
Notifying
notify :: (MonadBaseControl IO m, MonadIO m, MonadThrow m) => AirbrakeConf -> Error -> Locations -> m ()Source
Notify Airbrake of an exception.
notifyReq :: (MonadBaseControl IO m, MonadIO m, MonadThrow m, WebRequest req) => AirbrakeConf -> req -> Error -> Locations -> m ()Source
Notify Airbrake of an exception, providing request metadata along with it.
notify
, fetching the current file location using Template Haskell.
$notifyQ :: (MonadBaseControl
IO
m,MonadThrow
m,MonadIO
m) =>AirbrakeConf
->Error
-> m ()
notifyReqQ :: Q ExpSource
notifyReq
, fetching the current file location using Template
Haskell.
$notifyReqQ :: (MonadBaseControl
IO
m,MonadThrow
m,MonadIO
m,WebRequest
req) =>AirbrakeConf
-> req ->Error
-> m ()
Notification metadata
Location lists
data NonEmpty a
a :| [a] |
Monad NonEmpty | |
Functor NonEmpty | |
Typeable1 NonEmpty | |
Applicative NonEmpty | |
Foldable NonEmpty | |
Traversable NonEmpty | |
Eq a => Eq (NonEmpty a) | |
Data a => Data (NonEmpty a) | |
Ord a => Ord (NonEmpty a) | |
Read a => Read (NonEmpty a) | |
Show a => Show (NonEmpty a) | |
Generic (NonEmpty a) | |
Hashable a => Hashable (NonEmpty a) |
Wrapping errors
Configuration building
type Environment = StringSource
airbrakeConf :: APIKey -> Environment -> AirbrakeConfSource
Metadata about the server.
Convenience exports
module Airbrake.Credentials