{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TemplateHaskell #-}
module CoinbasePro.Authenticated.Report
( ReportId (..)
, ReportRequest (..)
, ReportResponse (..)
, FillsReportRequest
, AccountsReportRequest
, accountsReportRequest
, fillsReportRequest
) where
import Data.Aeson (ToJSON (..), object, (.=))
import Data.Aeson.Casing (snakeCase)
import Data.Aeson.TH (constructorTagModifier,
defaultOptions, deriveJSON,
fieldLabelModifier,
unwrapUnaryRecords)
import qualified Data.Char as Char
import Data.Text (Text)
import Data.Time.Clock (UTCTime)
import Data.UUID (UUID)
import Servant.API (ToHttpApiData)
import CoinbasePro.Authenticated.Accounts (AccountId)
import CoinbasePro.Types (CreatedAt, ProductId)
newtype ReportId = ReportId { ReportId -> UUID
unReportId:: UUID }
deriving (ReportId -> ReportId -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ReportId -> ReportId -> Bool
$c/= :: ReportId -> ReportId -> Bool
== :: ReportId -> ReportId -> Bool
$c== :: ReportId -> ReportId -> Bool
Eq, Int -> ReportId -> ShowS
[ReportId] -> ShowS
ReportId -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ReportId] -> ShowS
$cshowList :: [ReportId] -> ShowS
show :: ReportId -> String
$cshow :: ReportId -> String
showsPrec :: Int -> ReportId -> ShowS
$cshowsPrec :: Int -> ReportId -> ShowS
Show, ReportId -> ByteString
ReportId -> Builder
ReportId -> Text
forall a.
(a -> Text)
-> (a -> Builder)
-> (a -> ByteString)
-> (a -> Text)
-> ToHttpApiData a
toQueryParam :: ReportId -> Text
$ctoQueryParam :: ReportId -> Text
toHeader :: ReportId -> ByteString
$ctoHeader :: ReportId -> ByteString
toEncodedUrlPiece :: ReportId -> Builder
$ctoEncodedUrlPiece :: ReportId -> Builder
toUrlPiece :: ReportId -> Text
$ctoUrlPiece :: ReportId -> Text
ToHttpApiData)
deriveJSON defaultOptions
{ fieldLabelModifier = snakeCase
, unwrapUnaryRecords = True
} ''ReportId
data ReportFormat = PDF | CSV
deriving Int -> ReportFormat -> ShowS
[ReportFormat] -> ShowS
ReportFormat -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ReportFormat] -> ShowS
$cshowList :: [ReportFormat] -> ShowS
show :: ReportFormat -> String
$cshow :: ReportFormat -> String
showsPrec :: Int -> ReportFormat -> ShowS
$cshowsPrec :: Int -> ReportFormat -> ShowS
Show
deriveJSON defaultOptions { constructorTagModifier = fmap Char.toLower } ''ReportFormat
newtype Email = Email Text
deriving Int -> Email -> ShowS
[Email] -> ShowS
Email -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Email] -> ShowS
$cshowList :: [Email] -> ShowS
show :: Email -> String
$cshow :: Email -> String
showsPrec :: Int -> Email -> ShowS
$cshowsPrec :: Int -> Email -> ShowS
Show
deriveJSON defaultOptions { fieldLabelModifier = snakeCase } ''Email
data Request = Request
{ Request -> UTCTime
rStartDate :: UTCTime
, Request -> UTCTime
rEndDate :: UTCTime
, Request -> Maybe ReportFormat
rFormat :: Maybe ReportFormat
, Request -> Maybe Email
rEmail :: Maybe Email
} deriving Int -> Request -> ShowS
[Request] -> ShowS
Request -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Request] -> ShowS
$cshowList :: [Request] -> ShowS
show :: Request -> String
$cshow :: Request -> String
showsPrec :: Int -> Request -> ShowS
$cshowsPrec :: Int -> Request -> ShowS
Show
data FillsReportRequest = FillsReportRequest
{ FillsReportRequest -> ProductId
frProductId :: ProductId
, FillsReportRequest -> Maybe AccountId
frAccountId :: Maybe AccountId
, FillsReportRequest -> Request
frRequest :: Request
} deriving Int -> FillsReportRequest -> ShowS
[FillsReportRequest] -> ShowS
FillsReportRequest -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FillsReportRequest] -> ShowS
$cshowList :: [FillsReportRequest] -> ShowS
show :: FillsReportRequest -> String
$cshow :: FillsReportRequest -> String
showsPrec :: Int -> FillsReportRequest -> ShowS
$cshowsPrec :: Int -> FillsReportRequest -> ShowS
Show
data AccountsReportRequest = AccountsReportRequest
{ AccountsReportRequest -> AccountId
arAccountId :: AccountId
, AccountsReportRequest -> Maybe ProductId
arProductId :: Maybe ProductId
, AccountsReportRequest -> Request
arRequest :: Request
} deriving Int -> AccountsReportRequest -> ShowS
[AccountsReportRequest] -> ShowS
AccountsReportRequest -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AccountsReportRequest] -> ShowS
$cshowList :: [AccountsReportRequest] -> ShowS
show :: AccountsReportRequest -> String
$cshow :: AccountsReportRequest -> String
showsPrec :: Int -> AccountsReportRequest -> ShowS
$cshowsPrec :: Int -> AccountsReportRequest -> ShowS
Show
data ReportRequest = Fills FillsReportRequest | Accounts AccountsReportRequest
deriving Int -> ReportRequest -> ShowS
[ReportRequest] -> ShowS
ReportRequest -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ReportRequest] -> ShowS
$cshowList :: [ReportRequest] -> ShowS
show :: ReportRequest -> String
$cshow :: ReportRequest -> String
showsPrec :: Int -> ReportRequest -> ShowS
$cshowsPrec :: Int -> ReportRequest -> ShowS
Show
accountsReportRequest :: AccountId
-> Maybe ProductId
-> UTCTime
-> UTCTime
-> Maybe ReportFormat
-> Maybe Email
-> ReportRequest
accountsReportRequest :: AccountId
-> Maybe ProductId
-> UTCTime
-> UTCTime
-> Maybe ReportFormat
-> Maybe Email
-> ReportRequest
accountsReportRequest AccountId
aid Maybe ProductId
prid UTCTime
start UTCTime
end Maybe ReportFormat
format =
AccountsReportRequest -> ReportRequest
Accounts forall b c a. (b -> c) -> (a -> b) -> a -> c
. AccountId -> Maybe ProductId -> Request -> AccountsReportRequest
AccountsReportRequest AccountId
aid Maybe ProductId
prid forall b c a. (b -> c) -> (a -> b) -> a -> c
. UTCTime -> UTCTime -> Maybe ReportFormat -> Maybe Email -> Request
Request UTCTime
start UTCTime
end Maybe ReportFormat
format
fillsReportRequest :: ProductId
-> Maybe AccountId
-> UTCTime
-> UTCTime
-> Maybe ReportFormat
-> Maybe Email
-> ReportRequest
fillsReportRequest :: ProductId
-> Maybe AccountId
-> UTCTime
-> UTCTime
-> Maybe ReportFormat
-> Maybe Email
-> ReportRequest
fillsReportRequest ProductId
prid Maybe AccountId
aid UTCTime
start UTCTime
end Maybe ReportFormat
format =
FillsReportRequest -> ReportRequest
Fills forall b c a. (b -> c) -> (a -> b) -> a -> c
. ProductId -> Maybe AccountId -> Request -> FillsReportRequest
FillsReportRequest ProductId
prid Maybe AccountId
aid forall b c a. (b -> c) -> (a -> b) -> a -> c
. UTCTime -> UTCTime -> Maybe ReportFormat -> Maybe Email -> Request
Request UTCTime
start UTCTime
end Maybe ReportFormat
format
instance ToJSON ReportRequest where
toJSON :: ReportRequest -> Value
toJSON (Fills FillsReportRequest
frr) =
[Pair] -> Value
object ([ Key
"type" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= (Text
"fills" :: Text)
, Key
"start_date" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Request -> UTCTime
rStartDate (FillsReportRequest -> Request
frRequest FillsReportRequest
frr)
, Key
"end_date" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Request -> UTCTime
rEndDate (FillsReportRequest -> Request
frRequest FillsReportRequest
frr)
, Key
"product_id" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= FillsReportRequest -> ProductId
frProductId FillsReportRequest
frr
] forall a. Semigroup a => a -> a -> a
<> forall b a. b -> (a -> b) -> Maybe a -> b
maybe forall a. Monoid a => a
mempty (\AccountId
aid -> [Key
"account_id" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= AccountId
aid]) (FillsReportRequest -> Maybe AccountId
frAccountId FillsReportRequest
frr)
forall a. Semigroup a => a -> a -> a
<> forall b a. b -> (a -> b) -> Maybe a -> b
maybe forall a. Monoid a => a
mempty (\Email
em -> [Key
"email" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Email
em]) (Request -> Maybe Email
rEmail (FillsReportRequest -> Request
frRequest FillsReportRequest
frr))
forall a. Semigroup a => a -> a -> a
<> forall b a. b -> (a -> b) -> Maybe a -> b
maybe forall a. Monoid a => a
mempty (\ReportFormat
fmt -> [Key
"format" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= ReportFormat
fmt]) (Request -> Maybe ReportFormat
rFormat (FillsReportRequest -> Request
frRequest FillsReportRequest
frr))
)
toJSON (Accounts AccountsReportRequest
arr) =
[Pair] -> Value
object ([ Key
"type" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= (Text
"account" :: Text)
, Key
"start_date" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Request -> UTCTime
rStartDate (AccountsReportRequest -> Request
arRequest AccountsReportRequest
arr)
, Key
"end_date" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Request -> UTCTime
rEndDate (AccountsReportRequest -> Request
arRequest AccountsReportRequest
arr)
, Key
"account_id" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= AccountsReportRequest -> AccountId
arAccountId AccountsReportRequest
arr
] forall a. Semigroup a => a -> a -> a
<> forall b a. b -> (a -> b) -> Maybe a -> b
maybe forall a. Monoid a => a
mempty (\ProductId
prid -> [Key
"product_id" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= ProductId
prid]) (AccountsReportRequest -> Maybe ProductId
arProductId AccountsReportRequest
arr)
forall a. Semigroup a => a -> a -> a
<> forall b a. b -> (a -> b) -> Maybe a -> b
maybe forall a. Monoid a => a
mempty (\Email
em -> [Key
"email" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Email
em]) (Request -> Maybe Email
rEmail (AccountsReportRequest -> Request
arRequest AccountsReportRequest
arr))
forall a. Semigroup a => a -> a -> a
<> forall b a. b -> (a -> b) -> Maybe a -> b
maybe forall a. Monoid a => a
mempty (\ReportFormat
fmt -> [Key
"format" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= ReportFormat
fmt]) (Request -> Maybe ReportFormat
rFormat (AccountsReportRequest -> Request
arRequest AccountsReportRequest
arr))
)
data ReportRequestType = FillsType | AccountType
instance Show ReportRequestType where
show :: ReportRequestType -> String
show ReportRequestType
FillsType = String
"fills"
show ReportRequestType
AccountType = String
"account"
deriveJSON defaultOptions { constructorTagModifier = snakeCase . init . init . init . init } ''ReportRequestType
data ReportStatus = Pending | Creating | Ready
instance Show ReportStatus where
show :: ReportStatus -> String
show ReportStatus
Pending = String
"pending"
show ReportStatus
Creating = String
"creating"
show ReportStatus
Ready = String
"ready"
deriveJSON defaultOptions { constructorTagModifier = fmap Char.toLower
, fieldLabelModifier = snakeCase
} ''ReportStatus
data ReportParams = ReportParams
{ ReportParams -> UTCTime
startDate :: UTCTime
, ReportParams -> UTCTime
endDate :: UTCTime
} deriving Int -> ReportParams -> ShowS
[ReportParams] -> ShowS
ReportParams -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ReportParams] -> ShowS
$cshowList :: [ReportParams] -> ShowS
show :: ReportParams -> String
$cshow :: ReportParams -> String
showsPrec :: Int -> ReportParams -> ShowS
$cshowsPrec :: Int -> ReportParams -> ShowS
Show
deriveJSON defaultOptions { fieldLabelModifier = snakeCase } ''ReportParams
data ReportResponse = ReportResponse
{ ReportResponse -> ReportId
rrId :: ReportId
, ReportResponse -> ReportRequestType
rrType :: ReportRequestType
, ReportResponse -> ReportStatus
rrStatus :: ReportStatus
, ReportResponse -> Maybe CreatedAt
rrCreatedAt :: Maybe CreatedAt
, ReportResponse -> Maybe UTCTime
rrCompletedAt :: Maybe UTCTime
, ReportResponse -> Maybe UTCTime
rrExpiresAt :: Maybe UTCTime
, ReportResponse -> Maybe Text
rrFileUrl :: Maybe Text
, ReportResponse -> Maybe ReportParams
rrParams :: Maybe ReportParams
} deriving Int -> ReportResponse -> ShowS
[ReportResponse] -> ShowS
ReportResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ReportResponse] -> ShowS
$cshowList :: [ReportResponse] -> ShowS
show :: ReportResponse -> String
$cshow :: ReportResponse -> String
showsPrec :: Int -> ReportResponse -> ShowS
$cshowsPrec :: Int -> ReportResponse -> ShowS
Show
deriveJSON defaultOptions { fieldLabelModifier = snakeCase . drop 2 } ''ReportResponse