{-# LANGUAGE GeneralizedNewtypeDeriving #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE TemplateHaskell #-} module CoinbasePro.Authenticated.Accounts ( Account (..) , AccountId (..) , Currency (..) , Balance (..) , ProfileId (..) , Fees (..) , TrailingVolume (..) , AccountHistory (..) , Hold (..) ) where import Data.Aeson (FromJSON (..), ToJSON, withObject, withText, (.:), (.:?)) import qualified Data.Aeson as A import Data.Aeson.Casing (snakeCase) import Data.Aeson.TH (constructorTagModifier, defaultOptions, deriveJSON, fieldLabelModifier) import qualified Data.Char as Char import Data.Text (Text, pack, unpack) import Data.Time.Clock (UTCTime) import Text.Printf (printf) import Web.HttpApiData (ToHttpApiData (..)) import CoinbasePro.Types (CreatedAt (..), OrderId, ProductId, TradeId (..), Volume (..)) newtype AccountId = AccountId Text deriving AccountId -> AccountId -> Bool (AccountId -> AccountId -> Bool) -> (AccountId -> AccountId -> Bool) -> Eq AccountId forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: AccountId -> AccountId -> Bool $c/= :: AccountId -> AccountId -> Bool == :: AccountId -> AccountId -> Bool $c== :: AccountId -> AccountId -> Bool Eq instance Show AccountId where show :: AccountId -> String show (AccountId Text t) = Text -> String unpack Text t deriveJSON defaultOptions { fieldLabelModifier = snakeCase } ''AccountId instance ToHttpApiData AccountId where toUrlPiece :: AccountId -> Text toUrlPiece (AccountId Text aid) = Text aid toQueryParam :: AccountId -> Text toQueryParam (AccountId Text aid) = Text aid newtype Currency = Currency Text deriving (Currency -> Currency -> Bool (Currency -> Currency -> Bool) -> (Currency -> Currency -> Bool) -> Eq Currency forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: Currency -> Currency -> Bool $c/= :: Currency -> Currency -> Bool == :: Currency -> Currency -> Bool $c== :: Currency -> Currency -> Bool Eq, Int -> Currency -> ShowS [Currency] -> ShowS Currency -> String (Int -> Currency -> ShowS) -> (Currency -> String) -> ([Currency] -> ShowS) -> Show Currency forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [Currency] -> ShowS $cshowList :: [Currency] -> ShowS show :: Currency -> String $cshow :: Currency -> String showsPrec :: Int -> Currency -> ShowS $cshowsPrec :: Int -> Currency -> ShowS Show) newtype Balance = Balance Double deriving (Balance -> Balance -> Bool (Balance -> Balance -> Bool) -> (Balance -> Balance -> Bool) -> Eq Balance forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: Balance -> Balance -> Bool $c/= :: Balance -> Balance -> Bool == :: Balance -> Balance -> Bool $c== :: Balance -> Balance -> Bool Eq, Int -> Balance -> ShowS [Balance] -> ShowS Balance -> String (Int -> Balance -> ShowS) -> (Balance -> String) -> ([Balance] -> ShowS) -> Show Balance forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [Balance] -> ShowS $cshowList :: [Balance] -> ShowS show :: Balance -> String $cshow :: Balance -> String showsPrec :: Int -> Balance -> ShowS $cshowsPrec :: Int -> Balance -> ShowS Show) instance ToJSON Balance where toJSON :: Balance -> Value toJSON (Balance Double s) = Text -> Value A.String (Text -> Value) -> (String -> Text) -> String -> Value forall b c a. (b -> c) -> (a -> b) -> a -> c . String -> Text pack (String -> Value) -> String -> Value forall a b. (a -> b) -> a -> b $ String -> Double -> String forall r. PrintfType r => String -> r printf String "%.16f" Double s instance FromJSON Balance where parseJSON :: Value -> Parser Balance parseJSON = String -> (Text -> Parser Balance) -> Value -> Parser Balance forall a. String -> (Text -> Parser a) -> Value -> Parser a withText String "balance" ((Text -> Parser Balance) -> Value -> Parser Balance) -> (Text -> Parser Balance) -> Value -> Parser Balance forall a b. (a -> b) -> a -> b $ \Text t -> Balance -> Parser Balance forall (m :: * -> *) a. Monad m => a -> m a return (Balance -> Parser Balance) -> (String -> Balance) -> String -> Parser Balance forall b c a. (b -> c) -> (a -> b) -> a -> c . Double -> Balance Balance (Double -> Balance) -> (String -> Double) -> String -> Balance forall b c a. (b -> c) -> (a -> b) -> a -> c . String -> Double forall a. Read a => String -> a read (String -> Parser Balance) -> String -> Parser Balance forall a b. (a -> b) -> a -> b $ Text -> String unpack Text t newtype ProfileId = ProfileId Text deriving (ProfileId -> ProfileId -> Bool (ProfileId -> ProfileId -> Bool) -> (ProfileId -> ProfileId -> Bool) -> Eq ProfileId forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: ProfileId -> ProfileId -> Bool $c/= :: ProfileId -> ProfileId -> Bool == :: ProfileId -> ProfileId -> Bool $c== :: ProfileId -> ProfileId -> Bool Eq, Int -> ProfileId -> ShowS [ProfileId] -> ShowS ProfileId -> String (Int -> ProfileId -> ShowS) -> (ProfileId -> String) -> ([ProfileId] -> ShowS) -> Show ProfileId forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [ProfileId] -> ShowS $cshowList :: [ProfileId] -> ShowS show :: ProfileId -> String $cshow :: ProfileId -> String showsPrec :: Int -> ProfileId -> ShowS $cshowsPrec :: Int -> ProfileId -> ShowS Show) data Account = Account { Account -> AccountId accountId :: AccountId , Account -> Currency currency :: Currency , Account -> Balance balance :: Balance , Account -> Balance available :: Balance , Account -> Balance hold :: Balance , Account -> ProfileId profileId :: ProfileId } deriving (Account -> Account -> Bool (Account -> Account -> Bool) -> (Account -> Account -> Bool) -> Eq Account forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: Account -> Account -> Bool $c/= :: Account -> Account -> Bool == :: Account -> Account -> Bool $c== :: Account -> Account -> Bool Eq, Int -> Account -> ShowS [Account] -> ShowS Account -> String (Int -> Account -> ShowS) -> (Account -> String) -> ([Account] -> ShowS) -> Show Account forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [Account] -> ShowS $cshowList :: [Account] -> ShowS show :: Account -> String $cshow :: Account -> String showsPrec :: Int -> Account -> ShowS $cshowsPrec :: Int -> Account -> ShowS Show) instance FromJSON Account where parseJSON :: Value -> Parser Account parseJSON = String -> (Object -> Parser Account) -> Value -> Parser Account forall a. String -> (Object -> Parser a) -> Value -> Parser a withObject String "account" ((Object -> Parser Account) -> Value -> Parser Account) -> (Object -> Parser Account) -> Value -> Parser Account forall a b. (a -> b) -> a -> b $ \Object o -> AccountId -> Currency -> Balance -> Balance -> Balance -> ProfileId -> Account Account (AccountId -> Currency -> Balance -> Balance -> Balance -> ProfileId -> Account) -> Parser AccountId -> Parser (Currency -> Balance -> Balance -> Balance -> ProfileId -> Account) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> (Text -> AccountId AccountId (Text -> AccountId) -> Parser Text -> Parser AccountId forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Object o Object -> Text -> Parser Text forall a. FromJSON a => Object -> Text -> Parser a .: Text "id") Parser (Currency -> Balance -> Balance -> Balance -> ProfileId -> Account) -> Parser Currency -> Parser (Balance -> Balance -> Balance -> ProfileId -> Account) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> (Text -> Currency Currency (Text -> Currency) -> Parser Text -> Parser Currency forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Object o Object -> Text -> Parser Text forall a. FromJSON a => Object -> Text -> Parser a .: Text "currency") Parser (Balance -> Balance -> Balance -> ProfileId -> Account) -> Parser Balance -> Parser (Balance -> Balance -> ProfileId -> Account) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> (Double -> Balance Balance (Double -> Balance) -> (String -> Double) -> String -> Balance forall b c a. (b -> c) -> (a -> b) -> a -> c . String -> Double forall a. Read a => String -> a read (String -> Balance) -> Parser String -> Parser Balance forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Object o Object -> Text -> Parser String forall a. FromJSON a => Object -> Text -> Parser a .: Text "balance") Parser (Balance -> Balance -> ProfileId -> Account) -> Parser Balance -> Parser (Balance -> ProfileId -> Account) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> (Double -> Balance Balance (Double -> Balance) -> (String -> Double) -> String -> Balance forall b c a. (b -> c) -> (a -> b) -> a -> c . String -> Double forall a. Read a => String -> a read (String -> Balance) -> Parser String -> Parser Balance forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Object o Object -> Text -> Parser String forall a. FromJSON a => Object -> Text -> Parser a .: Text "available") Parser (Balance -> ProfileId -> Account) -> Parser Balance -> Parser (ProfileId -> Account) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> (Double -> Balance Balance (Double -> Balance) -> (String -> Double) -> String -> Balance forall b c a. (b -> c) -> (a -> b) -> a -> c . String -> Double forall a. Read a => String -> a read (String -> Balance) -> Parser String -> Parser Balance forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Object o Object -> Text -> Parser String forall a. FromJSON a => Object -> Text -> Parser a .: Text "hold") Parser (ProfileId -> Account) -> Parser ProfileId -> Parser Account forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> (Text -> ProfileId ProfileId (Text -> ProfileId) -> Parser Text -> Parser ProfileId forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Object o Object -> Text -> Parser Text forall a. FromJSON a => Object -> Text -> Parser a .: Text "profile_id") newtype FeeRate = FeeRate { FeeRate -> Double unFeeRate :: Double } deriving (FeeRate -> FeeRate -> Bool (FeeRate -> FeeRate -> Bool) -> (FeeRate -> FeeRate -> Bool) -> Eq FeeRate forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: FeeRate -> FeeRate -> Bool $c/= :: FeeRate -> FeeRate -> Bool == :: FeeRate -> FeeRate -> Bool $c== :: FeeRate -> FeeRate -> Bool Eq, Int -> FeeRate -> ShowS [FeeRate] -> ShowS FeeRate -> String (Int -> FeeRate -> ShowS) -> (FeeRate -> String) -> ([FeeRate] -> ShowS) -> Show FeeRate forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [FeeRate] -> ShowS $cshowList :: [FeeRate] -> ShowS show :: FeeRate -> String $cshow :: FeeRate -> String showsPrec :: Int -> FeeRate -> ShowS $cshowsPrec :: Int -> FeeRate -> ShowS Show, Value -> Parser [FeeRate] Value -> Parser FeeRate (Value -> Parser FeeRate) -> (Value -> Parser [FeeRate]) -> FromJSON FeeRate forall a. (Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a parseJSONList :: Value -> Parser [FeeRate] $cparseJSONList :: Value -> Parser [FeeRate] parseJSON :: Value -> Parser FeeRate $cparseJSON :: Value -> Parser FeeRate FromJSON, [FeeRate] -> Encoding [FeeRate] -> Value FeeRate -> Encoding FeeRate -> Value (FeeRate -> Value) -> (FeeRate -> Encoding) -> ([FeeRate] -> Value) -> ([FeeRate] -> Encoding) -> ToJSON FeeRate forall a. (a -> Value) -> (a -> Encoding) -> ([a] -> Value) -> ([a] -> Encoding) -> ToJSON a toEncodingList :: [FeeRate] -> Encoding $ctoEncodingList :: [FeeRate] -> Encoding toJSONList :: [FeeRate] -> Value $ctoJSONList :: [FeeRate] -> Value toEncoding :: FeeRate -> Encoding $ctoEncoding :: FeeRate -> Encoding toJSON :: FeeRate -> Value $ctoJSON :: FeeRate -> Value ToJSON) data Fees = Fees { Fees -> FeeRate makerFeeRate :: FeeRate , Fees -> FeeRate takerFeeRate :: FeeRate , Fees -> Volume usdVolume :: Volume } deriving (Fees -> Fees -> Bool (Fees -> Fees -> Bool) -> (Fees -> Fees -> Bool) -> Eq Fees forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: Fees -> Fees -> Bool $c/= :: Fees -> Fees -> Bool == :: Fees -> Fees -> Bool $c== :: Fees -> Fees -> Bool Eq, Int -> Fees -> ShowS [Fees] -> ShowS Fees -> String (Int -> Fees -> ShowS) -> (Fees -> String) -> ([Fees] -> ShowS) -> Show Fees forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [Fees] -> ShowS $cshowList :: [Fees] -> ShowS show :: Fees -> String $cshow :: Fees -> String showsPrec :: Int -> Fees -> ShowS $cshowsPrec :: Int -> Fees -> ShowS Show) instance FromJSON Fees where parseJSON :: Value -> Parser Fees parseJSON = String -> (Object -> Parser Fees) -> Value -> Parser Fees forall a. String -> (Object -> Parser a) -> Value -> Parser a withObject String "fees" ((Object -> Parser Fees) -> Value -> Parser Fees) -> (Object -> Parser Fees) -> Value -> Parser Fees forall a b. (a -> b) -> a -> b $ \Object o -> FeeRate -> FeeRate -> Volume -> Fees Fees (FeeRate -> FeeRate -> Volume -> Fees) -> Parser FeeRate -> Parser (FeeRate -> Volume -> Fees) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> (Double -> FeeRate FeeRate (Double -> FeeRate) -> (String -> Double) -> String -> FeeRate forall b c a. (b -> c) -> (a -> b) -> a -> c . String -> Double forall a. Read a => String -> a read (String -> FeeRate) -> Parser String -> Parser FeeRate forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Object o Object -> Text -> Parser String forall a. FromJSON a => Object -> Text -> Parser a .: Text "maker_fee_rate") Parser (FeeRate -> Volume -> Fees) -> Parser FeeRate -> Parser (Volume -> Fees) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> (Double -> FeeRate FeeRate (Double -> FeeRate) -> (String -> Double) -> String -> FeeRate forall b c a. (b -> c) -> (a -> b) -> a -> c . String -> Double forall a. Read a => String -> a read (String -> FeeRate) -> Parser String -> Parser FeeRate forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Object o Object -> Text -> Parser String forall a. FromJSON a => Object -> Text -> Parser a .: Text "taker_fee_rate") Parser (Volume -> Fees) -> Parser Volume -> Parser Fees forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> (Double -> Volume Volume (Double -> Volume) -> (String -> Double) -> String -> Volume forall b c a. (b -> c) -> (a -> b) -> a -> c . String -> Double forall a. Read a => String -> a read (String -> Volume) -> Parser String -> Parser Volume forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Object o Object -> Text -> Parser String forall a. FromJSON a => Object -> Text -> Parser a .: Text "usd_volume") data TrailingVolume = TrailingVolume { TrailingVolume -> ProductId productId :: ProductId , TrailingVolume -> Volume exchangeVolume :: Volume , TrailingVolume -> Volume volume :: Volume , TrailingVolume -> UTCTime recordedAt :: UTCTime } deriving (TrailingVolume -> TrailingVolume -> Bool (TrailingVolume -> TrailingVolume -> Bool) -> (TrailingVolume -> TrailingVolume -> Bool) -> Eq TrailingVolume forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: TrailingVolume -> TrailingVolume -> Bool $c/= :: TrailingVolume -> TrailingVolume -> Bool == :: TrailingVolume -> TrailingVolume -> Bool $c== :: TrailingVolume -> TrailingVolume -> Bool Eq, Int -> TrailingVolume -> ShowS [TrailingVolume] -> ShowS TrailingVolume -> String (Int -> TrailingVolume -> ShowS) -> (TrailingVolume -> String) -> ([TrailingVolume] -> ShowS) -> Show TrailingVolume forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [TrailingVolume] -> ShowS $cshowList :: [TrailingVolume] -> ShowS show :: TrailingVolume -> String $cshow :: TrailingVolume -> String showsPrec :: Int -> TrailingVolume -> ShowS $cshowsPrec :: Int -> TrailingVolume -> ShowS Show) deriveJSON defaultOptions { fieldLabelModifier = snakeCase } ''TrailingVolume data AccountHistoryType = Transfer | Match | Fee | Rebate | Conversion deriving (AccountHistoryType -> AccountHistoryType -> Bool (AccountHistoryType -> AccountHistoryType -> Bool) -> (AccountHistoryType -> AccountHistoryType -> Bool) -> Eq AccountHistoryType forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: AccountHistoryType -> AccountHistoryType -> Bool $c/= :: AccountHistoryType -> AccountHistoryType -> Bool == :: AccountHistoryType -> AccountHistoryType -> Bool $c== :: AccountHistoryType -> AccountHistoryType -> Bool Eq, Int -> AccountHistoryType -> ShowS [AccountHistoryType] -> ShowS AccountHistoryType -> String (Int -> AccountHistoryType -> ShowS) -> (AccountHistoryType -> String) -> ([AccountHistoryType] -> ShowS) -> Show AccountHistoryType forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [AccountHistoryType] -> ShowS $cshowList :: [AccountHistoryType] -> ShowS show :: AccountHistoryType -> String $cshow :: AccountHistoryType -> String showsPrec :: Int -> AccountHistoryType -> ShowS $cshowsPrec :: Int -> AccountHistoryType -> ShowS Show) deriveJSON defaultOptions { constructorTagModifier = fmap Char.toLower } ''AccountHistoryType data Details = Details { Details -> Maybe OrderId dOrderId :: Maybe OrderId , Details -> Maybe TradeId dTradeId :: Maybe TradeId , Details -> Maybe ProductId dProductId :: Maybe ProductId } deriving (Details -> Details -> Bool (Details -> Details -> Bool) -> (Details -> Details -> Bool) -> Eq Details forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: Details -> Details -> Bool $c/= :: Details -> Details -> Bool == :: Details -> Details -> Bool $c== :: Details -> Details -> Bool Eq, Int -> Details -> ShowS [Details] -> ShowS Details -> String (Int -> Details -> ShowS) -> (Details -> String) -> ([Details] -> ShowS) -> Show Details forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [Details] -> ShowS $cshowList :: [Details] -> ShowS show :: Details -> String $cshow :: Details -> String showsPrec :: Int -> Details -> ShowS $cshowsPrec :: Int -> Details -> ShowS Show) instance FromJSON Details where parseJSON :: Value -> Parser Details parseJSON = String -> (Object -> Parser Details) -> Value -> Parser Details forall a. String -> (Object -> Parser a) -> Value -> Parser a withObject String "details" ((Object -> Parser Details) -> Value -> Parser Details) -> (Object -> Parser Details) -> Value -> Parser Details forall a b. (a -> b) -> a -> b $ \Object o -> Maybe OrderId -> Maybe TradeId -> Maybe ProductId -> Details Details (Maybe OrderId -> Maybe TradeId -> Maybe ProductId -> Details) -> Parser (Maybe OrderId) -> Parser (Maybe TradeId -> Maybe ProductId -> Details) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> (Object o Object -> Text -> Parser (Maybe OrderId) forall a. FromJSON a => Object -> Text -> Parser (Maybe a) .:? Text "order_id") Parser (Maybe TradeId -> Maybe ProductId -> Details) -> Parser (Maybe TradeId) -> Parser (Maybe ProductId -> Details) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> ((String -> TradeId) -> Maybe String -> Maybe TradeId forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap (Int -> TradeId TradeId (Int -> TradeId) -> (String -> Int) -> String -> TradeId forall b c a. (b -> c) -> (a -> b) -> a -> c . String -> Int forall a. Read a => String -> a read) (Maybe String -> Maybe TradeId) -> Parser (Maybe String) -> Parser (Maybe TradeId) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Object o Object -> Text -> Parser (Maybe String) forall a. FromJSON a => Object -> Text -> Parser (Maybe a) .:? Text "trade_id") Parser (Maybe ProductId -> Details) -> Parser (Maybe ProductId) -> Parser Details forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> (Object o Object -> Text -> Parser (Maybe ProductId) forall a. FromJSON a => Object -> Text -> Parser (Maybe a) .:? Text "product_id") data AccountHistory = AccountHistory { AccountHistory -> AccountId hAccountId :: AccountId , AccountHistory -> CreatedAt hCreatedAt :: CreatedAt , AccountHistory -> Double hAmount :: Double , AccountHistory -> Balance hBalance :: Balance , AccountHistory -> AccountHistoryType hType :: AccountHistoryType , AccountHistory -> Maybe Details hDetails :: Maybe Details } deriving (AccountHistory -> AccountHistory -> Bool (AccountHistory -> AccountHistory -> Bool) -> (AccountHistory -> AccountHistory -> Bool) -> Eq AccountHistory forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: AccountHistory -> AccountHistory -> Bool $c/= :: AccountHistory -> AccountHistory -> Bool == :: AccountHistory -> AccountHistory -> Bool $c== :: AccountHistory -> AccountHistory -> Bool Eq, Int -> AccountHistory -> ShowS [AccountHistory] -> ShowS AccountHistory -> String (Int -> AccountHistory -> ShowS) -> (AccountHistory -> String) -> ([AccountHistory] -> ShowS) -> Show AccountHistory forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [AccountHistory] -> ShowS $cshowList :: [AccountHistory] -> ShowS show :: AccountHistory -> String $cshow :: AccountHistory -> String showsPrec :: Int -> AccountHistory -> ShowS $cshowsPrec :: Int -> AccountHistory -> ShowS Show) instance FromJSON AccountHistory where parseJSON :: Value -> Parser AccountHistory parseJSON = String -> (Object -> Parser AccountHistory) -> Value -> Parser AccountHistory forall a. String -> (Object -> Parser a) -> Value -> Parser a withObject String "account_history" ((Object -> Parser AccountHistory) -> Value -> Parser AccountHistory) -> (Object -> Parser AccountHistory) -> Value -> Parser AccountHistory forall a b. (a -> b) -> a -> b $ \Object o -> AccountId -> CreatedAt -> Double -> Balance -> AccountHistoryType -> Maybe Details -> AccountHistory AccountHistory (AccountId -> CreatedAt -> Double -> Balance -> AccountHistoryType -> Maybe Details -> AccountHistory) -> Parser AccountId -> Parser (CreatedAt -> Double -> Balance -> AccountHistoryType -> Maybe Details -> AccountHistory) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> (Text -> AccountId AccountId (Text -> AccountId) -> Parser Text -> Parser AccountId forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Object o Object -> Text -> Parser Text forall a. FromJSON a => Object -> Text -> Parser a .: Text "id") Parser (CreatedAt -> Double -> Balance -> AccountHistoryType -> Maybe Details -> AccountHistory) -> Parser CreatedAt -> Parser (Double -> Balance -> AccountHistoryType -> Maybe Details -> AccountHistory) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> (UTCTime -> CreatedAt CreatedAt (UTCTime -> CreatedAt) -> Parser UTCTime -> Parser CreatedAt forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Object o Object -> Text -> Parser UTCTime forall a. FromJSON a => Object -> Text -> Parser a .: Text "created_at") Parser (Double -> Balance -> AccountHistoryType -> Maybe Details -> AccountHistory) -> Parser Double -> Parser (Balance -> AccountHistoryType -> Maybe Details -> AccountHistory) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> (String -> Double forall a. Read a => String -> a read (String -> Double) -> Parser String -> Parser Double forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Object o Object -> Text -> Parser String forall a. FromJSON a => Object -> Text -> Parser a .: Text "amount") Parser (Balance -> AccountHistoryType -> Maybe Details -> AccountHistory) -> Parser Balance -> Parser (AccountHistoryType -> Maybe Details -> AccountHistory) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> (Double -> Balance Balance (Double -> Balance) -> (String -> Double) -> String -> Balance forall b c a. (b -> c) -> (a -> b) -> a -> c . String -> Double forall a. Read a => String -> a read (String -> Balance) -> Parser String -> Parser Balance forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Object o Object -> Text -> Parser String forall a. FromJSON a => Object -> Text -> Parser a .: Text "balance") Parser (AccountHistoryType -> Maybe Details -> AccountHistory) -> Parser AccountHistoryType -> Parser (Maybe Details -> AccountHistory) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> (Object o Object -> Text -> Parser AccountHistoryType forall a. FromJSON a => Object -> Text -> Parser a .: Text "type") Parser (Maybe Details -> AccountHistory) -> Parser (Maybe Details) -> Parser AccountHistory forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> (Object o Object -> Text -> Parser (Maybe Details) forall a. FromJSON a => Object -> Text -> Parser a .: Text "details") newtype HoldId = HoldId Text deriving (HoldId -> HoldId -> Bool (HoldId -> HoldId -> Bool) -> (HoldId -> HoldId -> Bool) -> Eq HoldId forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: HoldId -> HoldId -> Bool $c/= :: HoldId -> HoldId -> Bool == :: HoldId -> HoldId -> Bool $c== :: HoldId -> HoldId -> Bool Eq, Int -> HoldId -> ShowS [HoldId] -> ShowS HoldId -> String (Int -> HoldId -> ShowS) -> (HoldId -> String) -> ([HoldId] -> ShowS) -> Show HoldId forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [HoldId] -> ShowS $cshowList :: [HoldId] -> ShowS show :: HoldId -> String $cshow :: HoldId -> String showsPrec :: Int -> HoldId -> ShowS $cshowsPrec :: Int -> HoldId -> ShowS Show, [HoldId] -> Encoding [HoldId] -> Value HoldId -> Encoding HoldId -> Value (HoldId -> Value) -> (HoldId -> Encoding) -> ([HoldId] -> Value) -> ([HoldId] -> Encoding) -> ToJSON HoldId forall a. (a -> Value) -> (a -> Encoding) -> ([a] -> Value) -> ([a] -> Encoding) -> ToJSON a toEncodingList :: [HoldId] -> Encoding $ctoEncodingList :: [HoldId] -> Encoding toJSONList :: [HoldId] -> Value $ctoJSONList :: [HoldId] -> Value toEncoding :: HoldId -> Encoding $ctoEncoding :: HoldId -> Encoding toJSON :: HoldId -> Value $ctoJSON :: HoldId -> Value ToJSON, Value -> Parser [HoldId] Value -> Parser HoldId (Value -> Parser HoldId) -> (Value -> Parser [HoldId]) -> FromJSON HoldId forall a. (Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a parseJSONList :: Value -> Parser [HoldId] $cparseJSONList :: Value -> Parser [HoldId] parseJSON :: Value -> Parser HoldId $cparseJSON :: Value -> Parser HoldId FromJSON) data HoldType = Order | HoldTransfer deriving (HoldType -> HoldType -> Bool (HoldType -> HoldType -> Bool) -> (HoldType -> HoldType -> Bool) -> Eq HoldType forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: HoldType -> HoldType -> Bool $c/= :: HoldType -> HoldType -> Bool == :: HoldType -> HoldType -> Bool $c== :: HoldType -> HoldType -> Bool Eq, Int -> HoldType -> ShowS [HoldType] -> ShowS HoldType -> String (Int -> HoldType -> ShowS) -> (HoldType -> String) -> ([HoldType] -> ShowS) -> Show HoldType forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [HoldType] -> ShowS $cshowList :: [HoldType] -> ShowS show :: HoldType -> String $cshow :: HoldType -> String showsPrec :: Int -> HoldType -> ShowS $cshowsPrec :: Int -> HoldType -> ShowS Show) newtype HoldRef = HoldRef Text deriving (HoldRef -> HoldRef -> Bool (HoldRef -> HoldRef -> Bool) -> (HoldRef -> HoldRef -> Bool) -> Eq HoldRef forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: HoldRef -> HoldRef -> Bool $c/= :: HoldRef -> HoldRef -> Bool == :: HoldRef -> HoldRef -> Bool $c== :: HoldRef -> HoldRef -> Bool Eq, Int -> HoldRef -> ShowS [HoldRef] -> ShowS HoldRef -> String (Int -> HoldRef -> ShowS) -> (HoldRef -> String) -> ([HoldRef] -> ShowS) -> Show HoldRef forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [HoldRef] -> ShowS $cshowList :: [HoldRef] -> ShowS show :: HoldRef -> String $cshow :: HoldRef -> String showsPrec :: Int -> HoldRef -> ShowS $cshowsPrec :: Int -> HoldRef -> ShowS Show, [HoldRef] -> Encoding [HoldRef] -> Value HoldRef -> Encoding HoldRef -> Value (HoldRef -> Value) -> (HoldRef -> Encoding) -> ([HoldRef] -> Value) -> ([HoldRef] -> Encoding) -> ToJSON HoldRef forall a. (a -> Value) -> (a -> Encoding) -> ([a] -> Value) -> ([a] -> Encoding) -> ToJSON a toEncodingList :: [HoldRef] -> Encoding $ctoEncodingList :: [HoldRef] -> Encoding toJSONList :: [HoldRef] -> Value $ctoJSONList :: [HoldRef] -> Value toEncoding :: HoldRef -> Encoding $ctoEncoding :: HoldRef -> Encoding toJSON :: HoldRef -> Value $ctoJSON :: HoldRef -> Value ToJSON, Value -> Parser [HoldRef] Value -> Parser HoldRef (Value -> Parser HoldRef) -> (Value -> Parser [HoldRef]) -> FromJSON HoldRef forall a. (Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a parseJSONList :: Value -> Parser [HoldRef] $cparseJSONList :: Value -> Parser [HoldRef] parseJSON :: Value -> Parser HoldRef $cparseJSON :: Value -> Parser HoldRef FromJSON) deriveJSON defaultOptions { constructorTagModifier = fmap Char.toLower } ''HoldType data Hold = Hold { Hold -> HoldId holdId :: HoldId , Hold -> AccountId holdAccountId :: AccountId , Hold -> CreatedAt holdCreatedAt :: CreatedAt , Hold -> CreatedAt holdUpdatedAt :: CreatedAt , Hold -> Double holdAmount :: Double , Hold -> HoldType holdType :: HoldType , Hold -> HoldRef holdRef :: HoldRef } deriving (Hold -> Hold -> Bool (Hold -> Hold -> Bool) -> (Hold -> Hold -> Bool) -> Eq Hold forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: Hold -> Hold -> Bool $c/= :: Hold -> Hold -> Bool == :: Hold -> Hold -> Bool $c== :: Hold -> Hold -> Bool Eq, Int -> Hold -> ShowS [Hold] -> ShowS Hold -> String (Int -> Hold -> ShowS) -> (Hold -> String) -> ([Hold] -> ShowS) -> Show Hold forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [Hold] -> ShowS $cshowList :: [Hold] -> ShowS show :: Hold -> String $cshow :: Hold -> String showsPrec :: Int -> Hold -> ShowS $cshowsPrec :: Int -> Hold -> ShowS Show) deriveJSON defaultOptions { constructorTagModifier = fmap Char.toLower . drop 4, fieldLabelModifier = snakeCase } ''Hold