rollbar-hs-0.3.1.0: Core Rollbar data types and APIs.

Copyright(c) Hardy Jones 2017
LicenseBSD3
Maintainerjones3.hardy@gmail.com
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Rollbar.Item

Contents

Description

Provides a data type that subsumes most of what Rollbar expects for "item"s.

See Rollbar's Data Format for more details.

Synopsis

Data helpers

These functions are probably what you want to use most of the time.

They create a Data with lots of data prefilled. You can then override what you need with record updates.

debug :: Environment -> Maybe MessageBody -> payload -> Data payload ("Authorization" ': headers) Source #

Creates Data with the level set to Debug.

info :: Environment -> Maybe MessageBody -> payload -> Data payload ("Authorization" ': headers) Source #

Creates Data with the level set to Info.

warning :: Environment -> Maybe MessageBody -> payload -> Data payload ("Authorization" ': headers) Source #

Creates Data with the level set to Warning.

error :: Environment -> Maybe MessageBody -> payload -> Data payload ("Authorization" ': headers) Source #

Creates Data with the level set to Error.

critical :: Environment -> Maybe MessageBody -> payload -> Data payload ("Authorization" ': headers) Source #

Creates Data with the level set to Critical.

Item

data Item a headers Source #

The thing we actually give to Rollbar.

Constructors

Item 

Fields

Instances
Eq a => Eq (Item a headers) Source # 
Instance details

Defined in Rollbar.Item

Methods

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

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

Show a => Show (Item a headers) Source # 
Instance details

Defined in Rollbar.Item

Methods

showsPrec :: Int -> Item a headers -> ShowS #

show :: Item a headers -> String #

showList :: [Item a headers] -> ShowS #

Generic (Item a headers) Source # 
Instance details

Defined in Rollbar.Item

Associated Types

type Rep (Item a headers) :: * -> * #

Methods

from :: Item a headers -> Rep (Item a headers) x #

to :: Rep (Item a headers) x -> Item a headers #

(RemoveHeaders headers, ToJSON a) => ToJSON (Item a headers) Source # 
Instance details

Defined in Rollbar.Item

Methods

toJSON :: Item a headers -> Value #

toEncoding :: Item a headers -> Encoding #

toJSONList :: [Item a headers] -> Value #

toEncodingList :: [Item a headers] -> Encoding #

FromJSON a => FromJSON (Item a headers) Source # 
Instance details

Defined in Rollbar.Item

Methods

parseJSON :: Value -> Parser (Item a headers) #

parseJSONList :: Value -> Parser [Item a headers] #

type Rep (Item a headers) Source # 
Instance details

Defined in Rollbar.Item

type Rep (Item a headers) = D1 (MetaData "Item" "Rollbar.Item" "rollbar-hs-0.3.1.0-AHXin9WUqD3IOtR3mTqHpy" False) (C1 (MetaCons "Item" PrefixI True) (S1 (MetaSel (Just "accessToken") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 AccessToken) :*: S1 (MetaSel (Just "itemData") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Data a headers))))

Item data

newtype AccessToken Source #

Should have the scope "post_server_item".

Constructors

AccessToken Text 

data Data body headers Source #

The main payload of an item. Most of this is metadata.

N.B. While it's entirely possible for you to create one of these yourself, it's usually easier to use helpers like info and error.

Constructors

Data 

Fields

Instances
Eq body => Eq (Data body headers) Source # 
Instance details

Defined in Rollbar.Item.Data

Methods

(==) :: Data body headers -> Data body headers -> Bool #

(/=) :: Data body headers -> Data body headers -> Bool #

Show body => Show (Data body headers) Source # 
Instance details

Defined in Rollbar.Item.Data

Methods

showsPrec :: Int -> Data body headers -> ShowS #

show :: Data body headers -> String #

showList :: [Data body headers] -> ShowS #

Generic (Data body headers) Source # 
Instance details

Defined in Rollbar.Item.Data

Associated Types

type Rep (Data body headers) :: * -> * #

Methods

from :: Data body headers -> Rep (Data body headers) x #

to :: Rep (Data body headers) x -> Data body headers #

(RemoveHeaders headers, ToJSON body) => ToJSON (Data body headers) Source # 
Instance details

Defined in Rollbar.Item.Data

Methods

toJSON :: Data body headers -> Value #

toEncoding :: Data body headers -> Encoding #

toJSONList :: [Data body headers] -> Value #

toEncodingList :: [Data body headers] -> Encoding #

FromJSON body => FromJSON (Data body headers) Source # 
Instance details

Defined in Rollbar.Item.Data

Methods

parseJSON :: Value -> Parser (Data body headers) #

parseJSONList :: Value -> Parser [Data body headers] #

type Rep (Data body headers) Source # 
Instance details

Defined in Rollbar.Item.Data

type Rep (Data body headers) = D1 (MetaData "Data" "Rollbar.Item.Data" "rollbar-hs-0.3.1.0-AHXin9WUqD3IOtR3mTqHpy" False) (C1 (MetaCons "Data" PrefixI True) ((((S1 (MetaSel (Just "body") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Body body)) :*: S1 (MetaSel (Just "codeVersion") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe CodeVersion))) :*: (S1 (MetaSel (Just "context") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Context)) :*: S1 (MetaSel (Just "custom") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (HashMap Text Value))))) :*: ((S1 (MetaSel (Just "environment") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Environment) :*: S1 (MetaSel (Just "fingerprint") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Fingerprint))) :*: (S1 (MetaSel (Just "framework") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Framework)) :*: S1 (MetaSel (Just "language") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Hardcoded "haskell"))))) :*: (((S1 (MetaSel (Just "level") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Level) :*: S1 (MetaSel (Just "notifier") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Notifier)) :*: (S1 (MetaSel (Just "person") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Person)) :*: S1 (MetaSel (Just "platform") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Platform))) :*: ((S1 (MetaSel (Just "request") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (Request headers))) :*: S1 (MetaSel (Just "server") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Server))) :*: (S1 (MetaSel (Just "timestamp") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe UTCTime)) :*: (S1 (MetaSel (Just "title") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Title)) :*: S1 (MetaSel (Just "uuid") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe UUID4))))))))

newtype Context Source #

The place in the code where this item came from.

Constructors

Context Text 
Instances
Eq Context Source # 
Instance details

Defined in Rollbar.Item.Data

Methods

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

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

Show Context Source # 
Instance details

Defined in Rollbar.Item.Data

IsString Context Source # 
Instance details

Defined in Rollbar.Item.Data

Methods

fromString :: String -> Context #

ToJSON Context Source # 
Instance details

Defined in Rollbar.Item.Data

FromJSON Context Source # 
Instance details

Defined in Rollbar.Item.Data

newtype Fingerprint Source #

How to group the item.

Constructors

Fingerprint Text 

newtype Framework Source #

The framework that is using this package. E.g. "scotty", "servant", "yesod"

Constructors

Framework Text 
Instances
Eq Framework Source # 
Instance details

Defined in Rollbar.Item.Data

Show Framework Source # 
Instance details

Defined in Rollbar.Item.Data

IsString Framework Source # 
Instance details

Defined in Rollbar.Item.Data

ToJSON Framework Source # 
Instance details

Defined in Rollbar.Item.Data

FromJSON Framework Source # 
Instance details

Defined in Rollbar.Item.Data

newtype Title Source #

The title of the item.

Constructors

Title Text 
Instances
Eq Title Source # 
Instance details

Defined in Rollbar.Item.Data

Methods

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

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

Show Title Source # 
Instance details

Defined in Rollbar.Item.Data

Methods

showsPrec :: Int -> Title -> ShowS #

show :: Title -> String #

showList :: [Title] -> ShowS #

IsString Title Source # 
Instance details

Defined in Rollbar.Item.Data

Methods

fromString :: String -> Title #

ToJSON Title Source # 
Instance details

Defined in Rollbar.Item.Data

FromJSON Title Source # 
Instance details

Defined in Rollbar.Item.Data

newtype UUID4 Source #

A unique identifier for each item.

Constructors

UUID4 UUID 
Instances
Eq UUID4 Source # 
Instance details

Defined in Rollbar.Item.Data

Methods

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

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

Show UUID4 Source # 
Instance details

Defined in Rollbar.Item.Data

Methods

showsPrec :: Int -> UUID4 -> ShowS #

show :: UUID4 -> String #

showList :: [UUID4] -> ShowS #

Generic UUID4 Source # 
Instance details

Defined in Rollbar.Item.Data

Associated Types

type Rep UUID4 :: * -> * #

Methods

from :: UUID4 -> Rep UUID4 x #

to :: Rep UUID4 x -> UUID4 #

ToJSON UUID4 Source # 
Instance details

Defined in Rollbar.Item.Data

FromJSON UUID4 Source # 
Instance details

Defined in Rollbar.Item.Data

type Rep UUID4 Source # 
Instance details

Defined in Rollbar.Item.Data

type Rep UUID4 = D1 (MetaData "UUID4" "Rollbar.Item.Data" "rollbar-hs-0.3.1.0-AHXin9WUqD3IOtR3mTqHpy" True) (C1 (MetaCons "UUID4" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 UUID)))

Required data

data Body arbitrary Source #

This is the actual data that you want to give to Rollbar. Most of the rest of Rollbar is metadata.

Constructors

Message

No stack trace, just a message and some arbitrary data.

Fields

Instances
Eq arbitrary => Eq (Body arbitrary) Source # 
Instance details

Defined in Rollbar.Item.Body

Methods

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

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

Show arbitrary => Show (Body arbitrary) Source # 
Instance details

Defined in Rollbar.Item.Body

Methods

showsPrec :: Int -> Body arbitrary -> ShowS #

show :: Body arbitrary -> String #

showList :: [Body arbitrary] -> ShowS #

Generic (Body arbitrary) Source # 
Instance details

Defined in Rollbar.Item.Body

Associated Types

type Rep (Body arbitrary) :: * -> * #

Methods

from :: Body arbitrary -> Rep (Body arbitrary) x #

to :: Rep (Body arbitrary) x -> Body arbitrary #

ToJSON arbitrary => ToJSON (Body arbitrary) Source # 
Instance details

Defined in Rollbar.Item.Body

Methods

toJSON :: Body arbitrary -> Value #

toEncoding :: Body arbitrary -> Encoding #

toJSONList :: [Body arbitrary] -> Value #

toEncodingList :: [Body arbitrary] -> Encoding #

FromJSON arbitrary => FromJSON (Body arbitrary) Source # 
Instance details

Defined in Rollbar.Item.Body

Methods

parseJSON :: Value -> Parser (Body arbitrary) #

parseJSONList :: Value -> Parser [Body arbitrary] #

type Rep (Body arbitrary) Source # 
Instance details

Defined in Rollbar.Item.Body

type Rep (Body arbitrary) = D1 (MetaData "Body" "Rollbar.Item.Body" "rollbar-hs-0.3.1.0-AHXin9WUqD3IOtR3mTqHpy" False) (C1 (MetaCons "Message" PrefixI True) (S1 (MetaSel (Just "messageBody") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 MessageBody) :*: S1 (MetaSel (Just "messageData") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 arbitrary)))

newtype MessageBody Source #

The primary message text to send to Rollbar.

Constructors

MessageBody Text 

newtype Environment Source #

Should be something meaningful to your program. E.g. "development", "production", "staging"

Constructors

Environment Text 

data Level Source #

Corresponds to the levels Rollbar allows in order of severity.

Constructors

Debug 
Info 
Warning 
Error 
Critical 
Instances
Bounded Level Source # 
Instance details

Defined in Rollbar.Item.Level

Enum Level Source # 
Instance details

Defined in Rollbar.Item.Level

Eq Level Source # 
Instance details

Defined in Rollbar.Item.Level

Methods

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

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

Ord Level Source # 
Instance details

Defined in Rollbar.Item.Level

Methods

compare :: Level -> Level -> Ordering #

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

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

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

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

max :: Level -> Level -> Level #

min :: Level -> Level -> Level #

Show Level Source # 
Instance details

Defined in Rollbar.Item.Level

Methods

showsPrec :: Int -> Level -> ShowS #

show :: Level -> String #

showList :: [Level] -> ShowS #

Generic Level Source # 
Instance details

Defined in Rollbar.Item.Level

Associated Types

type Rep Level :: * -> * #

Methods

from :: Level -> Rep Level x #

to :: Rep Level x -> Level #

ToJSON Level Source # 
Instance details

Defined in Rollbar.Item.Level

FromJSON Level Source # 
Instance details

Defined in Rollbar.Item.Level

type Rep Level Source # 
Instance details

Defined in Rollbar.Item.Level

type Rep Level = D1 (MetaData "Level" "Rollbar.Item.Level" "rollbar-hs-0.3.1.0-AHXin9WUqD3IOtR3mTqHpy" False) ((C1 (MetaCons "Debug" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Info" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "Warning" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "Error" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Critical" PrefixI False) (U1 :: * -> *))))

Optional data

data CodeVersion Source #

Rollbar supports different ways to say what version the code is.

Constructors

SemVer Text

Good ole SemVer. It's Text because who knows if you actually got it right...

Number Int

Plain integers.

SHA Text

Should be a Git SHA.

Instances
Eq CodeVersion Source # 
Instance details

Defined in Rollbar.Item.CodeVersion

Show CodeVersion Source # 
Instance details

Defined in Rollbar.Item.CodeVersion

Generic CodeVersion Source # 
Instance details

Defined in Rollbar.Item.CodeVersion

Associated Types

type Rep CodeVersion :: * -> * #

ToJSON CodeVersion Source # 
Instance details

Defined in Rollbar.Item.CodeVersion

FromJSON CodeVersion Source # 
Instance details

Defined in Rollbar.Item.CodeVersion

type Rep CodeVersion Source # 
Instance details

Defined in Rollbar.Item.CodeVersion

data Hardcoded (symbol :: Symbol) Source #

This is basically Proxy with the variable restricted to Symbol. It's mostly useful so a value can be insert into a JSON blob easily.

Constructors

Hardcoded 
Instances
Eq (Hardcoded symbol) Source # 
Instance details

Defined in Rollbar.Item.Hardcoded

Methods

(==) :: Hardcoded symbol -> Hardcoded symbol -> Bool #

(/=) :: Hardcoded symbol -> Hardcoded symbol -> Bool #

Show (Hardcoded symbol) Source # 
Instance details

Defined in Rollbar.Item.Hardcoded

Methods

showsPrec :: Int -> Hardcoded symbol -> ShowS #

show :: Hardcoded symbol -> String #

showList :: [Hardcoded symbol] -> ShowS #

Generic (Hardcoded symbol) Source # 
Instance details

Defined in Rollbar.Item.Hardcoded

Associated Types

type Rep (Hardcoded symbol) :: * -> * #

Methods

from :: Hardcoded symbol -> Rep (Hardcoded symbol) x #

to :: Rep (Hardcoded symbol) x -> Hardcoded symbol #

KnownSymbol symbol => ToJSON (Hardcoded symbol) Source # 
Instance details

Defined in Rollbar.Item.Hardcoded

Methods

toJSON :: Hardcoded symbol -> Value #

toEncoding :: Hardcoded symbol -> Encoding #

toJSONList :: [Hardcoded symbol] -> Value #

toEncodingList :: [Hardcoded symbol] -> Encoding #

KnownSymbol symbol => FromJSON (Hardcoded symbol) Source # 
Instance details

Defined in Rollbar.Item.Hardcoded

Methods

parseJSON :: Value -> Parser (Hardcoded symbol) #

parseJSONList :: Value -> Parser [Hardcoded symbol] #

type Rep (Hardcoded symbol) Source # 
Instance details

Defined in Rollbar.Item.Hardcoded

type Rep (Hardcoded symbol) = D1 (MetaData "Hardcoded" "Rollbar.Item.Hardcoded" "rollbar-hs-0.3.1.0-AHXin9WUqD3IOtR3mTqHpy" False) (C1 (MetaCons "Hardcoded" PrefixI False) (U1 :: * -> *))

newtype MissingHeaders (headers :: [Symbol]) Source #

The request headers with some missing

This is useful for removing sensitive information like the Authorization header.

Instances
Eq (MissingHeaders headers) Source # 
Instance details

Defined in Rollbar.Item.MissingHeaders

Methods

(==) :: MissingHeaders headers -> MissingHeaders headers -> Bool #

(/=) :: MissingHeaders headers -> MissingHeaders headers -> Bool #

Show (MissingHeaders headers) Source # 
Instance details

Defined in Rollbar.Item.MissingHeaders

Methods

showsPrec :: Int -> MissingHeaders headers -> ShowS #

show :: MissingHeaders headers -> String #

showList :: [MissingHeaders headers] -> ShowS #

RemoveHeaders headers => ToJSON (MissingHeaders headers) Source # 
Instance details

Defined in Rollbar.Item.MissingHeaders

FromJSON (MissingHeaders headers) Source # 
Instance details

Defined in Rollbar.Item.MissingHeaders

data Person Source #

The affected user.

The Email and Username associated with the latest Id will overwrite any previous.

Constructors

Person 
Instances
Eq Person Source # 
Instance details

Defined in Rollbar.Item.Person

Methods

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

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

Show Person Source # 
Instance details

Defined in Rollbar.Item.Person

Generic Person Source # 
Instance details

Defined in Rollbar.Item.Person

Associated Types

type Rep Person :: * -> * #

Methods

from :: Person -> Rep Person x #

to :: Rep Person x -> Person #

ToJSON Person Source # 
Instance details

Defined in Rollbar.Item.Person

FromJSON Person Source # 
Instance details

Defined in Rollbar.Item.Person

type Rep Person Source # 
Instance details

Defined in Rollbar.Item.Person

type Rep Person = D1 (MetaData "Person" "Rollbar.Item.Person" "rollbar-hs-0.3.1.0-AHXin9WUqD3IOtR3mTqHpy" False) (C1 (MetaCons "Person" PrefixI True) (S1 (MetaSel (Just "id") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Id) :*: (S1 (MetaSel (Just "username") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Username)) :*: S1 (MetaSel (Just "email") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Email)))))

newtype Email Source #

The user's email.

Constructors

Email Text 
Instances
Eq Email Source # 
Instance details

Defined in Rollbar.Item.Person

Methods

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

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

Show Email Source # 
Instance details

Defined in Rollbar.Item.Person

Methods

showsPrec :: Int -> Email -> ShowS #

show :: Email -> String #

showList :: [Email] -> ShowS #

IsString Email Source # 
Instance details

Defined in Rollbar.Item.Person

Methods

fromString :: String -> Email #

ToJSON Email Source # 
Instance details

Defined in Rollbar.Item.Person

FromJSON Email Source # 
Instance details

Defined in Rollbar.Item.Person

newtype Id Source #

The user's identifier. This uniquely identifies a Person to Rollbar.

Constructors

Id Text 
Instances
Eq Id Source # 
Instance details

Defined in Rollbar.Item.Person

Methods

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

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

Show Id Source # 
Instance details

Defined in Rollbar.Item.Person

Methods

showsPrec :: Int -> Id -> ShowS #

show :: Id -> String #

showList :: [Id] -> ShowS #

IsString Id Source # 
Instance details

Defined in Rollbar.Item.Person

Methods

fromString :: String -> Id #

ToJSON Id Source # 
Instance details

Defined in Rollbar.Item.Person

FromJSON Id Source # 
Instance details

Defined in Rollbar.Item.Person

newtype Username Source #

The user's name.

Constructors

Username Text 
Instances
Eq Username Source # 
Instance details

Defined in Rollbar.Item.Person

Show Username Source # 
Instance details

Defined in Rollbar.Item.Person

IsString Username Source # 
Instance details

Defined in Rollbar.Item.Person

ToJSON Username Source # 
Instance details

Defined in Rollbar.Item.Person

FromJSON Username Source # 
Instance details

Defined in Rollbar.Item.Person

newtype Get Source #

The query string parameters as a more useful data structure.

Constructors

Get Query 
Instances
Eq Get Source # 
Instance details

Defined in Rollbar.Item.Request

Methods

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

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

Show Get Source # 
Instance details

Defined in Rollbar.Item.Request

Methods

showsPrec :: Int -> Get -> ShowS #

show :: Get -> String #

showList :: [Get] -> ShowS #

Generic Get Source # 
Instance details

Defined in Rollbar.Item.Request

Associated Types

type Rep Get :: * -> * #

Methods

from :: Get -> Rep Get x #

to :: Rep Get x -> Get #

ToJSON Get Source # 
Instance details

Defined in Rollbar.Item.Request

FromJSON Get Source # 
Instance details

Defined in Rollbar.Item.Request

type Rep Get Source # 
Instance details

Defined in Rollbar.Item.Request

type Rep Get = D1 (MetaData "Get" "Rollbar.Item.Request" "rollbar-hs-0.3.1.0-AHXin9WUqD3IOtR3mTqHpy" True) (C1 (MetaCons "Get" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Query)))

newtype IP Source #

The IP address of the client.

Constructors

IP SockAddr 
Instances
Eq IP Source # 
Instance details

Defined in Rollbar.Item.Request

Methods

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

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

Show IP Source # 
Instance details

Defined in Rollbar.Item.Request

Methods

showsPrec :: Int -> IP -> ShowS #

show :: IP -> String #

showList :: [IP] -> ShowS #

Generic IP Source # 
Instance details

Defined in Rollbar.Item.Request

Associated Types

type Rep IP :: * -> * #

Methods

from :: IP -> Rep IP x #

to :: Rep IP x -> IP #

ToJSON IP Source # 
Instance details

Defined in Rollbar.Item.Request

FromJSON IP Source # 
Instance details

Defined in Rollbar.Item.Request

type Rep IP Source # 
Instance details

Defined in Rollbar.Item.Request

type Rep IP = D1 (MetaData "IP" "Rollbar.Item.Request" "rollbar-hs-0.3.1.0-AHXin9WUqD3IOtR3mTqHpy" True) (C1 (MetaCons "IP" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SockAddr)))

newtype Method Source #

The HTTP Verb

Constructors

Method ByteString 
Instances
Eq Method Source # 
Instance details

Defined in Rollbar.Item.Request

Methods

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

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

Show Method Source # 
Instance details

Defined in Rollbar.Item.Request

Generic Method Source # 
Instance details

Defined in Rollbar.Item.Request

Associated Types

type Rep Method :: * -> * #

Methods

from :: Method -> Rep Method x #

to :: Rep Method x -> Method #

ToJSON Method Source # 
Instance details

Defined in Rollbar.Item.Request

FromJSON Method Source # 
Instance details

Defined in Rollbar.Item.Request

type Rep Method Source # 
Instance details

Defined in Rollbar.Item.Request

type Rep Method = D1 (MetaData "Method" "Rollbar.Item.Request" "rollbar-hs-0.3.1.0-AHXin9WUqD3IOtR3mTqHpy" True) (C1 (MetaCons "Method" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ByteString)))

newtype MissingHeaders (headers :: [Symbol]) Source #

The request headers with some missing

This is useful for removing sensitive information like the Authorization header.

Instances
Eq (MissingHeaders headers) Source # 
Instance details

Defined in Rollbar.Item.MissingHeaders

Methods

(==) :: MissingHeaders headers -> MissingHeaders headers -> Bool #

(/=) :: MissingHeaders headers -> MissingHeaders headers -> Bool #

Show (MissingHeaders headers) Source # 
Instance details

Defined in Rollbar.Item.MissingHeaders

Methods

showsPrec :: Int -> MissingHeaders headers -> ShowS #

show :: MissingHeaders headers -> String #

showList :: [MissingHeaders headers] -> ShowS #

RemoveHeaders headers => ToJSON (MissingHeaders headers) Source # 
Instance details

Defined in Rollbar.Item.MissingHeaders

FromJSON (MissingHeaders headers) Source # 
Instance details

Defined in Rollbar.Item.MissingHeaders

newtype QueryString Source #

The raw querystring.

Constructors

QueryString ByteString 
Instances
Eq QueryString Source # 
Instance details

Defined in Rollbar.Item.Request

Show QueryString Source # 
Instance details

Defined in Rollbar.Item.Request

Generic QueryString Source # 
Instance details

Defined in Rollbar.Item.Request

Associated Types

type Rep QueryString :: * -> * #

ToJSON QueryString Source # 
Instance details

Defined in Rollbar.Item.Request

FromJSON QueryString Source # 
Instance details

Defined in Rollbar.Item.Request

type Rep QueryString Source # 
Instance details

Defined in Rollbar.Item.Request

type Rep QueryString = D1 (MetaData "QueryString" "Rollbar.Item.Request" "rollbar-hs-0.3.1.0-AHXin9WUqD3IOtR3mTqHpy" True) (C1 (MetaCons "QueryString" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ByteString)))

newtype RawBody Source #

The raw request body as a ByteString.

Constructors

RawBody ByteString 
Instances
Eq RawBody Source # 
Instance details

Defined in Rollbar.Item.Request

Methods

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

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

Show RawBody Source # 
Instance details

Defined in Rollbar.Item.Request

IsString RawBody Source # 
Instance details

Defined in Rollbar.Item.Request

Methods

fromString :: String -> RawBody #

Generic RawBody Source # 
Instance details

Defined in Rollbar.Item.Request

Associated Types

type Rep RawBody :: * -> * #

Methods

from :: RawBody -> Rep RawBody x #

to :: Rep RawBody x -> RawBody #

ToJSON RawBody Source # 
Instance details

Defined in Rollbar.Item.Request

FromJSON RawBody Source # 
Instance details

Defined in Rollbar.Item.Request

type Rep RawBody Source # 
Instance details

Defined in Rollbar.Item.Request

type Rep RawBody = D1 (MetaData "RawBody" "Rollbar.Item.Request" "rollbar-hs-0.3.1.0-AHXin9WUqD3IOtR3mTqHpy" True) (C1 (MetaCons "RawBody" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ByteString)))

newtype URL Source #

The URL as a slightly more useful structure.

Constructors

URL (Maybe ByteString, [Text]) 
Instances
Eq URL Source # 
Instance details

Defined in Rollbar.Item.Request

Methods

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

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

Show URL Source # 
Instance details

Defined in Rollbar.Item.Request

Methods

showsPrec :: Int -> URL -> ShowS #

show :: URL -> String #

showList :: [URL] -> ShowS #

Generic URL Source # 
Instance details

Defined in Rollbar.Item.Request

Associated Types

type Rep URL :: * -> * #

Methods

from :: URL -> Rep URL x #

to :: Rep URL x -> URL #

ToJSON URL Source # 
Instance details

Defined in Rollbar.Item.Request

FromJSON URL Source # 
Instance details

Defined in Rollbar.Item.Request

type Rep URL Source # 
Instance details

Defined in Rollbar.Item.Request

type Rep URL = D1 (MetaData "URL" "Rollbar.Item.Request" "rollbar-hs-0.3.1.0-AHXin9WUqD3IOtR3mTqHpy" True) (C1 (MetaCons "URL" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe ByteString, [Text]))))

data Server Source #

Information about the server using this package.

Constructors

Server 

Fields

Instances
Eq Server Source # 
Instance details

Defined in Rollbar.Item.Server

Methods

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

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

Show Server Source # 
Instance details

Defined in Rollbar.Item.Server

Generic Server Source # 
Instance details

Defined in Rollbar.Item.Server

Associated Types

type Rep Server :: * -> * #

Methods

from :: Server -> Rep Server x #

to :: Rep Server x -> Server #

ToJSON Server Source # 
Instance details

Defined in Rollbar.Item.Server

FromJSON Server Source # 
Instance details

Defined in Rollbar.Item.Server

type Rep Server Source # 
Instance details

Defined in Rollbar.Item.Server

newtype Branch Source #

The git branch the server is running on.

Constructors

Branch Text 
Instances
Eq Branch Source # 
Instance details

Defined in Rollbar.Item.Server

Methods

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

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

Show Branch Source # 
Instance details

Defined in Rollbar.Item.Server

IsString Branch Source # 
Instance details

Defined in Rollbar.Item.Server

Methods

fromString :: String -> Branch #

ToJSON Branch Source # 
Instance details

Defined in Rollbar.Item.Server

FromJSON Branch Source # 
Instance details

Defined in Rollbar.Item.Server

newtype Root Source #

The root directory.

Constructors

Root Text 
Instances
Eq Root Source # 
Instance details

Defined in Rollbar.Item.Server

Methods

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

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

Show Root Source # 
Instance details

Defined in Rollbar.Item.Server

Methods

showsPrec :: Int -> Root -> ShowS #

show :: Root -> String #

showList :: [Root] -> ShowS #

IsString Root Source # 
Instance details

Defined in Rollbar.Item.Server

Methods

fromString :: String -> Root #

ToJSON Root Source # 
Instance details

Defined in Rollbar.Item.Server

FromJSON Root Source # 
Instance details

Defined in Rollbar.Item.Server