rollbar-client-0.1.0: Core library to communicate with Rollbar API.
Copyright(c) 2020 Stack Builders Inc.
LicenseMIT
MaintainerSebastián Estrella <sestrella@stackbuilders.com>
Safe HaskellNone
LanguageHaskell2010

Rollbar.Client

Description

 
Synopsis

Deploy

Requests

data Deploy Source #

Constructors

Deploy 

Fields

Instances

Instances details
Eq Deploy Source # 
Instance details

Defined in Rollbar.Client.Deploy

Methods

(==) :: Deploy -> Deploy -> Bool #

(/=) :: Deploy -> Deploy -> Bool #

Show Deploy Source # 
Instance details

Defined in Rollbar.Client.Deploy

ToJSON Deploy Source # 
Instance details

Defined in Rollbar.Client.Deploy

mkDeploy :: (HasSettings m, MonadIO m) => Revision -> m Deploy Source #

Builds a Deploy based on a Revision.

Example

getRevision >>= mkDeploy

data Status Source #

Status of the deployment.

Instances

Instances details
Eq Status Source # 
Instance details

Defined in Rollbar.Client.Deploy

Methods

(==) :: Status -> Status -> Bool #

(/=) :: Status -> Status -> Bool #

Show Status Source # 
Instance details

Defined in Rollbar.Client.Deploy

ToJSON Status Source # 
Instance details

Defined in Rollbar.Client.Deploy

Responses

Endpoints

reportDeploy :: (HasSettings m, MonadHttp m) => Deploy -> m DeployId Source #

Tracks a deploy in Rollbar.

Example

settings <- readSettings "rollbar.yaml"
runRollbar settings $ do
  deploy <- getRevision >>= mkDeploy
  reportDeploy deploy

Reference

https://explorer.docs.rollbar.com/#operation/post-deploy

Item

Requests

data Item Source #

Constructors

Item 

Fields

  • itemEnvironment :: Environment

    The name of the environment in which this occurrence was seen. A string up to 255 characters. For best results, use "production" or "prod" for your production environment. You don't need to configure anything in the Rollbar UI for new environment names; we'll detect them automatically.

  • itemBody :: Body

    The main data being sent. It can either be a message, an exception, or a crash report.

  • itemLevel :: Maybe Level

    The severity level. One of: "critical", "error", "warning", "info", "debug" Defaults to "error" for exceptions and "info" for messages. The level of the *first* occurrence of an item is used as the item's level. timestamp code_version

  • itemPlatform :: Maybe Text

    The platform on which this occurred. Meaningful platform names: "browser", "android", "ios", "flash", "client", "heroku", "google-app-engine" If this is a client-side event, be sure to specify the platform and use a post_client_item access token.

  • itemLanguage :: Maybe Text

    The name of the language your code is written in. This can affect the order of the frames in the stack trace. The following languages set the most recent call first - ruby, javascript, php, java, 'objective-c', lua It will also change the way the individual frames are displayed, with what is most consistent with users of the language.

  • itemFramework :: Maybe Text

    The name of the framework your code uses. context request

  • itemRequest :: Maybe Request

    Data about the request this event occurred in. person

  • itemServer :: Maybe Server

    Data about the server related to this event. client custom fingerprint title uuid

  • itemNotifier :: Notifier

    Describes the library used to send this event.

Instances

Instances details
Eq Item Source # 
Instance details

Defined in Rollbar.Client.Item

Methods

(==) :: Item -> Item -> Bool #

(/=) :: Item -> Item -> Bool #

Show Item Source # 
Instance details

Defined in Rollbar.Client.Item

Methods

showsPrec :: Int -> Item -> ShowS #

show :: Item -> String #

showList :: [Item] -> ShowS #

ToJSON Item Source # 
Instance details

Defined in Rollbar.Client.Item

mkItem :: (HasSettings m, MonadIO m) => Payload -> m Item Source #

Builds an Item based on a Payload.

newtype Body Source #

The main data being sent. It can either be a message, an exception, or a crash report.

Constructors

Body 

Fields

Instances

Instances details
Eq Body Source # 
Instance details

Defined in Rollbar.Client.Item

Methods

(==) :: Body -> Body -> Bool #

(/=) :: Body -> Body -> Bool #

Show Body Source # 
Instance details

Defined in Rollbar.Client.Item

Methods

showsPrec :: Int -> Body -> ShowS #

show :: Body -> String #

showList :: [Body] -> ShowS #

ToJSON Body Source # 
Instance details

Defined in Rollbar.Client.Item

data Payload Source #

Instances

Instances details
Eq Payload Source # 
Instance details

Defined in Rollbar.Client.Item

Methods

(==) :: Payload -> Payload -> Bool #

(/=) :: Payload -> Payload -> Bool #

Show Payload Source # 
Instance details

Defined in Rollbar.Client.Item

data Trace Source #

Constructors

Trace 

Fields

Instances

Instances details
Eq Trace Source # 
Instance details

Defined in Rollbar.Client.Item

Methods

(==) :: Trace -> Trace -> Bool #

(/=) :: Trace -> Trace -> Bool #

Show Trace Source # 
Instance details

Defined in Rollbar.Client.Item

Methods

showsPrec :: Int -> Trace -> ShowS #

show :: Trace -> String #

showList :: [Trace] -> ShowS #

ToJSON Trace Source # 
Instance details

Defined in Rollbar.Client.Item

data Frame Source #

Constructors

Frame 

Fields

Instances

Instances details
Eq Frame Source # 
Instance details

Defined in Rollbar.Client.Item

Methods

(==) :: Frame -> Frame -> Bool #

(/=) :: Frame -> Frame -> Bool #

Show Frame Source # 
Instance details

Defined in Rollbar.Client.Item

Methods

showsPrec :: Int -> Frame -> ShowS #

show :: Frame -> String #

showList :: [Frame] -> ShowS #

ToJSON Frame Source # 
Instance details

Defined in Rollbar.Client.Item

data Context Source #

Additional code before and after the "code" line.

Constructors

Context 

Fields

Instances

Instances details
Eq Context Source # 
Instance details

Defined in Rollbar.Client.Item

Methods

(==) :: Context -> Context -> Bool #

(/=) :: Context -> Context -> Bool #

Show Context Source # 
Instance details

Defined in Rollbar.Client.Item

ToJSON Context Source # 
Instance details

Defined in Rollbar.Client.Item

data Exception Source #

An object describing the exception instance.

Constructors

Exception 

Fields

Instances

Instances details
Eq Exception Source # 
Instance details

Defined in Rollbar.Client.Item

Show Exception Source # 
Instance details

Defined in Rollbar.Client.Item

ToJSON Exception Source # 
Instance details

Defined in Rollbar.Client.Item

data Message Source #

Constructors

Message 

Instances

Instances details
Eq Message Source # 
Instance details

Defined in Rollbar.Client.Item

Methods

(==) :: Message -> Message -> Bool #

(/=) :: Message -> Message -> Bool #

Show Message Source # 
Instance details

Defined in Rollbar.Client.Item

ToJSON Message Source # 
Instance details

Defined in Rollbar.Client.Item

data Level Source #

The severity level. One of: "critical", "error", "warning", "info", "debug" Defaults to "error" for exceptions and "info" for messages. The level of the *first* occurrence of an item is used as the item's level.

Instances

Instances details
Eq Level Source # 
Instance details

Defined in Rollbar.Client.Item

Methods

(==) :: Level -> Level -> Bool #

(/=) :: Level -> Level -> Bool #

Show Level Source # 
Instance details

Defined in Rollbar.Client.Item

Methods

showsPrec :: Int -> Level -> ShowS #

show :: Level -> String #

showList :: [Level] -> ShowS #

ToJSON Level Source # 
Instance details

Defined in Rollbar.Client.Item

mkLevel :: Payload -> Level Source #

Builds a Level based on a Payload.

data Request Source #

Data about the request this event occurred in.

Constructors

Request 

Fields

Instances

Instances details
Eq Request Source # 
Instance details

Defined in Rollbar.Client.Item

Methods

(==) :: Request -> Request -> Bool #

(/=) :: Request -> Request -> Bool #

Show Request Source # 
Instance details

Defined in Rollbar.Client.Item

ToJSON Request Source # 
Instance details

Defined in Rollbar.Client.Item

getRequestModifier :: (HasSettings m, Monad m) => m (Request -> Request) Source #

Pulls RequestModifiers out of Settings and build a list of 'Endo Request' which are folded as a single request modifier function.

data Server Source #

Data about the server related to this event.

Constructors

Server 

Fields

Instances

Instances details
Eq Server Source # 
Instance details

Defined in Rollbar.Client.Item

Methods

(==) :: Server -> Server -> Bool #

(/=) :: Server -> Server -> Bool #

Show Server Source # 
Instance details

Defined in Rollbar.Client.Item

ToJSON Server Source # 
Instance details

Defined in Rollbar.Client.Item

data Notifier Source #

Constructors

Notifier 

Instances

Instances details
Eq Notifier Source # 
Instance details

Defined in Rollbar.Client.Item

Show Notifier Source # 
Instance details

Defined in Rollbar.Client.Item

ToJSON Notifier Source # 
Instance details

Defined in Rollbar.Client.Item

defaultNotifier :: Notifier Source #

Returns information about this package such as the name and version.

Responses

newtype ItemId Source #

Constructors

ItemId Text 

Instances

Instances details
Eq ItemId Source # 
Instance details

Defined in Rollbar.Client.Item

Methods

(==) :: ItemId -> ItemId -> Bool #

(/=) :: ItemId -> ItemId -> Bool #

Show ItemId Source # 
Instance details

Defined in Rollbar.Client.Item

FromJSON ItemId Source # 
Instance details

Defined in Rollbar.Client.Item

Endpoints

createItem :: (HasSettings m, MonadHttp m) => Item -> m ItemId Source #

Reports an occurrence (exception or message) to Rollbar.

Example

settings <- readSettings "rollbar.yaml"
runRollbar settings $ do
  item <- mkItem $ PayloadTrace $ Trace [] $ Exception
    { exceptionClass = "NameError"
    , exceptionMessage = Just "global name 'foo' is not defined"
    , exceptionDescription = Just "Something went wrong while trying to save the user object"
    }
  createItem item

Reference

https://explorer.docs.rollbar.com/#operation/create-item

Ping

Requests

data Pong Source #

Constructors

Pong 

Instances

Instances details
Eq Pong Source # 
Instance details

Defined in Rollbar.Client.Ping

Methods

(==) :: Pong -> Pong -> Bool #

(/=) :: Pong -> Pong -> Bool #

Show Pong Source # 
Instance details

Defined in Rollbar.Client.Ping

Methods

showsPrec :: Int -> Pong -> ShowS #

show :: Pong -> String #

showList :: [Pong] -> ShowS #

Endpoints

ping :: MonadHttp m => m Pong Source #

Pings Rollbar API server, on success returns Pong.

Example

settings <- readSettings "rollbar.yaml"
runRollbar settings ping

Reference

https://explorer.docs.rollbar.com/#section/Ping

Settings

class HasSettings m where Source #

Typeclass used to pull Rollbar Settings out of a given Monad.

Instances

Instances details
HasSettings Rollbar Source # 
Instance details

Defined in Rollbar.Client

data Settings Source #

General settings required to interact with Rollbar API.

Constructors

Settings 

Fields

Instances

Instances details
Eq Settings Source # 
Instance details

Defined in Rollbar.Client.Settings

Show Settings Source # 
Instance details

Defined in Rollbar.Client.Settings

FromJSON Settings Source # 
Instance details

Defined in Rollbar.Client.Settings

readSettings :: MonadIO m => FilePath -> m Settings Source #

Reads Settings from a YAML file.

newtype Token Source #

Constructors

Token ByteString 

Instances

Instances details
Eq Token Source # 
Instance details

Defined in Rollbar.Client.Settings

Methods

(==) :: Token -> Token -> Bool #

(/=) :: Token -> Token -> Bool #

Show Token Source # 
Instance details

Defined in Rollbar.Client.Settings

Methods

showsPrec :: Int -> Token -> ShowS #

show :: Token -> String #

showList :: [Token] -> ShowS #

FromJSON Token Source # 
Instance details

Defined in Rollbar.Client.Settings

newtype Environment Source #

Environment to which the revision was deployed.

Constructors

Environment Text 

newtype Revision Source #

Git SHA of revision being deployed.

Constructors

Revision Text 

Instances

Instances details
Eq Revision Source # 
Instance details

Defined in Rollbar.Client.Settings

Show Revision Source # 
Instance details

Defined in Rollbar.Client.Settings

ToJSON Revision Source # 
Instance details

Defined in Rollbar.Client.Settings

FromJSON Revision Source # 
Instance details

Defined in Rollbar.Client.Settings

getRevision :: (HasSettings m, MonadIO m) => m Revision Source #

Similar to getRevisionMaybe, but it throws a RevisionNotFound if the Revision is not found.

getRevisionMaybe :: (HasSettings m, MonadIO m) => m (Maybe Revision) Source #

Gets the Revision from Settings (if the value is present), otherwise gets the Revision from git (if the executable is present) directly by running the following command git rev-parse HEAD, if none of them are present (neither the value nor the executable) returns Nothing.

data RequestModifiers Source #

Represents a list of Request modifiers that are combined by getRequestModifier into a single function.

Constructors

RequestModifiers 

Fields

defaultRequestModifiers :: RequestModifiers Source #

Returns an empty RequestModifiers, the function produced by getRequestModifier given this values is equivalent to id.

newtype Rollbar a Source #

Constructors

Rollbar (ReaderT Settings Req a) 

Instances

Instances details
Monad Rollbar Source # 
Instance details

Defined in Rollbar.Client

Methods

(>>=) :: Rollbar a -> (a -> Rollbar b) -> Rollbar b #

(>>) :: Rollbar a -> Rollbar b -> Rollbar b #

return :: a -> Rollbar a #

Functor Rollbar Source # 
Instance details

Defined in Rollbar.Client

Methods

fmap :: (a -> b) -> Rollbar a -> Rollbar b #

(<$) :: a -> Rollbar b -> Rollbar a #

Applicative Rollbar Source # 
Instance details

Defined in Rollbar.Client

Methods

pure :: a -> Rollbar a #

(<*>) :: Rollbar (a -> b) -> Rollbar a -> Rollbar b #

liftA2 :: (a -> b -> c) -> Rollbar a -> Rollbar b -> Rollbar c #

(*>) :: Rollbar a -> Rollbar b -> Rollbar b #

(<*) :: Rollbar a -> Rollbar b -> Rollbar a #

MonadIO Rollbar Source # 
Instance details

Defined in Rollbar.Client

Methods

liftIO :: IO a -> Rollbar a #

MonadHttp Rollbar Source # 
Instance details

Defined in Rollbar.Client

HasSettings Rollbar Source # 
Instance details

Defined in Rollbar.Client

withRollbar :: (MonadCatch m, MonadIO m) => Settings -> m a -> m a Source #

Runs a computation, captures any SomeException threw, and send it to Rollbar.

runRollbar :: MonadIO m => Settings -> Rollbar a -> m a Source #

Run a computation in Rollbar monad.