{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE OverloadedStrings #-}
module Rollbar.API
(
itemsPOST
, itemsPOST'
, itemsPOSTRaw
, itemsPOSTRaw'
, makeRequest
, ItemsPOSTResponse(..)
, ItemsPOSTErrorMessage(..)
, ItemsPOSTSuccessResult(..)
, itemsPOSTWithException
) where
import Control.Monad.IO.Class (MonadIO)
import Data.Aeson.Types
( FromJSON(parseJSON)
, SumEncoding(UntaggedValue)
, ToJSON
, defaultOptions
, fieldLabelModifier
, genericParseJSON
, sumEncoding
)
import Data.Text (Text)
import GHC.Generics (Generic)
import Network.HTTP.Client
( Manager
, Request(host, method, path, port, secure)
, Response
, defaultRequest
, setRequestIgnoreStatus
)
import Network.HTTP.Simple
( JSONException
, httpJSON
, httpJSONEither
, setRequestBodyJSON
, setRequestManager
)
import Rollbar.Item (Item, RemoveHeaders, UUID4)
data ItemsPOSTResponse
= ItemsPOSTSuccess
{ err_ItemsPOSTSuccess :: Int
, result_ItemsPOSTSuccess :: ItemsPOSTSuccessResult
}
| ItemsPOSTError
{ err_ItemsPOSTError :: Int
, message_ItemsPOSTError :: Text
}
deriving (Eq, Generic, Show)
instance FromJSON ItemsPOSTResponse where
parseJSON = genericParseJSON defaultOptions
{ fieldLabelModifier = takeWhile (/= '_')
, sumEncoding = UntaggedValue
}
newtype ItemsPOSTSuccessResult
= ItemsPOSTSuccessResult
{ uuid :: UUID4
}
deriving (Eq, FromJSON, Generic, Show)
newtype ItemsPOSTErrorMessage
= ItemsPOSTErrorMessage Text
deriving (Eq, FromJSON, Generic, Show)
itemsPOST
:: (MonadIO f, RemoveHeaders b, ToJSON a)
=> Item a b
-> f (Response (Either JSONException ItemsPOSTResponse))
itemsPOST = itemsPOSTRaw
itemsPOST'
:: (MonadIO f, RemoveHeaders b, ToJSON a)
=> Manager
-> Item a b
-> f (Response (Either JSONException ItemsPOSTResponse))
itemsPOST' = itemsPOSTRaw'
itemsPOSTRaw
:: (FromJSON c, MonadIO f, RemoveHeaders b, ToJSON a)
=> Item a b
-> f (Response (Either JSONException c))
itemsPOSTRaw = httpJSONEither . makeRequest
itemsPOSTRaw'
:: (FromJSON c, MonadIO f, RemoveHeaders b, ToJSON a)
=> Manager
-> Item a b
-> f (Response (Either JSONException c))
itemsPOSTRaw' manager = httpJSONEither . setRequestManager manager . makeRequest
itemsPOSTWithException
:: (FromJSON c, MonadIO f, RemoveHeaders b, ToJSON a)
=> Item a b
-> f (Response c)
itemsPOSTWithException = httpJSON . makeRequest
makeRequest :: (RemoveHeaders headers, ToJSON a) => Item a headers -> Request
makeRequest payload =
setRequestBodyJSON payload
. setRequestIgnoreStatus
$ defaultRequest
{ host = "api.rollbar.com"
, method = "POST"
, path = "api/1/item/"
, port = 443
, secure = True
}