wai-middleware-rollbar-0.4.0: Middleware that communicates to Rollbar.

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

Rollbar.Item.Request

Description

 

Synopsis

Documentation

data Request headers Source #

Data sent to the server

Constructors

Request 

Fields

Instances

Eq (Request headers) Source # 

Methods

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

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

Show (Request headers) Source # 

Methods

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

show :: Request headers -> String #

showList :: [Request headers] -> ShowS #

Generic (Request headers) Source # 

Associated Types

type Rep (Request headers) :: * -> * #

Methods

from :: Request headers -> Rep (Request headers) x #

to :: Rep (Request headers) x -> Request headers #

RemoveHeaders headers => ToJSON (Request headers) Source # 

Methods

toJSON :: Request headers -> Value #

toEncoding :: Request headers -> Encoding #

toJSONList :: [Request headers] -> Value #

toEncodingList :: [Request headers] -> Encoding #

FromJSON (Request headers) Source # 

Methods

parseJSON :: Value -> Parser (Request headers) #

parseJSONList :: Value -> Parser [Request headers] #

type Rep (Request headers) Source # 

newtype Get Source #

The query string parameters as a more useful data structure.

Constructors

Get Query 

Instances

Eq Get Source # 

Methods

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

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

Show Get Source # 

Methods

showsPrec :: Int -> Get -> ShowS #

show :: Get -> String #

showList :: [Get] -> ShowS #

Generic Get Source # 

Associated Types

type Rep Get :: * -> * #

Methods

from :: Get -> Rep Get x #

to :: Rep Get x -> Get #

ToJSON Get Source # 
FromJSON Get Source # 
type Rep Get Source # 
type Rep Get = D1 (MetaData "Get" "Rollbar.Item.Request" "wai-middleware-rollbar-0.4.0-KzJIUalteMh3Y0QheZBmq1" True) (C1 (MetaCons "Get" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Query)))

newtype IP Source #

The IP address of the client.

Constructors

IP SockAddr 

Instances

Eq IP Source # 

Methods

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

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

Show IP Source # 

Methods

showsPrec :: Int -> IP -> ShowS #

show :: IP -> String #

showList :: [IP] -> ShowS #

Generic IP Source # 

Associated Types

type Rep IP :: * -> * #

Methods

from :: IP -> Rep IP x #

to :: Rep IP x -> IP #

ToJSON IP Source # 
FromJSON IP Source # 
type Rep IP Source # 
type Rep IP = D1 (MetaData "IP" "Rollbar.Item.Request" "wai-middleware-rollbar-0.4.0-KzJIUalteMh3Y0QheZBmq1" True) (C1 (MetaCons "IP" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SockAddr)))

newtype Method Source #

The HTTP Verb

Constructors

Method ByteString 

Instances

Eq Method Source # 

Methods

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

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

Show Method Source # 
Generic Method Source # 

Associated Types

type Rep Method :: * -> * #

Methods

from :: Method -> Rep Method x #

to :: Rep Method x -> Method #

ToJSON Method Source # 
FromJSON Method Source # 
type Rep Method Source # 
type Rep Method = D1 (MetaData "Method" "Rollbar.Item.Request" "wai-middleware-rollbar-0.4.0-KzJIUalteMh3Y0QheZBmq1" True) (C1 (MetaCons "Method" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ByteString)))

newtype MissingHeaders headers Source #

The request headers with some missing

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

Instances

Eq (MissingHeaders headers) Source # 

Methods

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

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

Show (MissingHeaders headers) Source # 

Methods

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

show :: MissingHeaders headers -> String #

showList :: [MissingHeaders headers] -> ShowS #

RemoveHeaders headers => ToJSON (MissingHeaders headers) Source # 
FromJSON (MissingHeaders headers) Source # 

newtype RawBody Source #

The raw request body as a ByteString.

Constructors

RawBody ByteString 

Instances

Eq RawBody Source # 

Methods

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

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

Show RawBody Source # 
IsString RawBody Source # 

Methods

fromString :: String -> RawBody #

Generic RawBody Source # 

Associated Types

type Rep RawBody :: * -> * #

Methods

from :: RawBody -> Rep RawBody x #

to :: Rep RawBody x -> RawBody #

ToJSON RawBody Source # 
FromJSON RawBody Source # 
type Rep RawBody Source # 
type Rep RawBody = D1 (MetaData "RawBody" "Rollbar.Item.Request" "wai-middleware-rollbar-0.4.0-KzJIUalteMh3Y0QheZBmq1" True) (C1 (MetaCons "RawBody" PrefixI False) (S1 (MetaSel (Nothing 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 # 

Methods

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

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

Show URL Source # 

Methods

showsPrec :: Int -> URL -> ShowS #

show :: URL -> String #

showList :: [URL] -> ShowS #

Generic URL Source # 

Associated Types

type Rep URL :: * -> * #

Methods

from :: URL -> Rep URL x #

to :: Rep URL x -> URL #

ToJSON URL Source # 
FromJSON URL Source # 
type Rep URL Source # 
type Rep URL = D1 (MetaData "URL" "Rollbar.Item.Request" "wai-middleware-rollbar-0.4.0-KzJIUalteMh3Y0QheZBmq1" True) (C1 (MetaCons "URL" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe ByteString, [Text]))))

class RemoveHeaders headers Source #

Remove the headers given from the underlying request headers.

Minimal complete definition

removeHeaders

Instances

RemoveHeaders ([] Symbol) Source # 
(KnownSymbol header, RemoveHeaders headers) => RemoveHeaders ((:) Symbol header headers) Source # 

Methods

removeHeaders :: MissingHeaders ((Symbol ': header) headers) -> RequestHeaders