{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
module Rollbar.Client.Item
(
Item(..)
, mkItem
, Body(..)
, Payload(..)
, Trace(..)
, Frame(..)
, Context(..)
, Exception(..)
, mkException
, Message(..)
, Level(..)
, mkLevel
, Request(..)
, getRequestModifier
, Server(..)
, Notifier(..)
, defaultNotifier
, ItemId(..)
, createItem
) where
import qualified Control.Exception as E
import qualified Data.Aeson.KeyMap as KM
import qualified Data.Aeson.Key as K
import qualified Data.Text as T
import Control.Monad.IO.Class (MonadIO(..))
import Data.Aeson
import Data.Maybe (catMaybes)
import Data.Monoid (Endo(..))
import Data.Text (Text)
import Network.HTTP.Req
import Rollbar.Client.Internal
import Rollbar.Client.Settings
import System.Directory (getCurrentDirectory)
import System.Info (arch, os)
data Item = Item
{ Item -> Environment
itemEnvironment :: Environment
, Item -> Body
itemBody :: Body
, Item -> Maybe Level
itemLevel :: Maybe Level
, Item -> Maybe Text
itemPlatform :: Maybe Text
, Item -> Maybe Text
itemLanguage :: Maybe Text
, Item -> Maybe Text
itemFramework :: Maybe Text
, Item -> Maybe Request
itemRequest :: Maybe Request
, Item -> Maybe Server
itemServer :: Maybe Server
, Item -> Maybe Object
custom :: Maybe Object
, Item -> Maybe Text
title :: Maybe Text
, Item -> Maybe Text
uuid :: Maybe Text
, Item -> Maybe Text
fingerprint :: Maybe Text
, Item -> Notifier
itemNotifier :: Notifier
} deriving (Item -> Item -> Bool
(Item -> Item -> Bool) -> (Item -> Item -> Bool) -> Eq Item
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Item -> Item -> Bool
== :: Item -> Item -> Bool
$c/= :: Item -> Item -> Bool
/= :: Item -> Item -> Bool
Eq, Int -> Item -> ShowS
[Item] -> ShowS
Item -> String
(Int -> Item -> ShowS)
-> (Item -> String) -> ([Item] -> ShowS) -> Show Item
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Item -> ShowS
showsPrec :: Int -> Item -> ShowS
$cshow :: Item -> String
show :: Item -> String
$cshowList :: [Item] -> ShowS
showList :: [Item] -> ShowS
Show)
instance ToJSON Item where
toJSON :: Item -> Value
toJSON Item{Maybe Object
Maybe Text
Maybe Server
Maybe Request
Maybe Level
Environment
Notifier
Body
itemEnvironment :: Item -> Environment
itemBody :: Item -> Body
itemLevel :: Item -> Maybe Level
itemPlatform :: Item -> Maybe Text
itemLanguage :: Item -> Maybe Text
itemFramework :: Item -> Maybe Text
itemRequest :: Item -> Maybe Request
itemServer :: Item -> Maybe Server
custom :: Item -> Maybe Object
title :: Item -> Maybe Text
uuid :: Item -> Maybe Text
fingerprint :: Item -> Maybe Text
itemNotifier :: Item -> Notifier
itemEnvironment :: Environment
itemBody :: Body
itemLevel :: Maybe Level
itemPlatform :: Maybe Text
itemLanguage :: Maybe Text
itemFramework :: Maybe Text
itemRequest :: Maybe Request
itemServer :: Maybe Server
custom :: Maybe Object
title :: Maybe Text
uuid :: Maybe Text
fingerprint :: Maybe Text
itemNotifier :: Notifier
..} =
let dataFields :: [Pair]
dataFields =
[ Key
"environment" Key -> Environment -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Environment
itemEnvironment
, Key
"body" Key -> Body -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Body
itemBody
, Key
"level" Key -> Maybe Level -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Maybe Level
itemLevel
, Key
"platform" Key -> Maybe Text -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Maybe Text
itemPlatform
, Key
"language" Key -> Maybe Text -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Maybe Text
itemLanguage
, Key
"framework" Key -> Maybe Text -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Maybe Text
itemFramework
, Key
"request" Key -> Maybe Request -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Maybe Request
itemRequest
, Key
"server" Key -> Maybe Server -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Maybe Server
itemServer
, Key
"notifier" Key -> Notifier -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Notifier
itemNotifier
] [Pair] -> [Pair] -> [Pair]
forall a. [a] -> [a] -> [a]
++ [Maybe Pair] -> [Pair]
forall a. [Maybe a] -> [a]
catMaybes
[ (Key
"custom" Key -> Object -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.=) (Object -> Pair) -> Maybe Object -> Maybe Pair
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Object
custom
, (Key
"fingerprint" Key -> Text -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.=) (Text -> Pair) -> Maybe Text -> Maybe Pair
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Text
fingerprint
, (Key
"title" Key -> Text -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.=) (Text -> Pair) -> Maybe Text -> Maybe Pair
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Text
title
, (Key
"uuid" Key -> Text -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.=) (Text -> Pair) -> Maybe Text -> Maybe Pair
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Text
uuid
]
in
[Pair] -> Value
object [ Key
"data" Key -> Value -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= [Pair] -> Value
object [Pair]
dataFields ]
mkItem
:: (HasSettings m, MonadIO m)
=> Payload
-> m Item
mkItem :: forall (m :: * -> *).
(HasSettings m, MonadIO m) =>
Payload -> m Item
mkItem Payload
payload = do
Environment
environment <- Settings -> Environment
settingsEnvironment (Settings -> Environment) -> m Settings -> m Environment
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> m Settings
forall (m :: * -> *). HasSettings m => m Settings
getSettings
String
root <- IO String -> m String
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO String
getCurrentDirectory
Item -> m Item
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return Item
{ itemEnvironment :: Environment
itemEnvironment = Environment
environment
, itemBody :: Body
itemBody = Body
{ bodyPayload :: Payload
bodyPayload = Payload
payload
}
, itemLevel :: Maybe Level
itemLevel = Level -> Maybe Level
forall a. a -> Maybe a
Just (Level -> Maybe Level) -> Level -> Maybe Level
forall a b. (a -> b) -> a -> b
$ Payload -> Level
mkLevel Payload
payload
, itemPlatform :: Maybe Text
itemPlatform = Text -> Maybe Text
forall a. a -> Maybe a
Just (Text -> Maybe Text) -> Text -> Maybe Text
forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack String
os
, itemLanguage :: Maybe Text
itemLanguage = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"haskell"
, itemFramework :: Maybe Text
itemFramework = Maybe Text
forall a. Maybe a
Nothing
, itemRequest :: Maybe Request
itemRequest = Maybe Request
forall a. Maybe a
Nothing
, itemServer :: Maybe Server
itemServer = Server -> Maybe Server
forall a. a -> Maybe a
Just Server
{ serverCpu :: Maybe Text
serverCpu = Text -> Maybe Text
forall a. a -> Maybe a
Just (Text -> Maybe Text) -> Text -> Maybe Text
forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack String
arch
, serverHost :: Maybe Text
serverHost = Maybe Text
forall a. Maybe a
Nothing
, serverRoot :: Maybe Text
serverRoot = Text -> Maybe Text
forall a. a -> Maybe a
Just (Text -> Maybe Text) -> Text -> Maybe Text
forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack String
root
, serverBranch :: Maybe Text
serverBranch = Maybe Text
forall a. Maybe a
Nothing
, serverCodeVersion :: Maybe Text
serverCodeVersion = Maybe Text
forall a. Maybe a
Nothing
}
, itemNotifier :: Notifier
itemNotifier = Notifier
defaultNotifier
, custom :: Maybe Object
custom = Maybe Object
forall a. Maybe a
Nothing
, title :: Maybe Text
title = Maybe Text
forall a. Maybe a
Nothing
, uuid :: Maybe Text
uuid = Maybe Text
forall a. Maybe a
Nothing
, fingerprint :: Maybe Text
fingerprint = Maybe Text
forall a. Maybe a
Nothing
}
newtype Body = Body { Body -> Payload
bodyPayload :: Payload }
deriving (Body -> Body -> Bool
(Body -> Body -> Bool) -> (Body -> Body -> Bool) -> Eq Body
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Body -> Body -> Bool
== :: Body -> Body -> Bool
$c/= :: Body -> Body -> Bool
/= :: Body -> Body -> Bool
Eq, Int -> Body -> ShowS
[Body] -> ShowS
Body -> String
(Int -> Body -> ShowS)
-> (Body -> String) -> ([Body] -> ShowS) -> Show Body
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Body -> ShowS
showsPrec :: Int -> Body -> ShowS
$cshow :: Body -> String
show :: Body -> String
$cshowList :: [Body] -> ShowS
showList :: [Body] -> ShowS
Show)
instance ToJSON Body where
toJSON :: Body -> Value
toJSON Body{Payload
bodyPayload :: Body -> Payload
bodyPayload :: Payload
..} = [Pair] -> Value
object
[ case Payload
bodyPayload of
(PayloadTrace Trace
trace) -> (Key
"trace", Trace -> Value
forall a. ToJSON a => a -> Value
toJSON Trace
trace)
(PayloadTraceChain [Trace]
traceChain) -> (Key
"trace_chain", [Trace] -> Value
forall a. ToJSON a => a -> Value
toJSON [Trace]
traceChain)
(PayloadMessage Message
message) -> (Key
"message", Message -> Value
forall a. ToJSON a => a -> Value
toJSON Message
message)
]
data Payload
= PayloadTrace Trace
| PayloadTraceChain [Trace]
| PayloadMessage Message
deriving (Payload -> Payload -> Bool
(Payload -> Payload -> Bool)
-> (Payload -> Payload -> Bool) -> Eq Payload
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Payload -> Payload -> Bool
== :: Payload -> Payload -> Bool
$c/= :: Payload -> Payload -> Bool
/= :: Payload -> Payload -> Bool
Eq, Int -> Payload -> ShowS
[Payload] -> ShowS
Payload -> String
(Int -> Payload -> ShowS)
-> (Payload -> String) -> ([Payload] -> ShowS) -> Show Payload
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Payload -> ShowS
showsPrec :: Int -> Payload -> ShowS
$cshow :: Payload -> String
show :: Payload -> String
$cshowList :: [Payload] -> ShowS
showList :: [Payload] -> ShowS
Show)
data Trace = Trace
{ Trace -> [Frame]
traceFrames :: [Frame]
, Trace -> Exception
traceException :: Exception
} deriving (Trace -> Trace -> Bool
(Trace -> Trace -> Bool) -> (Trace -> Trace -> Bool) -> Eq Trace
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Trace -> Trace -> Bool
== :: Trace -> Trace -> Bool
$c/= :: Trace -> Trace -> Bool
/= :: Trace -> Trace -> Bool
Eq, Int -> Trace -> ShowS
[Trace] -> ShowS
Trace -> String
(Int -> Trace -> ShowS)
-> (Trace -> String) -> ([Trace] -> ShowS) -> Show Trace
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Trace -> ShowS
showsPrec :: Int -> Trace -> ShowS
$cshow :: Trace -> String
show :: Trace -> String
$cshowList :: [Trace] -> ShowS
showList :: [Trace] -> ShowS
Show)
instance ToJSON Trace where
toJSON :: Trace -> Value
toJSON Trace{[Frame]
Exception
traceFrames :: Trace -> [Frame]
traceException :: Trace -> Exception
traceFrames :: [Frame]
traceException :: Exception
..} = [Pair] -> Value
object
[ Key
"frames" Key -> [Frame] -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= [Frame]
traceFrames
, Key
"exception" Key -> Exception -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Exception
traceException
]
data Frame = Frame
{ Frame -> Text
frameFilename :: Text
, Frame -> Maybe Integer
frameLineno :: Maybe Integer
, Frame -> Maybe Integer
frameColno :: Maybe Integer
, Frame -> Maybe Text
frameMethod :: Maybe Text
, Frame -> Maybe Text
frameCode :: Maybe Text
, Frame -> Maybe Text
frameClassName :: Maybe Text
, Frame -> Maybe Context
frameContext :: Maybe Context
} deriving (Frame -> Frame -> Bool
(Frame -> Frame -> Bool) -> (Frame -> Frame -> Bool) -> Eq Frame
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Frame -> Frame -> Bool
== :: Frame -> Frame -> Bool
$c/= :: Frame -> Frame -> Bool
/= :: Frame -> Frame -> Bool
Eq, Int -> Frame -> ShowS
[Frame] -> ShowS
Frame -> String
(Int -> Frame -> ShowS)
-> (Frame -> String) -> ([Frame] -> ShowS) -> Show Frame
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Frame -> ShowS
showsPrec :: Int -> Frame -> ShowS
$cshow :: Frame -> String
show :: Frame -> String
$cshowList :: [Frame] -> ShowS
showList :: [Frame] -> ShowS
Show)
instance ToJSON Frame where
toJSON :: Frame -> Value
toJSON Frame{Maybe Integer
Maybe Text
Maybe Context
Text
frameFilename :: Frame -> Text
frameLineno :: Frame -> Maybe Integer
frameColno :: Frame -> Maybe Integer
frameMethod :: Frame -> Maybe Text
frameCode :: Frame -> Maybe Text
frameClassName :: Frame -> Maybe Text
frameContext :: Frame -> Maybe Context
frameFilename :: Text
frameLineno :: Maybe Integer
frameColno :: Maybe Integer
frameMethod :: Maybe Text
frameCode :: Maybe Text
frameClassName :: Maybe Text
frameContext :: Maybe Context
..} = [Pair] -> Value
object
[ Key
"filename" Key -> Text -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Text
frameFilename
, Key
"lineno" Key -> Maybe Integer -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Maybe Integer
frameLineno
, Key
"colno" Key -> Maybe Integer -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Maybe Integer
frameColno
, Key
"method" Key -> Maybe Text -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Maybe Text
frameMethod
, Key
"code" Key -> Maybe Text -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Maybe Text
frameCode
, Key
"class_name" Key -> Maybe Text -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Maybe Text
frameClassName
, Key
"context" Key -> Maybe Context -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Maybe Context
frameContext
]
data Context = Context
{ Context -> [Text]
contextPre :: [Text]
, Context -> [Text]
contextPost :: [Text]
} deriving (Context -> Context -> Bool
(Context -> Context -> Bool)
-> (Context -> Context -> Bool) -> Eq Context
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Context -> Context -> Bool
== :: Context -> Context -> Bool
$c/= :: Context -> Context -> Bool
/= :: Context -> Context -> Bool
Eq, Int -> Context -> ShowS
[Context] -> ShowS
Context -> String
(Int -> Context -> ShowS)
-> (Context -> String) -> ([Context] -> ShowS) -> Show Context
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Context -> ShowS
showsPrec :: Int -> Context -> ShowS
$cshow :: Context -> String
show :: Context -> String
$cshowList :: [Context] -> ShowS
showList :: [Context] -> ShowS
Show)
instance ToJSON Context where
toJSON :: Context -> Value
toJSON Context{[Text]
contextPre :: Context -> [Text]
contextPost :: Context -> [Text]
contextPre :: [Text]
contextPost :: [Text]
..} = [Pair] -> Value
object
[ Key
"pre" Key -> [Text] -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= [Text]
contextPre
, Key
"post" Key -> [Text] -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= [Text]
contextPost
]
data Exception = Exception
{ Exception -> Text
exceptionClass :: Text
, Exception -> Maybe Text
exceptionMessage :: Maybe Text
, Exception -> Maybe Text
exceptionDescription :: Maybe Text
} deriving (Exception -> Exception -> Bool
(Exception -> Exception -> Bool)
-> (Exception -> Exception -> Bool) -> Eq Exception
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Exception -> Exception -> Bool
== :: Exception -> Exception -> Bool
$c/= :: Exception -> Exception -> Bool
/= :: Exception -> Exception -> Bool
Eq, Int -> Exception -> ShowS
[Exception] -> ShowS
Exception -> String
(Int -> Exception -> ShowS)
-> (Exception -> String)
-> ([Exception] -> ShowS)
-> Show Exception
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Exception -> ShowS
showsPrec :: Int -> Exception -> ShowS
$cshow :: Exception -> String
show :: Exception -> String
$cshowList :: [Exception] -> ShowS
showList :: [Exception] -> ShowS
Show)
instance ToJSON Exception where
toJSON :: Exception -> Value
toJSON Exception{Maybe Text
Text
exceptionClass :: Exception -> Text
exceptionMessage :: Exception -> Maybe Text
exceptionDescription :: Exception -> Maybe Text
exceptionClass :: Text
exceptionMessage :: Maybe Text
exceptionDescription :: Maybe Text
..} = [Pair] -> Value
object
[ Key
"class" Key -> Text -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Text
exceptionClass
, Key
"message" Key -> Maybe Text -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Maybe Text
exceptionMessage
, Key
"description" Key -> Maybe Text -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Maybe Text
exceptionDescription
]
mkException :: E.Exception e => e -> Exception
mkException :: forall e. Exception e => e -> Exception
mkException e
e = Exception
{ exceptionClass :: Text
exceptionClass = String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ e -> String
forall e. Exception e => e -> String
E.displayException e
e
, exceptionMessage :: Maybe Text
exceptionMessage = Maybe Text
forall a. Maybe a
Nothing
, exceptionDescription :: Maybe Text
exceptionDescription = Maybe Text
forall a. Maybe a
Nothing
}
data Message = Message
{ Message -> Text
messageBody :: Text
, Message -> Object
messageMetadata :: Object
} deriving (Message -> Message -> Bool
(Message -> Message -> Bool)
-> (Message -> Message -> Bool) -> Eq Message
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Message -> Message -> Bool
== :: Message -> Message -> Bool
$c/= :: Message -> Message -> Bool
/= :: Message -> Message -> Bool
Eq, Int -> Message -> ShowS
[Message] -> ShowS
Message -> String
(Int -> Message -> ShowS)
-> (Message -> String) -> ([Message] -> ShowS) -> Show Message
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Message -> ShowS
showsPrec :: Int -> Message -> ShowS
$cshow :: Message -> String
show :: Message -> String
$cshowList :: [Message] -> ShowS
showList :: [Message] -> ShowS
Show)
instance ToJSON Message where
toJSON :: Message -> Value
toJSON Message{Object
Text
messageBody :: Message -> Text
messageMetadata :: Message -> Object
messageBody :: Text
messageMetadata :: Object
..} = Object -> Value
Object (Object -> Value) -> Object -> Value
forall a b. (a -> b) -> a -> b
$
Key -> Value -> Object -> Object
forall v. Key -> v -> KeyMap v -> KeyMap v
KM.insert Key
"body" (Text -> Value
forall a. ToJSON a => a -> Value
toJSON Text
messageBody) Object
messageMetadata
data Level
= LevelCritical
| LevelError
| LevelWarning
| LevelInfo
| LevelDebug
deriving (Level -> Level -> Bool
(Level -> Level -> Bool) -> (Level -> Level -> Bool) -> Eq Level
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Level -> Level -> Bool
== :: Level -> Level -> Bool
$c/= :: Level -> Level -> Bool
/= :: Level -> Level -> Bool
Eq, Int -> Level -> ShowS
[Level] -> ShowS
Level -> String
(Int -> Level -> ShowS)
-> (Level -> String) -> ([Level] -> ShowS) -> Show Level
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Level -> ShowS
showsPrec :: Int -> Level -> ShowS
$cshow :: Level -> String
show :: Level -> String
$cshowList :: [Level] -> ShowS
showList :: [Level] -> ShowS
Show)
instance ToJSON Level where
toJSON :: Level -> Value
toJSON = \case
Level
LevelCritical -> Value
"critical"
Level
LevelError -> Value
"error"
Level
LevelWarning -> Value
"warning"
Level
LevelInfo -> Value
"info"
Level
LevelDebug -> Value
"debug"
mkLevel :: Payload -> Level
mkLevel :: Payload -> Level
mkLevel (PayloadMessage Message
_) = Level
LevelInfo
mkLevel Payload
_ = Level
LevelError
data Request = Request
{ Request -> Text
requestUrl :: Text
, Request -> Text
requestMethod :: Text
, :: Object
, Request -> Object
requestParams :: Object
, Request -> Object
requestGet :: Object
, Request -> Text
requestQueryStrings :: Text
, Request -> Object
requestPost :: Object
, Request -> Text
requestBody :: Text
, Request -> Text
requestUserIp :: Text
} deriving (Request -> Request -> Bool
(Request -> Request -> Bool)
-> (Request -> Request -> Bool) -> Eq Request
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Request -> Request -> Bool
== :: Request -> Request -> Bool
$c/= :: Request -> Request -> Bool
/= :: Request -> Request -> Bool
Eq, Int -> Request -> ShowS
[Request] -> ShowS
Request -> String
(Int -> Request -> ShowS)
-> (Request -> String) -> ([Request] -> ShowS) -> Show Request
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Request -> ShowS
showsPrec :: Int -> Request -> ShowS
$cshow :: Request -> String
show :: Request -> String
$cshowList :: [Request] -> ShowS
showList :: [Request] -> ShowS
Show)
instance ToJSON Request where
toJSON :: Request -> Value
toJSON Request{Object
Text
requestUrl :: Request -> Text
requestMethod :: Request -> Text
requestHeaders :: Request -> Object
requestParams :: Request -> Object
requestGet :: Request -> Object
requestQueryStrings :: Request -> Text
requestPost :: Request -> Object
requestBody :: Request -> Text
requestUserIp :: Request -> Text
requestUrl :: Text
requestMethod :: Text
requestHeaders :: Object
requestParams :: Object
requestGet :: Object
requestQueryStrings :: Text
requestPost :: Object
requestBody :: Text
requestUserIp :: Text
..} = [Pair] -> Value
object
[ Key
"url" Key -> Text -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Text
requestUrl
, Key
"method" Key -> Text -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Text
requestMethod
, Key
"headers" Key -> Object -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Object
requestHeaders
, Key
"params" Key -> Object -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Object
requestParams
, Key
"GET" Key -> Object -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Object
requestGet
, Key
"query_string" Key -> Text -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Text
requestQueryStrings
, Key
"POST" Key -> Object -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Object
requestPost
, Key
"body" Key -> Text -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Text
requestBody
, Key
"user_ip" Key -> Text -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Text
requestUserIp
]
getRequestModifier :: (HasSettings m, Monad m) => m (Request -> Request)
getRequestModifier :: forall (m :: * -> *).
(HasSettings m, Monad m) =>
m (Request -> Request)
getRequestModifier = do
RequestModifiers{Maybe (NonEmpty Text)
requestModifiersExcludeHeaders :: Maybe (NonEmpty Text)
requestModifiersExcludeParams :: Maybe (NonEmpty Text)
requestModifiersIncludeHeaders :: Maybe (NonEmpty Text)
requestModifiersIncludeParams :: Maybe (NonEmpty Text)
requestModifiersExcludeHeaders :: RequestModifiers -> Maybe (NonEmpty Text)
requestModifiersExcludeParams :: RequestModifiers -> Maybe (NonEmpty Text)
requestModifiersIncludeHeaders :: RequestModifiers -> Maybe (NonEmpty Text)
requestModifiersIncludeParams :: RequestModifiers -> Maybe (NonEmpty Text)
..} <- Settings -> RequestModifiers
settingsRequestModifiers (Settings -> RequestModifiers) -> m Settings -> m RequestModifiers
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> m Settings
forall (m :: * -> *). HasSettings m => m Settings
getSettings
(Request -> Request) -> m (Request -> Request)
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return ((Request -> Request) -> m (Request -> Request))
-> (Request -> Request) -> m (Request -> Request)
forall a b. (a -> b) -> a -> b
$ Endo Request -> Request -> Request
forall a. Endo a -> a -> a
appEndo (Endo Request -> Request -> Request)
-> Endo Request -> Request -> Request
forall a b. (a -> b) -> a -> b
$ [Endo Request] -> Endo Request
forall a. Monoid a => [a] -> a
mconcat ([Endo Request] -> Endo Request) -> [Endo Request] -> Endo Request
forall a b. (a -> b) -> a -> b
$ [Maybe (Endo Request)] -> [Endo Request]
forall a. [Maybe a] -> [a]
catMaybes
[ (Object -> Object) -> Endo Request
withHeaders ((Object -> Object) -> Endo Request)
-> (NonEmpty Text -> Object -> Object)
-> NonEmpty Text
-> Endo Request
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NonEmpty Key -> Object -> Object
forall {t :: * -> *} {v}.
Foldable t =>
t Key -> KeyMap v -> KeyMap v
excludeNames (NonEmpty Key -> Object -> Object)
-> (NonEmpty Text -> NonEmpty Key)
-> NonEmpty Text
-> Object
-> Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text -> Key) -> NonEmpty Text -> NonEmpty Key
forall a b. (a -> b) -> NonEmpty a -> NonEmpty b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> Key
K.fromText (NonEmpty Text -> Endo Request)
-> Maybe (NonEmpty Text) -> Maybe (Endo Request)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe (NonEmpty Text)
requestModifiersExcludeHeaders
, (Object -> Object) -> Endo Request
withParams ((Object -> Object) -> Endo Request)
-> (NonEmpty Text -> Object -> Object)
-> NonEmpty Text
-> Endo Request
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NonEmpty Key -> Object -> Object
forall {t :: * -> *} {v}.
Foldable t =>
t Key -> KeyMap v -> KeyMap v
excludeNames (NonEmpty Key -> Object -> Object)
-> (NonEmpty Text -> NonEmpty Key)
-> NonEmpty Text
-> Object
-> Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text -> Key) -> NonEmpty Text -> NonEmpty Key
forall a b. (a -> b) -> NonEmpty a -> NonEmpty b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> Key
K.fromText (NonEmpty Text -> Endo Request)
-> Maybe (NonEmpty Text) -> Maybe (Endo Request)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe (NonEmpty Text)
requestModifiersExcludeParams
, (Object -> Object) -> Endo Request
withHeaders ((Object -> Object) -> Endo Request)
-> (NonEmpty Text -> Object -> Object)
-> NonEmpty Text
-> Endo Request
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NonEmpty Key -> Object -> Object
forall {t :: * -> *} {v}.
Foldable t =>
t Key -> KeyMap v -> KeyMap v
includeNames (NonEmpty Key -> Object -> Object)
-> (NonEmpty Text -> NonEmpty Key)
-> NonEmpty Text
-> Object
-> Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text -> Key) -> NonEmpty Text -> NonEmpty Key
forall a b. (a -> b) -> NonEmpty a -> NonEmpty b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> Key
K.fromText (NonEmpty Text -> Endo Request)
-> Maybe (NonEmpty Text) -> Maybe (Endo Request)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe (NonEmpty Text)
requestModifiersIncludeHeaders
, (Object -> Object) -> Endo Request
withParams ((Object -> Object) -> Endo Request)
-> (NonEmpty Text -> Object -> Object)
-> NonEmpty Text
-> Endo Request
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NonEmpty Key -> Object -> Object
forall {t :: * -> *} {v}.
Foldable t =>
t Key -> KeyMap v -> KeyMap v
includeNames (NonEmpty Key -> Object -> Object)
-> (NonEmpty Text -> NonEmpty Key)
-> NonEmpty Text
-> Object
-> Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text -> Key) -> NonEmpty Text -> NonEmpty Key
forall a b. (a -> b) -> NonEmpty a -> NonEmpty b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> Key
K.fromText (NonEmpty Text -> Endo Request)
-> Maybe (NonEmpty Text) -> Maybe (Endo Request)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe (NonEmpty Text)
requestModifiersIncludeParams
]
where
withHeaders :: (Object -> Object) -> Endo Request
withHeaders Object -> Object
f = (Request -> Request) -> Endo Request
forall a. (a -> a) -> Endo a
Endo ((Request -> Request) -> Endo Request)
-> (Request -> Request) -> Endo Request
forall a b. (a -> b) -> a -> b
$ \Request
request -> Request
request
{ requestHeaders = f $ requestHeaders request }
withParams :: (Object -> Object) -> Endo Request
withParams Object -> Object
f = (Request -> Request) -> Endo Request
forall a. (a -> a) -> Endo a
Endo ((Request -> Request) -> Endo Request)
-> (Request -> Request) -> Endo Request
forall a b. (a -> b) -> a -> b
$ \Request
request -> Request
request
{ requestParams = f $ requestParams request }
excludeNames :: t Key -> KeyMap v -> KeyMap v
excludeNames t Key
names = (Key -> v -> Bool) -> KeyMap v -> KeyMap v
forall v. (Key -> v -> Bool) -> KeyMap v -> KeyMap v
KM.filterWithKey ((Key -> v -> Bool) -> KeyMap v -> KeyMap v)
-> (Key -> v -> Bool) -> KeyMap v -> KeyMap v
forall a b. (a -> b) -> a -> b
$ \Key
name v
_ -> Key
name Key -> t Key -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`notElem` t Key
names
includeNames :: t Key -> KeyMap v -> KeyMap v
includeNames t Key
names = (Key -> v -> Bool) -> KeyMap v -> KeyMap v
forall v. (Key -> v -> Bool) -> KeyMap v -> KeyMap v
KM.filterWithKey ((Key -> v -> Bool) -> KeyMap v -> KeyMap v)
-> (Key -> v -> Bool) -> KeyMap v -> KeyMap v
forall a b. (a -> b) -> a -> b
$ \Key
name v
_ -> Key
name Key -> t Key -> Bool
forall a. Eq a => a -> t a -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` t Key
names
data Server = Server
{ Server -> Maybe Text
serverCpu :: Maybe Text
, Server -> Maybe Text
serverHost :: Maybe Text
, Server -> Maybe Text
serverRoot :: Maybe Text
, Server -> Maybe Text
serverBranch :: Maybe Text
, Server -> Maybe Text
serverCodeVersion :: Maybe Text
} deriving (Server -> Server -> Bool
(Server -> Server -> Bool)
-> (Server -> Server -> Bool) -> Eq Server
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Server -> Server -> Bool
== :: Server -> Server -> Bool
$c/= :: Server -> Server -> Bool
/= :: Server -> Server -> Bool
Eq, Int -> Server -> ShowS
[Server] -> ShowS
Server -> String
(Int -> Server -> ShowS)
-> (Server -> String) -> ([Server] -> ShowS) -> Show Server
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Server -> ShowS
showsPrec :: Int -> Server -> ShowS
$cshow :: Server -> String
show :: Server -> String
$cshowList :: [Server] -> ShowS
showList :: [Server] -> ShowS
Show)
instance ToJSON Server where
toJSON :: Server -> Value
toJSON Server{Maybe Text
serverCpu :: Server -> Maybe Text
serverHost :: Server -> Maybe Text
serverRoot :: Server -> Maybe Text
serverBranch :: Server -> Maybe Text
serverCodeVersion :: Server -> Maybe Text
serverCpu :: Maybe Text
serverHost :: Maybe Text
serverRoot :: Maybe Text
serverBranch :: Maybe Text
serverCodeVersion :: Maybe Text
..} = [Pair] -> Value
object
[ Key
"cpu" Key -> Maybe Text -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Maybe Text
serverCpu
, Key
"host" Key -> Maybe Text -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Maybe Text
serverHost
, Key
"root" Key -> Maybe Text -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Maybe Text
serverRoot
, Key
"branch" Key -> Maybe Text -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Maybe Text
serverBranch
, Key
"code_version" Key -> Maybe Text -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Maybe Text
serverCodeVersion
]
data Notifier = Notifier
{ Notifier -> Text
notifierName :: Text
, Notifier -> Text
notifierVersion :: Text
} deriving (Notifier -> Notifier -> Bool
(Notifier -> Notifier -> Bool)
-> (Notifier -> Notifier -> Bool) -> Eq Notifier
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Notifier -> Notifier -> Bool
== :: Notifier -> Notifier -> Bool
$c/= :: Notifier -> Notifier -> Bool
/= :: Notifier -> Notifier -> Bool
Eq, Int -> Notifier -> ShowS
[Notifier] -> ShowS
Notifier -> String
(Int -> Notifier -> ShowS)
-> (Notifier -> String) -> ([Notifier] -> ShowS) -> Show Notifier
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Notifier -> ShowS
showsPrec :: Int -> Notifier -> ShowS
$cshow :: Notifier -> String
show :: Notifier -> String
$cshowList :: [Notifier] -> ShowS
showList :: [Notifier] -> ShowS
Show)
instance ToJSON Notifier where
toJSON :: Notifier -> Value
toJSON Notifier{Text
notifierName :: Notifier -> Text
notifierVersion :: Notifier -> Text
notifierName :: Text
notifierVersion :: Text
..} = [Pair] -> Value
object
[ Key
"name" Key -> Text -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Text
notifierName
, Key
"version" Key -> Text -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Text
notifierVersion
]
defaultNotifier :: Notifier
defaultNotifier :: Notifier
defaultNotifier = Notifier
{ notifierName :: Text
notifierName = Text
"rollbar-client"
, notifierVersion :: Text
notifierVersion = Text
"1.1.0"
}
newtype ItemId = ItemId Text
deriving (ItemId -> ItemId -> Bool
(ItemId -> ItemId -> Bool)
-> (ItemId -> ItemId -> Bool) -> Eq ItemId
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ItemId -> ItemId -> Bool
== :: ItemId -> ItemId -> Bool
$c/= :: ItemId -> ItemId -> Bool
/= :: ItemId -> ItemId -> Bool
Eq, Int -> ItemId -> ShowS
[ItemId] -> ShowS
ItemId -> String
(Int -> ItemId -> ShowS)
-> (ItemId -> String) -> ([ItemId] -> ShowS) -> Show ItemId
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ItemId -> ShowS
showsPrec :: Int -> ItemId -> ShowS
$cshow :: ItemId -> String
show :: ItemId -> String
$cshowList :: [ItemId] -> ShowS
showList :: [ItemId] -> ShowS
Show)
instance FromJSON ItemId where
parseJSON :: Value -> Parser ItemId
parseJSON = String -> (Object -> Parser ItemId) -> Value -> Parser ItemId
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"ItemId" ((Object -> Parser ItemId) -> Value -> Parser ItemId)
-> (Object -> Parser ItemId) -> Value -> Parser ItemId
forall a b. (a -> b) -> a -> b
$ \Object
o ->
Text -> ItemId
ItemId (Text -> ItemId) -> Parser Text -> Parser ItemId
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"uuid"
createItem
:: (HasSettings m, MonadHttp m)
=> Item
-> m ItemId
createItem :: forall (m :: * -> *).
(HasSettings m, MonadHttp m) =>
Item -> m ItemId
createItem Item
item = do
Request -> Request
requestModifier <- m (Request -> Request)
forall (m :: * -> *).
(HasSettings m, Monad m) =>
m (Request -> Request)
getRequestModifier
(JsonResponse (ResultResponse ItemId) -> ItemId)
-> m (JsonResponse (ResultResponse ItemId)) -> m ItemId
forall a b. (a -> b) -> m a -> m b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap
(ResultResponse ItemId -> ItemId
forall a. ResultResponse a -> a
resultResponseResult (ResultResponse ItemId -> ItemId)
-> (JsonResponse (ResultResponse ItemId) -> ResultResponse ItemId)
-> JsonResponse (ResultResponse ItemId)
-> ItemId
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JsonResponse (ResultResponse ItemId)
-> HttpResponseBody (JsonResponse (ResultResponse ItemId))
JsonResponse (ResultResponse ItemId) -> ResultResponse ItemId
forall response.
HttpResponse response =>
response -> HttpResponseBody response
responseBody)
(POST
-> Url 'Https
-> ReqBodyJson Item
-> Proxy (JsonResponse (ResultResponse ItemId))
-> m (JsonResponse (ResultResponse ItemId))
forall (m :: * -> *) body method response.
(HasSettings m, HttpBody body,
HttpBodyAllowed (AllowsBody method) (ProvidesBody body),
HttpMethod method, HttpResponse response, MonadHttp m) =>
method -> Url 'Https -> body -> Proxy response -> m response
rollbar POST
POST Url 'Https
url ((Request -> Request) -> ReqBodyJson Item
body Request -> Request
requestModifier) Proxy (JsonResponse (ResultResponse ItemId))
forall a. Proxy (JsonResponse a)
jsonResponse)
where
url :: Url 'Https
url = Url 'Https
baseUrl Url 'Https -> Text -> Url 'Https
forall (scheme :: Scheme). Url scheme -> Text -> Url scheme
/: Text
"item" Url 'Https -> Text -> Url 'Https
forall (scheme :: Scheme). Url scheme -> Text -> Url scheme
/: Text
""
body :: (Request -> Request) -> ReqBodyJson Item
body Request -> Request
requestModifier = Item -> ReqBodyJson Item
forall a. a -> ReqBodyJson a
ReqBodyJson (Item -> ReqBodyJson Item) -> Item -> ReqBodyJson Item
forall a b. (a -> b) -> a -> b
$
Item
item { itemRequest = requestModifier <$> itemRequest item }