{-# LANGUAGE DataKinds #-} {-# LANGUAGE GeneralizedNewtypeDeriving #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE TemplateHaskell #-} module CoinbasePro.Types ( OrderId (..) , ClientOrderId (..) , Price (..) , ProductId (..) , Sequence , UserId , ProfileId , Side (..) , Size (..) , Volume (..) , TradeId (..) , Funds , OrderType (..) , CreatedAt (..) , Candle (..) , CandleGranularity (..) , TwentyFourHourStats (..) , CurrencyType (..) , Currency (..) , CryptoAddress (..) , filterOrderFieldName ) where import Data.Aeson (FromJSON, FromJSONKey, ToJSON, ToJSONKey, parseJSON, toJSON, withArray, withObject, withText, (.:), (.:?)) import qualified Data.Aeson as A import Data.Aeson.Casing (camelCase, snakeCase) import Data.Aeson.TH (constructorTagModifier, defaultOptions, deriveJSON, fieldLabelModifier, unwrapUnaryRecords) import Data.Text (Text, pack, toLower, unpack) import Data.Time.Clock (UTCTime) import Data.Time.Clock.POSIX (posixSecondsToUTCTime) import Data.UUID (UUID, toString, toText) import qualified Data.Vector as V import Servant.API import Text.Printf (printf) type UserId = Text type ProfileId = Text type Sequence = Int data Side = Buy | Sell deriving (Side -> Side -> Bool (Side -> Side -> Bool) -> (Side -> Side -> Bool) -> Eq Side forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: Side -> Side -> Bool $c/= :: Side -> Side -> Bool == :: Side -> Side -> Bool $c== :: Side -> Side -> Bool Eq, Eq Side Eq Side -> (Side -> Side -> Ordering) -> (Side -> Side -> Bool) -> (Side -> Side -> Bool) -> (Side -> Side -> Bool) -> (Side -> Side -> Bool) -> (Side -> Side -> Side) -> (Side -> Side -> Side) -> Ord Side Side -> Side -> Bool Side -> Side -> Ordering Side -> Side -> Side forall a. Eq a -> (a -> a -> Ordering) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> a) -> (a -> a -> a) -> Ord a min :: Side -> Side -> Side $cmin :: Side -> Side -> Side max :: Side -> Side -> Side $cmax :: Side -> Side -> Side >= :: Side -> Side -> Bool $c>= :: Side -> Side -> Bool > :: Side -> Side -> Bool $c> :: Side -> Side -> Bool <= :: Side -> Side -> Bool $c<= :: Side -> Side -> Bool < :: Side -> Side -> Bool $c< :: Side -> Side -> Bool compare :: Side -> Side -> Ordering $ccompare :: Side -> Side -> Ordering $cp1Ord :: Eq Side Ord, Int -> Side -> ShowS [Side] -> ShowS Side -> String (Int -> Side -> ShowS) -> (Side -> String) -> ([Side] -> ShowS) -> Show Side forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [Side] -> ShowS $cshowList :: [Side] -> ShowS show :: Side -> String $cshow :: Side -> String showsPrec :: Int -> Side -> ShowS $cshowsPrec :: Int -> Side -> ShowS Show) instance ToHttpApiData Side where toUrlPiece :: Side -> Text toUrlPiece = Text -> Text toLower (Text -> Text) -> (Side -> Text) -> Side -> Text forall b c a. (b -> c) -> (a -> b) -> a -> c . String -> Text pack (String -> Text) -> (Side -> String) -> Side -> Text forall b c a. (b -> c) -> (a -> b) -> a -> c . Side -> String forall a. Show a => a -> String show toQueryParam :: Side -> Text toQueryParam = Text -> Text toLower (Text -> Text) -> (Side -> Text) -> Side -> Text forall b c a. (b -> c) -> (a -> b) -> a -> c . String -> Text pack (String -> Text) -> (Side -> String) -> Side -> Text forall b c a. (b -> c) -> (a -> b) -> a -> c . Side -> String forall a. Show a => a -> String show deriveJSON defaultOptions { constructorTagModifier = camelCase , fieldLabelModifier = snakeCase } ''Side newtype OrderId = OrderId { OrderId -> Text unOrderId :: Text } deriving (OrderId -> OrderId -> Bool (OrderId -> OrderId -> Bool) -> (OrderId -> OrderId -> Bool) -> Eq OrderId forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: OrderId -> OrderId -> Bool $c/= :: OrderId -> OrderId -> Bool == :: OrderId -> OrderId -> Bool $c== :: OrderId -> OrderId -> Bool Eq, Eq OrderId Eq OrderId -> (OrderId -> OrderId -> Ordering) -> (OrderId -> OrderId -> Bool) -> (OrderId -> OrderId -> Bool) -> (OrderId -> OrderId -> Bool) -> (OrderId -> OrderId -> Bool) -> (OrderId -> OrderId -> OrderId) -> (OrderId -> OrderId -> OrderId) -> Ord OrderId OrderId -> OrderId -> Bool OrderId -> OrderId -> Ordering OrderId -> OrderId -> OrderId forall a. Eq a -> (a -> a -> Ordering) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> a) -> (a -> a -> a) -> Ord a min :: OrderId -> OrderId -> OrderId $cmin :: OrderId -> OrderId -> OrderId max :: OrderId -> OrderId -> OrderId $cmax :: OrderId -> OrderId -> OrderId >= :: OrderId -> OrderId -> Bool $c>= :: OrderId -> OrderId -> Bool > :: OrderId -> OrderId -> Bool $c> :: OrderId -> OrderId -> Bool <= :: OrderId -> OrderId -> Bool $c<= :: OrderId -> OrderId -> Bool < :: OrderId -> OrderId -> Bool $c< :: OrderId -> OrderId -> Bool compare :: OrderId -> OrderId -> Ordering $ccompare :: OrderId -> OrderId -> Ordering $cp1Ord :: Eq OrderId Ord, OrderId -> ByteString OrderId -> Builder OrderId -> Text (OrderId -> Text) -> (OrderId -> Builder) -> (OrderId -> ByteString) -> (OrderId -> Text) -> ToHttpApiData OrderId forall a. (a -> Text) -> (a -> Builder) -> (a -> ByteString) -> (a -> Text) -> ToHttpApiData a toQueryParam :: OrderId -> Text $ctoQueryParam :: OrderId -> Text toHeader :: OrderId -> ByteString $ctoHeader :: OrderId -> ByteString toEncodedUrlPiece :: OrderId -> Builder $ctoEncodedUrlPiece :: OrderId -> Builder toUrlPiece :: OrderId -> Text $ctoUrlPiece :: OrderId -> Text ToHttpApiData) instance Show OrderId where show :: OrderId -> String show (OrderId Text t) = Text -> String unpack Text t deriveJSON defaultOptions { fieldLabelModifier = snakeCase , unwrapUnaryRecords = True } ''OrderId newtype ClientOrderId = ClientOrderId { ClientOrderId -> UUID unClientOrderId :: UUID } deriving (ClientOrderId -> ClientOrderId -> Bool (ClientOrderId -> ClientOrderId -> Bool) -> (ClientOrderId -> ClientOrderId -> Bool) -> Eq ClientOrderId forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: ClientOrderId -> ClientOrderId -> Bool $c/= :: ClientOrderId -> ClientOrderId -> Bool == :: ClientOrderId -> ClientOrderId -> Bool $c== :: ClientOrderId -> ClientOrderId -> Bool Eq, Eq ClientOrderId Eq ClientOrderId -> (ClientOrderId -> ClientOrderId -> Ordering) -> (ClientOrderId -> ClientOrderId -> Bool) -> (ClientOrderId -> ClientOrderId -> Bool) -> (ClientOrderId -> ClientOrderId -> Bool) -> (ClientOrderId -> ClientOrderId -> Bool) -> (ClientOrderId -> ClientOrderId -> ClientOrderId) -> (ClientOrderId -> ClientOrderId -> ClientOrderId) -> Ord ClientOrderId ClientOrderId -> ClientOrderId -> Bool ClientOrderId -> ClientOrderId -> Ordering ClientOrderId -> ClientOrderId -> ClientOrderId forall a. Eq a -> (a -> a -> Ordering) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> a) -> (a -> a -> a) -> Ord a min :: ClientOrderId -> ClientOrderId -> ClientOrderId $cmin :: ClientOrderId -> ClientOrderId -> ClientOrderId max :: ClientOrderId -> ClientOrderId -> ClientOrderId $cmax :: ClientOrderId -> ClientOrderId -> ClientOrderId >= :: ClientOrderId -> ClientOrderId -> Bool $c>= :: ClientOrderId -> ClientOrderId -> Bool > :: ClientOrderId -> ClientOrderId -> Bool $c> :: ClientOrderId -> ClientOrderId -> Bool <= :: ClientOrderId -> ClientOrderId -> Bool $c<= :: ClientOrderId -> ClientOrderId -> Bool < :: ClientOrderId -> ClientOrderId -> Bool $c< :: ClientOrderId -> ClientOrderId -> Bool compare :: ClientOrderId -> ClientOrderId -> Ordering $ccompare :: ClientOrderId -> ClientOrderId -> Ordering $cp1Ord :: Eq ClientOrderId Ord) instance Show ClientOrderId where show :: ClientOrderId -> String show (ClientOrderId UUID t) = UUID -> String toString UUID t instance ToHttpApiData ClientOrderId where toUrlPiece :: ClientOrderId -> Text toUrlPiece = (Text "client:" Text -> Text -> Text forall a. Semigroup a => a -> a -> a <>) (Text -> Text) -> (ClientOrderId -> Text) -> ClientOrderId -> Text forall b c a. (b -> c) -> (a -> b) -> a -> c . UUID -> Text toText (UUID -> Text) -> (ClientOrderId -> UUID) -> ClientOrderId -> Text forall b c a. (b -> c) -> (a -> b) -> a -> c . ClientOrderId -> UUID unClientOrderId deriveJSON defaultOptions { unwrapUnaryRecords = True } ''ClientOrderId newtype ProductId = ProductId { ProductId -> Text unProductId :: Text } deriving (ProductId -> ProductId -> Bool (ProductId -> ProductId -> Bool) -> (ProductId -> ProductId -> Bool) -> Eq ProductId forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: ProductId -> ProductId -> Bool $c/= :: ProductId -> ProductId -> Bool == :: ProductId -> ProductId -> Bool $c== :: ProductId -> ProductId -> Bool Eq, Eq ProductId Eq ProductId -> (ProductId -> ProductId -> Ordering) -> (ProductId -> ProductId -> Bool) -> (ProductId -> ProductId -> Bool) -> (ProductId -> ProductId -> Bool) -> (ProductId -> ProductId -> Bool) -> (ProductId -> ProductId -> ProductId) -> (ProductId -> ProductId -> ProductId) -> Ord ProductId ProductId -> ProductId -> Bool ProductId -> ProductId -> Ordering ProductId -> ProductId -> ProductId forall a. Eq a -> (a -> a -> Ordering) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> a) -> (a -> a -> a) -> Ord a min :: ProductId -> ProductId -> ProductId $cmin :: ProductId -> ProductId -> ProductId max :: ProductId -> ProductId -> ProductId $cmax :: ProductId -> ProductId -> ProductId >= :: ProductId -> ProductId -> Bool $c>= :: ProductId -> ProductId -> Bool > :: ProductId -> ProductId -> Bool $c> :: ProductId -> ProductId -> Bool <= :: ProductId -> ProductId -> Bool $c<= :: ProductId -> ProductId -> Bool < :: ProductId -> ProductId -> Bool $c< :: ProductId -> ProductId -> Bool compare :: ProductId -> ProductId -> Ordering $ccompare :: ProductId -> ProductId -> Ordering $cp1Ord :: Eq ProductId Ord, ProductId -> ByteString ProductId -> Builder ProductId -> Text (ProductId -> Text) -> (ProductId -> Builder) -> (ProductId -> ByteString) -> (ProductId -> Text) -> ToHttpApiData ProductId forall a. (a -> Text) -> (a -> Builder) -> (a -> ByteString) -> (a -> Text) -> ToHttpApiData a toQueryParam :: ProductId -> Text $ctoQueryParam :: ProductId -> Text toHeader :: ProductId -> ByteString $ctoHeader :: ProductId -> ByteString toEncodedUrlPiece :: ProductId -> Builder $ctoEncodedUrlPiece :: ProductId -> Builder toUrlPiece :: ProductId -> Text $ctoUrlPiece :: ProductId -> Text ToHttpApiData, ToJSONKeyFunction [ProductId] ToJSONKeyFunction ProductId ToJSONKeyFunction ProductId -> ToJSONKeyFunction [ProductId] -> ToJSONKey ProductId forall a. ToJSONKeyFunction a -> ToJSONKeyFunction [a] -> ToJSONKey a toJSONKeyList :: ToJSONKeyFunction [ProductId] $ctoJSONKeyList :: ToJSONKeyFunction [ProductId] toJSONKey :: ToJSONKeyFunction ProductId $ctoJSONKey :: ToJSONKeyFunction ProductId ToJSONKey, FromJSONKeyFunction [ProductId] FromJSONKeyFunction ProductId FromJSONKeyFunction ProductId -> FromJSONKeyFunction [ProductId] -> FromJSONKey ProductId forall a. FromJSONKeyFunction a -> FromJSONKeyFunction [a] -> FromJSONKey a fromJSONKeyList :: FromJSONKeyFunction [ProductId] $cfromJSONKeyList :: FromJSONKeyFunction [ProductId] fromJSONKey :: FromJSONKeyFunction ProductId $cfromJSONKey :: FromJSONKeyFunction ProductId FromJSONKey) instance Show ProductId where show :: ProductId -> String show (ProductId Text t) = Text -> String unpack Text t deriveJSON defaultOptions { fieldLabelModifier = snakeCase , unwrapUnaryRecords = True } ''ProductId newtype Price = Price { Price -> Double unPrice :: Double } deriving (Price -> Price -> Bool (Price -> Price -> Bool) -> (Price -> Price -> Bool) -> Eq Price forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: Price -> Price -> Bool $c/= :: Price -> Price -> Bool == :: Price -> Price -> Bool $c== :: Price -> Price -> Bool Eq, Eq Price Eq Price -> (Price -> Price -> Ordering) -> (Price -> Price -> Bool) -> (Price -> Price -> Bool) -> (Price -> Price -> Bool) -> (Price -> Price -> Bool) -> (Price -> Price -> Price) -> (Price -> Price -> Price) -> Ord Price Price -> Price -> Bool Price -> Price -> Ordering Price -> Price -> Price forall a. Eq a -> (a -> a -> Ordering) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> a) -> (a -> a -> a) -> Ord a min :: Price -> Price -> Price $cmin :: Price -> Price -> Price max :: Price -> Price -> Price $cmax :: Price -> Price -> Price >= :: Price -> Price -> Bool $c>= :: Price -> Price -> Bool > :: Price -> Price -> Bool $c> :: Price -> Price -> Bool <= :: Price -> Price -> Bool $c<= :: Price -> Price -> Bool < :: Price -> Price -> Bool $c< :: Price -> Price -> Bool compare :: Price -> Price -> Ordering $ccompare :: Price -> Price -> Ordering $cp1Ord :: Eq Price Ord, Integer -> Price Price -> Price Price -> Price -> Price (Price -> Price -> Price) -> (Price -> Price -> Price) -> (Price -> Price -> Price) -> (Price -> Price) -> (Price -> Price) -> (Price -> Price) -> (Integer -> Price) -> Num Price forall a. (a -> a -> a) -> (a -> a -> a) -> (a -> a -> a) -> (a -> a) -> (a -> a) -> (a -> a) -> (Integer -> a) -> Num a fromInteger :: Integer -> Price $cfromInteger :: Integer -> Price signum :: Price -> Price $csignum :: Price -> Price abs :: Price -> Price $cabs :: Price -> Price negate :: Price -> Price $cnegate :: Price -> Price * :: Price -> Price -> Price $c* :: Price -> Price -> Price - :: Price -> Price -> Price $c- :: Price -> Price -> Price + :: Price -> Price -> Price $c+ :: Price -> Price -> Price Num, Price -> ByteString Price -> Builder Price -> Text (Price -> Text) -> (Price -> Builder) -> (Price -> ByteString) -> (Price -> Text) -> ToHttpApiData Price forall a. (a -> Text) -> (a -> Builder) -> (a -> ByteString) -> (a -> Text) -> ToHttpApiData a toQueryParam :: Price -> Text $ctoQueryParam :: Price -> Text toHeader :: Price -> ByteString $ctoHeader :: Price -> ByteString toEncodedUrlPiece :: Price -> Builder $ctoEncodedUrlPiece :: Price -> Builder toUrlPiece :: Price -> Text $ctoUrlPiece :: Price -> Text ToHttpApiData) instance Show Price where show :: Price -> String show (Price Double d) = String -> Double -> String forall r. PrintfType r => String -> r printf String "%.8f" Double d instance FromJSON Price where parseJSON :: Value -> Parser Price parseJSON = String -> (Text -> Parser Price) -> Value -> Parser Price forall a. String -> (Text -> Parser a) -> Value -> Parser a withText String "price" ((Text -> Parser Price) -> Value -> Parser Price) -> (Text -> Parser Price) -> Value -> Parser Price forall a b. (a -> b) -> a -> b $ \Text t -> Price -> Parser Price forall (m :: * -> *) a. Monad m => a -> m a return (Price -> Parser Price) -> (String -> Price) -> String -> Parser Price forall b c a. (b -> c) -> (a -> b) -> a -> c . Double -> Price Price (Double -> Price) -> (String -> Double) -> String -> Price forall b c a. (b -> c) -> (a -> b) -> a -> c . String -> Double forall a. Read a => String -> a read (String -> Parser Price) -> String -> Parser Price forall a b. (a -> b) -> a -> b $ Text -> String unpack Text t instance ToJSON Price where toJSON :: Price -> Value toJSON = Text -> Value A.String (Text -> Value) -> (Price -> Text) -> Price -> Value forall b c a. (b -> c) -> (a -> b) -> a -> c . String -> Text pack (String -> Text) -> (Price -> String) -> Price -> Text forall b c a. (b -> c) -> (a -> b) -> a -> c . Price -> String forall a. Show a => a -> String show newtype Size = Size { Size -> Double unSize :: Double } deriving (Size -> Size -> Bool (Size -> Size -> Bool) -> (Size -> Size -> Bool) -> Eq Size forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: Size -> Size -> Bool $c/= :: Size -> Size -> Bool == :: Size -> Size -> Bool $c== :: Size -> Size -> Bool Eq, Eq Size Eq Size -> (Size -> Size -> Ordering) -> (Size -> Size -> Bool) -> (Size -> Size -> Bool) -> (Size -> Size -> Bool) -> (Size -> Size -> Bool) -> (Size -> Size -> Size) -> (Size -> Size -> Size) -> Ord Size Size -> Size -> Bool Size -> Size -> Ordering Size -> Size -> Size forall a. Eq a -> (a -> a -> Ordering) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> a) -> (a -> a -> a) -> Ord a min :: Size -> Size -> Size $cmin :: Size -> Size -> Size max :: Size -> Size -> Size $cmax :: Size -> Size -> Size >= :: Size -> Size -> Bool $c>= :: Size -> Size -> Bool > :: Size -> Size -> Bool $c> :: Size -> Size -> Bool <= :: Size -> Size -> Bool $c<= :: Size -> Size -> Bool < :: Size -> Size -> Bool $c< :: Size -> Size -> Bool compare :: Size -> Size -> Ordering $ccompare :: Size -> Size -> Ordering $cp1Ord :: Eq Size Ord, Integer -> Size Size -> Size Size -> Size -> Size (Size -> Size -> Size) -> (Size -> Size -> Size) -> (Size -> Size -> Size) -> (Size -> Size) -> (Size -> Size) -> (Size -> Size) -> (Integer -> Size) -> Num Size forall a. (a -> a -> a) -> (a -> a -> a) -> (a -> a -> a) -> (a -> a) -> (a -> a) -> (a -> a) -> (Integer -> a) -> Num a fromInteger :: Integer -> Size $cfromInteger :: Integer -> Size signum :: Size -> Size $csignum :: Size -> Size abs :: Size -> Size $cabs :: Size -> Size negate :: Size -> Size $cnegate :: Size -> Size * :: Size -> Size -> Size $c* :: Size -> Size -> Size - :: Size -> Size -> Size $c- :: Size -> Size -> Size + :: Size -> Size -> Size $c+ :: Size -> Size -> Size Num, Size -> ByteString Size -> Builder Size -> Text (Size -> Text) -> (Size -> Builder) -> (Size -> ByteString) -> (Size -> Text) -> ToHttpApiData Size forall a. (a -> Text) -> (a -> Builder) -> (a -> ByteString) -> (a -> Text) -> ToHttpApiData a toQueryParam :: Size -> Text $ctoQueryParam :: Size -> Text toHeader :: Size -> ByteString $ctoHeader :: Size -> ByteString toEncodedUrlPiece :: Size -> Builder $ctoEncodedUrlPiece :: Size -> Builder toUrlPiece :: Size -> Text $ctoUrlPiece :: Size -> Text ToHttpApiData) instance Show Size where show :: Size -> String show (Size Double d) = String -> Double -> String forall r. PrintfType r => String -> r printf String "%.8f" Double d instance ToJSON Size where toJSON :: Size -> Value toJSON = Text -> Value A.String (Text -> Value) -> (Size -> Text) -> Size -> Value forall b c a. (b -> c) -> (a -> b) -> a -> c . String -> Text pack (String -> Text) -> (Size -> String) -> Size -> Text forall b c a. (b -> c) -> (a -> b) -> a -> c . Size -> String forall a. Show a => a -> String show instance FromJSON Size where parseJSON :: Value -> Parser Size parseJSON = String -> (Text -> Parser Size) -> Value -> Parser Size forall a. String -> (Text -> Parser a) -> Value -> Parser a withText String "size" ((Text -> Parser Size) -> Value -> Parser Size) -> (Text -> Parser Size) -> Value -> Parser Size forall a b. (a -> b) -> a -> b $ \Text t -> Size -> Parser Size forall (m :: * -> *) a. Monad m => a -> m a return (Size -> Parser Size) -> (String -> Size) -> String -> Parser Size forall b c a. (b -> c) -> (a -> b) -> a -> c . Double -> Size Size (Double -> Size) -> (String -> Double) -> String -> Size forall b c a. (b -> c) -> (a -> b) -> a -> c . String -> Double forall a. Read a => String -> a read (String -> Parser Size) -> String -> Parser Size forall a b. (a -> b) -> a -> b $ Text -> String unpack Text t newtype Volume = Volume { Volume -> Double unVolume :: Double } deriving (Volume -> Volume -> Bool (Volume -> Volume -> Bool) -> (Volume -> Volume -> Bool) -> Eq Volume forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: Volume -> Volume -> Bool $c/= :: Volume -> Volume -> Bool == :: Volume -> Volume -> Bool $c== :: Volume -> Volume -> Bool Eq, Eq Volume Eq Volume -> (Volume -> Volume -> Ordering) -> (Volume -> Volume -> Bool) -> (Volume -> Volume -> Bool) -> (Volume -> Volume -> Bool) -> (Volume -> Volume -> Bool) -> (Volume -> Volume -> Volume) -> (Volume -> Volume -> Volume) -> Ord Volume Volume -> Volume -> Bool Volume -> Volume -> Ordering Volume -> Volume -> Volume forall a. Eq a -> (a -> a -> Ordering) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> a) -> (a -> a -> a) -> Ord a min :: Volume -> Volume -> Volume $cmin :: Volume -> Volume -> Volume max :: Volume -> Volume -> Volume $cmax :: Volume -> Volume -> Volume >= :: Volume -> Volume -> Bool $c>= :: Volume -> Volume -> Bool > :: Volume -> Volume -> Bool $c> :: Volume -> Volume -> Bool <= :: Volume -> Volume -> Bool $c<= :: Volume -> Volume -> Bool < :: Volume -> Volume -> Bool $c< :: Volume -> Volume -> Bool compare :: Volume -> Volume -> Ordering $ccompare :: Volume -> Volume -> Ordering $cp1Ord :: Eq Volume Ord) instance Show Volume where show :: Volume -> String show (Volume Double d) = String -> Double -> String forall r. PrintfType r => String -> r printf String "%.8f" Double d instance FromJSON Volume where parseJSON :: Value -> Parser Volume parseJSON = String -> (Text -> Parser Volume) -> Value -> Parser Volume forall a. String -> (Text -> Parser a) -> Value -> Parser a withText String "volume" ((Text -> Parser Volume) -> Value -> Parser Volume) -> (Text -> Parser Volume) -> Value -> Parser Volume forall a b. (a -> b) -> a -> b $ \Text t -> Volume -> Parser Volume forall (m :: * -> *) a. Monad m => a -> m a return (Volume -> Parser Volume) -> (String -> Volume) -> String -> Parser Volume forall b c a. (b -> c) -> (a -> b) -> a -> c . 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 -> Parser Volume) -> String -> Parser Volume forall a b. (a -> b) -> a -> b $ Text -> String unpack Text t instance ToJSON Volume where toJSON :: Volume -> Value toJSON = Text -> Value A.String (Text -> Value) -> (Volume -> Text) -> Volume -> Value forall b c a. (b -> c) -> (a -> b) -> a -> c . String -> Text pack (String -> Text) -> (Volume -> String) -> Volume -> Text forall b c a. (b -> c) -> (a -> b) -> a -> c . Volume -> String forall a. Show a => a -> String show newtype TradeId = TradeId Int deriving (TradeId -> TradeId -> Bool (TradeId -> TradeId -> Bool) -> (TradeId -> TradeId -> Bool) -> Eq TradeId forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: TradeId -> TradeId -> Bool $c/= :: TradeId -> TradeId -> Bool == :: TradeId -> TradeId -> Bool $c== :: TradeId -> TradeId -> Bool Eq, Int -> TradeId -> ShowS [TradeId] -> ShowS TradeId -> String (Int -> TradeId -> ShowS) -> (TradeId -> String) -> ([TradeId] -> ShowS) -> Show TradeId forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [TradeId] -> ShowS $cshowList :: [TradeId] -> ShowS show :: TradeId -> String $cshow :: TradeId -> String showsPrec :: Int -> TradeId -> ShowS $cshowsPrec :: Int -> TradeId -> ShowS Show) deriveJSON defaultOptions { fieldLabelModifier = snakeCase } ''TradeId newtype Funds = Funds Double deriving (Funds -> Funds -> Bool (Funds -> Funds -> Bool) -> (Funds -> Funds -> Bool) -> Eq Funds forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: Funds -> Funds -> Bool $c/= :: Funds -> Funds -> Bool == :: Funds -> Funds -> Bool $c== :: Funds -> Funds -> Bool Eq, Eq Funds Eq Funds -> (Funds -> Funds -> Ordering) -> (Funds -> Funds -> Bool) -> (Funds -> Funds -> Bool) -> (Funds -> Funds -> Bool) -> (Funds -> Funds -> Bool) -> (Funds -> Funds -> Funds) -> (Funds -> Funds -> Funds) -> Ord Funds Funds -> Funds -> Bool Funds -> Funds -> Ordering Funds -> Funds -> Funds forall a. Eq a -> (a -> a -> Ordering) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> a) -> (a -> a -> a) -> Ord a min :: Funds -> Funds -> Funds $cmin :: Funds -> Funds -> Funds max :: Funds -> Funds -> Funds $cmax :: Funds -> Funds -> Funds >= :: Funds -> Funds -> Bool $c>= :: Funds -> Funds -> Bool > :: Funds -> Funds -> Bool $c> :: Funds -> Funds -> Bool <= :: Funds -> Funds -> Bool $c<= :: Funds -> Funds -> Bool < :: Funds -> Funds -> Bool $c< :: Funds -> Funds -> Bool compare :: Funds -> Funds -> Ordering $ccompare :: Funds -> Funds -> Ordering $cp1Ord :: Eq Funds Ord, Funds -> ByteString Funds -> Builder Funds -> Text (Funds -> Text) -> (Funds -> Builder) -> (Funds -> ByteString) -> (Funds -> Text) -> ToHttpApiData Funds forall a. (a -> Text) -> (a -> Builder) -> (a -> ByteString) -> (a -> Text) -> ToHttpApiData a toQueryParam :: Funds -> Text $ctoQueryParam :: Funds -> Text toHeader :: Funds -> ByteString $ctoHeader :: Funds -> ByteString toEncodedUrlPiece :: Funds -> Builder $ctoEncodedUrlPiece :: Funds -> Builder toUrlPiece :: Funds -> Text $ctoUrlPiece :: Funds -> Text ToHttpApiData) instance Show Funds where show :: Funds -> String show (Funds Double d) = String -> Double -> String forall r. PrintfType r => String -> r printf String "%.16f" Double d instance ToJSON Funds where toJSON :: Funds -> Value toJSON = Text -> Value A.String (Text -> Value) -> (Funds -> Text) -> Funds -> Value forall b c a. (b -> c) -> (a -> b) -> a -> c . String -> Text pack (String -> Text) -> (Funds -> String) -> Funds -> Text forall b c a. (b -> c) -> (a -> b) -> a -> c . Funds -> String forall a. Show a => a -> String show instance FromJSON Funds where parseJSON :: Value -> Parser Funds parseJSON = String -> (Text -> Parser Funds) -> Value -> Parser Funds forall a. String -> (Text -> Parser a) -> Value -> Parser a withText String "funds" ((Text -> Parser Funds) -> Value -> Parser Funds) -> (Text -> Parser Funds) -> Value -> Parser Funds forall a b. (a -> b) -> a -> b $ \Text t -> Funds -> Parser Funds forall (m :: * -> *) a. Monad m => a -> m a return (Funds -> Parser Funds) -> (String -> Funds) -> String -> Parser Funds forall b c a. (b -> c) -> (a -> b) -> a -> c . Double -> Funds Funds (Double -> Funds) -> (String -> Double) -> String -> Funds forall b c a. (b -> c) -> (a -> b) -> a -> c . String -> Double forall a. Read a => String -> a read (String -> Parser Funds) -> String -> Parser Funds forall a b. (a -> b) -> a -> b $ Text -> String unpack Text t data OrderType = Limit | Market deriving (OrderType -> OrderType -> Bool (OrderType -> OrderType -> Bool) -> (OrderType -> OrderType -> Bool) -> Eq OrderType forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: OrderType -> OrderType -> Bool $c/= :: OrderType -> OrderType -> Bool == :: OrderType -> OrderType -> Bool $c== :: OrderType -> OrderType -> Bool Eq, Eq OrderType Eq OrderType -> (OrderType -> OrderType -> Ordering) -> (OrderType -> OrderType -> Bool) -> (OrderType -> OrderType -> Bool) -> (OrderType -> OrderType -> Bool) -> (OrderType -> OrderType -> Bool) -> (OrderType -> OrderType -> OrderType) -> (OrderType -> OrderType -> OrderType) -> Ord OrderType OrderType -> OrderType -> Bool OrderType -> OrderType -> Ordering OrderType -> OrderType -> OrderType forall a. Eq a -> (a -> a -> Ordering) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> a) -> (a -> a -> a) -> Ord a min :: OrderType -> OrderType -> OrderType $cmin :: OrderType -> OrderType -> OrderType max :: OrderType -> OrderType -> OrderType $cmax :: OrderType -> OrderType -> OrderType >= :: OrderType -> OrderType -> Bool $c>= :: OrderType -> OrderType -> Bool > :: OrderType -> OrderType -> Bool $c> :: OrderType -> OrderType -> Bool <= :: OrderType -> OrderType -> Bool $c<= :: OrderType -> OrderType -> Bool < :: OrderType -> OrderType -> Bool $c< :: OrderType -> OrderType -> Bool compare :: OrderType -> OrderType -> Ordering $ccompare :: OrderType -> OrderType -> Ordering $cp1Ord :: Eq OrderType Ord, Int -> OrderType -> ShowS [OrderType] -> ShowS OrderType -> String (Int -> OrderType -> ShowS) -> (OrderType -> String) -> ([OrderType] -> ShowS) -> Show OrderType forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [OrderType] -> ShowS $cshowList :: [OrderType] -> ShowS show :: OrderType -> String $cshow :: OrderType -> String showsPrec :: Int -> OrderType -> ShowS $cshowsPrec :: Int -> OrderType -> ShowS Show) instance ToHttpApiData OrderType where toUrlPiece :: OrderType -> Text toUrlPiece = Text -> Text toLower (Text -> Text) -> (OrderType -> Text) -> OrderType -> Text forall b c a. (b -> c) -> (a -> b) -> a -> c . String -> Text pack (String -> Text) -> (OrderType -> String) -> OrderType -> Text forall b c a. (b -> c) -> (a -> b) -> a -> c . OrderType -> String forall a. Show a => a -> String show toQueryParam :: OrderType -> Text toQueryParam = Text -> Text toLower (Text -> Text) -> (OrderType -> Text) -> OrderType -> Text forall b c a. (b -> c) -> (a -> b) -> a -> c . String -> Text pack (String -> Text) -> (OrderType -> String) -> OrderType -> Text forall b c a. (b -> c) -> (a -> b) -> a -> c . OrderType -> String forall a. Show a => a -> String show deriveJSON defaultOptions {constructorTagModifier = camelCase} ''OrderType newtype CreatedAt = CreatedAt UTCTime deriving (CreatedAt -> CreatedAt -> Bool (CreatedAt -> CreatedAt -> Bool) -> (CreatedAt -> CreatedAt -> Bool) -> Eq CreatedAt forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: CreatedAt -> CreatedAt -> Bool $c/= :: CreatedAt -> CreatedAt -> Bool == :: CreatedAt -> CreatedAt -> Bool $c== :: CreatedAt -> CreatedAt -> Bool Eq, Int -> CreatedAt -> ShowS [CreatedAt] -> ShowS CreatedAt -> String (Int -> CreatedAt -> ShowS) -> (CreatedAt -> String) -> ([CreatedAt] -> ShowS) -> Show CreatedAt forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [CreatedAt] -> ShowS $cshowList :: [CreatedAt] -> ShowS show :: CreatedAt -> String $cshow :: CreatedAt -> String showsPrec :: Int -> CreatedAt -> ShowS $cshowsPrec :: Int -> CreatedAt -> ShowS Show, Eq CreatedAt Eq CreatedAt -> (CreatedAt -> CreatedAt -> Ordering) -> (CreatedAt -> CreatedAt -> Bool) -> (CreatedAt -> CreatedAt -> Bool) -> (CreatedAt -> CreatedAt -> Bool) -> (CreatedAt -> CreatedAt -> Bool) -> (CreatedAt -> CreatedAt -> CreatedAt) -> (CreatedAt -> CreatedAt -> CreatedAt) -> Ord CreatedAt CreatedAt -> CreatedAt -> Bool CreatedAt -> CreatedAt -> Ordering CreatedAt -> CreatedAt -> CreatedAt forall a. Eq a -> (a -> a -> Ordering) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> a) -> (a -> a -> a) -> Ord a min :: CreatedAt -> CreatedAt -> CreatedAt $cmin :: CreatedAt -> CreatedAt -> CreatedAt max :: CreatedAt -> CreatedAt -> CreatedAt $cmax :: CreatedAt -> CreatedAt -> CreatedAt >= :: CreatedAt -> CreatedAt -> Bool $c>= :: CreatedAt -> CreatedAt -> Bool > :: CreatedAt -> CreatedAt -> Bool $c> :: CreatedAt -> CreatedAt -> Bool <= :: CreatedAt -> CreatedAt -> Bool $c<= :: CreatedAt -> CreatedAt -> Bool < :: CreatedAt -> CreatedAt -> Bool $c< :: CreatedAt -> CreatedAt -> Bool compare :: CreatedAt -> CreatedAt -> Ordering $ccompare :: CreatedAt -> CreatedAt -> Ordering $cp1Ord :: Eq CreatedAt Ord) deriveJSON defaultOptions ''CreatedAt filterOrderFieldName :: String -> String filterOrderFieldName :: ShowS filterOrderFieldName String "order_type" = String "type" filterOrderFieldName String s = String s data Candle = Candle { Candle -> UTCTime time :: UTCTime , Candle -> Price low :: Price , Candle -> Price high :: Price , Candle -> Price open :: Price , Candle -> Price close :: Price , Candle -> Double volume :: Double } deriving (Candle -> Candle -> Bool (Candle -> Candle -> Bool) -> (Candle -> Candle -> Bool) -> Eq Candle forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: Candle -> Candle -> Bool $c/= :: Candle -> Candle -> Bool == :: Candle -> Candle -> Bool $c== :: Candle -> Candle -> Bool Eq, Int -> Candle -> ShowS [Candle] -> ShowS Candle -> String (Int -> Candle -> ShowS) -> (Candle -> String) -> ([Candle] -> ShowS) -> Show Candle forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [Candle] -> ShowS $cshowList :: [Candle] -> ShowS show :: Candle -> String $cshow :: Candle -> String showsPrec :: Int -> Candle -> ShowS $cshowsPrec :: Int -> Candle -> ShowS Show) instance FromJSON Candle where parseJSON :: Value -> Parser Candle parseJSON = String -> (Array -> Parser Candle) -> Value -> Parser Candle forall a. String -> (Array -> Parser a) -> Value -> Parser a withArray String "candle" ((Array -> Parser Candle) -> Value -> Parser Candle) -> (Array -> Parser Candle) -> Value -> Parser Candle forall a b. (a -> b) -> a -> b $ \Array a -> do let l :: [Value] l = Array -> [Value] forall a. Vector a -> [a] V.toList Array a UTCTime t <- POSIXTime -> UTCTime posixSecondsToUTCTime (POSIXTime -> UTCTime) -> Parser POSIXTime -> Parser UTCTime forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Value -> Parser POSIXTime forall a. FromJSON a => Value -> Parser a parseJSON ([Value] -> Value forall a. [a] -> a head [Value] l) Price lw <- Double -> Price Price (Double -> Price) -> Parser Double -> Parser Price forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Value -> Parser Double forall a. FromJSON a => Value -> Parser a parseJSON ([Value] l [Value] -> Int -> Value forall a. [a] -> Int -> a !! Int 1) Price h <- Double -> Price Price (Double -> Price) -> Parser Double -> Parser Price forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Value -> Parser Double forall a. FromJSON a => Value -> Parser a parseJSON ([Value] l [Value] -> Int -> Value forall a. [a] -> Int -> a !! Int 2) Price o <- Double -> Price Price (Double -> Price) -> Parser Double -> Parser Price forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Value -> Parser Double forall a. FromJSON a => Value -> Parser a parseJSON ([Value] l [Value] -> Int -> Value forall a. [a] -> Int -> a !! Int 3) Price c <- Double -> Price Price (Double -> Price) -> Parser Double -> Parser Price forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Value -> Parser Double forall a. FromJSON a => Value -> Parser a parseJSON ([Value] l [Value] -> Int -> Value forall a. [a] -> Int -> a !! Int 4) Double v <- Value -> Parser Double forall a. FromJSON a => Value -> Parser a parseJSON (Value -> Parser Double) -> Value -> Parser Double forall a b. (a -> b) -> a -> b $ [Value] l [Value] -> Int -> Value forall a. [a] -> Int -> a !! Int 5 Candle -> Parser Candle forall (m :: * -> *) a. Monad m => a -> m a return (Candle -> Parser Candle) -> Candle -> Parser Candle forall a b. (a -> b) -> a -> b $ UTCTime -> Price -> Price -> Price -> Price -> Double -> Candle Candle UTCTime t Price lw Price h Price o Price c Double v data CandleGranularity = Minute | FiveMinutes | FifteenMinutes | Hour | SixHours | Day deriving (CandleGranularity -> CandleGranularity -> Bool (CandleGranularity -> CandleGranularity -> Bool) -> (CandleGranularity -> CandleGranularity -> Bool) -> Eq CandleGranularity forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: CandleGranularity -> CandleGranularity -> Bool $c/= :: CandleGranularity -> CandleGranularity -> Bool == :: CandleGranularity -> CandleGranularity -> Bool $c== :: CandleGranularity -> CandleGranularity -> Bool Eq, Eq CandleGranularity Eq CandleGranularity -> (CandleGranularity -> CandleGranularity -> Ordering) -> (CandleGranularity -> CandleGranularity -> Bool) -> (CandleGranularity -> CandleGranularity -> Bool) -> (CandleGranularity -> CandleGranularity -> Bool) -> (CandleGranularity -> CandleGranularity -> Bool) -> (CandleGranularity -> CandleGranularity -> CandleGranularity) -> (CandleGranularity -> CandleGranularity -> CandleGranularity) -> Ord CandleGranularity CandleGranularity -> CandleGranularity -> Bool CandleGranularity -> CandleGranularity -> Ordering CandleGranularity -> CandleGranularity -> CandleGranularity forall a. Eq a -> (a -> a -> Ordering) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> a) -> (a -> a -> a) -> Ord a min :: CandleGranularity -> CandleGranularity -> CandleGranularity $cmin :: CandleGranularity -> CandleGranularity -> CandleGranularity max :: CandleGranularity -> CandleGranularity -> CandleGranularity $cmax :: CandleGranularity -> CandleGranularity -> CandleGranularity >= :: CandleGranularity -> CandleGranularity -> Bool $c>= :: CandleGranularity -> CandleGranularity -> Bool > :: CandleGranularity -> CandleGranularity -> Bool $c> :: CandleGranularity -> CandleGranularity -> Bool <= :: CandleGranularity -> CandleGranularity -> Bool $c<= :: CandleGranularity -> CandleGranularity -> Bool < :: CandleGranularity -> CandleGranularity -> Bool $c< :: CandleGranularity -> CandleGranularity -> Bool compare :: CandleGranularity -> CandleGranularity -> Ordering $ccompare :: CandleGranularity -> CandleGranularity -> Ordering $cp1Ord :: Eq CandleGranularity Ord, Int -> CandleGranularity -> ShowS [CandleGranularity] -> ShowS CandleGranularity -> String (Int -> CandleGranularity -> ShowS) -> (CandleGranularity -> String) -> ([CandleGranularity] -> ShowS) -> Show CandleGranularity forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [CandleGranularity] -> ShowS $cshowList :: [CandleGranularity] -> ShowS show :: CandleGranularity -> String $cshow :: CandleGranularity -> String showsPrec :: Int -> CandleGranularity -> ShowS $cshowsPrec :: Int -> CandleGranularity -> ShowS Show) instance ToHttpApiData CandleGranularity where toUrlPiece :: CandleGranularity -> Text toUrlPiece CandleGranularity Minute = Text "60" toUrlPiece CandleGranularity FiveMinutes = Text "300" toUrlPiece CandleGranularity FifteenMinutes = Text "900" toUrlPiece CandleGranularity Hour = Text "3600" toUrlPiece CandleGranularity SixHours = Text "21600" toUrlPiece CandleGranularity Day = Text "86400" toQueryParam :: CandleGranularity -> Text toQueryParam CandleGranularity Minute = Text "60" toQueryParam CandleGranularity FiveMinutes = Text "300" toQueryParam CandleGranularity FifteenMinutes = Text "900" toQueryParam CandleGranularity Hour = Text "3600" toQueryParam CandleGranularity SixHours = Text "21600" toQueryParam CandleGranularity Day = Text "86400" data TwentyFourHourStats = TwentyFourHourStats { TwentyFourHourStats -> Price open24 :: Price , TwentyFourHourStats -> Price high24 :: Price , TwentyFourHourStats -> Price low24 :: Price , TwentyFourHourStats -> Volume volume24 :: Volume , TwentyFourHourStats -> Price last24 :: Price , TwentyFourHourStats -> Volume volume30 :: Volume } deriving (TwentyFourHourStats -> TwentyFourHourStats -> Bool (TwentyFourHourStats -> TwentyFourHourStats -> Bool) -> (TwentyFourHourStats -> TwentyFourHourStats -> Bool) -> Eq TwentyFourHourStats forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: TwentyFourHourStats -> TwentyFourHourStats -> Bool $c/= :: TwentyFourHourStats -> TwentyFourHourStats -> Bool == :: TwentyFourHourStats -> TwentyFourHourStats -> Bool $c== :: TwentyFourHourStats -> TwentyFourHourStats -> Bool Eq, Int -> TwentyFourHourStats -> ShowS [TwentyFourHourStats] -> ShowS TwentyFourHourStats -> String (Int -> TwentyFourHourStats -> ShowS) -> (TwentyFourHourStats -> String) -> ([TwentyFourHourStats] -> ShowS) -> Show TwentyFourHourStats forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [TwentyFourHourStats] -> ShowS $cshowList :: [TwentyFourHourStats] -> ShowS show :: TwentyFourHourStats -> String $cshow :: TwentyFourHourStats -> String showsPrec :: Int -> TwentyFourHourStats -> ShowS $cshowsPrec :: Int -> TwentyFourHourStats -> ShowS Show) deriveJSON defaultOptions { fieldLabelModifier = init . init } ''TwentyFourHourStats data CurrencyDetails = CurrencyDetails { CurrencyDetails -> Text cdType :: Text , CurrencyDetails -> Maybe Text symbol :: Maybe Text , CurrencyDetails -> Maybe Int networkConfirmations :: Maybe Int , CurrencyDetails -> Maybe Int sortOrder :: Maybe Int , CurrencyDetails -> Maybe Text cryptoAddressLink :: Maybe Text , CurrencyDetails -> [Text] pushPaymentMethods :: [Text] , CurrencyDetails -> Maybe [Text] groupTypes :: Maybe [Text] , CurrencyDetails -> Maybe Double maxPrecision :: Maybe Double , CurrencyDetails -> Maybe Double maxWithdrawalAmount :: Maybe Double } deriving (CurrencyDetails -> CurrencyDetails -> Bool (CurrencyDetails -> CurrencyDetails -> Bool) -> (CurrencyDetails -> CurrencyDetails -> Bool) -> Eq CurrencyDetails forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: CurrencyDetails -> CurrencyDetails -> Bool $c/= :: CurrencyDetails -> CurrencyDetails -> Bool == :: CurrencyDetails -> CurrencyDetails -> Bool $c== :: CurrencyDetails -> CurrencyDetails -> Bool Eq, Int -> CurrencyDetails -> ShowS [CurrencyDetails] -> ShowS CurrencyDetails -> String (Int -> CurrencyDetails -> ShowS) -> (CurrencyDetails -> String) -> ([CurrencyDetails] -> ShowS) -> Show CurrencyDetails forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [CurrencyDetails] -> ShowS $cshowList :: [CurrencyDetails] -> ShowS show :: CurrencyDetails -> String $cshow :: CurrencyDetails -> String showsPrec :: Int -> CurrencyDetails -> ShowS $cshowsPrec :: Int -> CurrencyDetails -> ShowS Show) instance FromJSON CurrencyDetails where parseJSON :: Value -> Parser CurrencyDetails parseJSON = String -> (Object -> Parser CurrencyDetails) -> Value -> Parser CurrencyDetails forall a. String -> (Object -> Parser a) -> Value -> Parser a withObject String "currency details" ((Object -> Parser CurrencyDetails) -> Value -> Parser CurrencyDetails) -> (Object -> Parser CurrencyDetails) -> Value -> Parser CurrencyDetails forall a b. (a -> b) -> a -> b $ \Object o -> Text -> Maybe Text -> Maybe Int -> Maybe Int -> Maybe Text -> [Text] -> Maybe [Text] -> Maybe Double -> Maybe Double -> CurrencyDetails CurrencyDetails (Text -> Maybe Text -> Maybe Int -> Maybe Int -> Maybe Text -> [Text] -> Maybe [Text] -> Maybe Double -> Maybe Double -> CurrencyDetails) -> Parser Text -> Parser (Maybe Text -> Maybe Int -> Maybe Int -> Maybe Text -> [Text] -> Maybe [Text] -> Maybe Double -> Maybe Double -> CurrencyDetails) 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 "type" Parser (Maybe Text -> Maybe Int -> Maybe Int -> Maybe Text -> [Text] -> Maybe [Text] -> Maybe Double -> Maybe Double -> CurrencyDetails) -> Parser (Maybe Text) -> Parser (Maybe Int -> Maybe Int -> Maybe Text -> [Text] -> Maybe [Text] -> Maybe Double -> Maybe Double -> CurrencyDetails) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> Object o Object -> Text -> Parser (Maybe Text) forall a. FromJSON a => Object -> Text -> Parser (Maybe a) .:? Text "symbol" Parser (Maybe Int -> Maybe Int -> Maybe Text -> [Text] -> Maybe [Text] -> Maybe Double -> Maybe Double -> CurrencyDetails) -> Parser (Maybe Int) -> Parser (Maybe Int -> Maybe Text -> [Text] -> Maybe [Text] -> Maybe Double -> Maybe Double -> CurrencyDetails) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> Object o Object -> Text -> Parser (Maybe Int) forall a. FromJSON a => Object -> Text -> Parser (Maybe a) .:? Text "network_confirmations" Parser (Maybe Int -> Maybe Text -> [Text] -> Maybe [Text] -> Maybe Double -> Maybe Double -> CurrencyDetails) -> Parser (Maybe Int) -> Parser (Maybe Text -> [Text] -> Maybe [Text] -> Maybe Double -> Maybe Double -> CurrencyDetails) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> Object o Object -> Text -> Parser (Maybe Int) forall a. FromJSON a => Object -> Text -> Parser (Maybe a) .:? Text "set_order" Parser (Maybe Text -> [Text] -> Maybe [Text] -> Maybe Double -> Maybe Double -> CurrencyDetails) -> Parser (Maybe Text) -> Parser ([Text] -> Maybe [Text] -> Maybe Double -> Maybe Double -> CurrencyDetails) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> Object o Object -> Text -> Parser (Maybe Text) forall a. FromJSON a => Object -> Text -> Parser (Maybe a) .:? Text "crypto_address_link" Parser ([Text] -> Maybe [Text] -> Maybe Double -> Maybe Double -> CurrencyDetails) -> Parser [Text] -> Parser (Maybe [Text] -> Maybe Double -> Maybe Double -> CurrencyDetails) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> Object o Object -> Text -> Parser [Text] forall a. FromJSON a => Object -> Text -> Parser a .: Text "push_payment_methods" Parser (Maybe [Text] -> Maybe Double -> Maybe Double -> CurrencyDetails) -> Parser (Maybe [Text]) -> Parser (Maybe Double -> Maybe Double -> CurrencyDetails) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> Object o Object -> Text -> Parser (Maybe [Text]) forall a. FromJSON a => Object -> Text -> Parser (Maybe a) .:? Text "group_types" Parser (Maybe Double -> Maybe Double -> CurrencyDetails) -> Parser (Maybe Double) -> Parser (Maybe Double -> CurrencyDetails) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> Object o Object -> Text -> Parser (Maybe Double) forall a. FromJSON a => Object -> Text -> Parser (Maybe a) .:? Text "max_precision" Parser (Maybe Double -> CurrencyDetails) -> Parser (Maybe Double) -> Parser CurrencyDetails forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> Object o Object -> Text -> Parser (Maybe Double) forall a. FromJSON a => Object -> Text -> Parser (Maybe a) .:? Text "max_withdrawal_amount" newtype CurrencyType = CurrencyType Text deriving (CurrencyType -> CurrencyType -> Bool (CurrencyType -> CurrencyType -> Bool) -> (CurrencyType -> CurrencyType -> Bool) -> Eq CurrencyType forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: CurrencyType -> CurrencyType -> Bool $c/= :: CurrencyType -> CurrencyType -> Bool == :: CurrencyType -> CurrencyType -> Bool $c== :: CurrencyType -> CurrencyType -> Bool Eq, Eq CurrencyType Eq CurrencyType -> (CurrencyType -> CurrencyType -> Ordering) -> (CurrencyType -> CurrencyType -> Bool) -> (CurrencyType -> CurrencyType -> Bool) -> (CurrencyType -> CurrencyType -> Bool) -> (CurrencyType -> CurrencyType -> Bool) -> (CurrencyType -> CurrencyType -> CurrencyType) -> (CurrencyType -> CurrencyType -> CurrencyType) -> Ord CurrencyType CurrencyType -> CurrencyType -> Bool CurrencyType -> CurrencyType -> Ordering CurrencyType -> CurrencyType -> CurrencyType forall a. Eq a -> (a -> a -> Ordering) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> a) -> (a -> a -> a) -> Ord a min :: CurrencyType -> CurrencyType -> CurrencyType $cmin :: CurrencyType -> CurrencyType -> CurrencyType max :: CurrencyType -> CurrencyType -> CurrencyType $cmax :: CurrencyType -> CurrencyType -> CurrencyType >= :: CurrencyType -> CurrencyType -> Bool $c>= :: CurrencyType -> CurrencyType -> Bool > :: CurrencyType -> CurrencyType -> Bool $c> :: CurrencyType -> CurrencyType -> Bool <= :: CurrencyType -> CurrencyType -> Bool $c<= :: CurrencyType -> CurrencyType -> Bool < :: CurrencyType -> CurrencyType -> Bool $c< :: CurrencyType -> CurrencyType -> Bool compare :: CurrencyType -> CurrencyType -> Ordering $ccompare :: CurrencyType -> CurrencyType -> Ordering $cp1Ord :: Eq CurrencyType Ord, CurrencyType -> ByteString CurrencyType -> Builder CurrencyType -> Text (CurrencyType -> Text) -> (CurrencyType -> Builder) -> (CurrencyType -> ByteString) -> (CurrencyType -> Text) -> ToHttpApiData CurrencyType forall a. (a -> Text) -> (a -> Builder) -> (a -> ByteString) -> (a -> Text) -> ToHttpApiData a toQueryParam :: CurrencyType -> Text $ctoQueryParam :: CurrencyType -> Text toHeader :: CurrencyType -> ByteString $ctoHeader :: CurrencyType -> ByteString toEncodedUrlPiece :: CurrencyType -> Builder $ctoEncodedUrlPiece :: CurrencyType -> Builder toUrlPiece :: CurrencyType -> Text $ctoUrlPiece :: CurrencyType -> Text ToHttpApiData, FromJSONKeyFunction [CurrencyType] FromJSONKeyFunction CurrencyType FromJSONKeyFunction CurrencyType -> FromJSONKeyFunction [CurrencyType] -> FromJSONKey CurrencyType forall a. FromJSONKeyFunction a -> FromJSONKeyFunction [a] -> FromJSONKey a fromJSONKeyList :: FromJSONKeyFunction [CurrencyType] $cfromJSONKeyList :: FromJSONKeyFunction [CurrencyType] fromJSONKey :: FromJSONKeyFunction CurrencyType $cfromJSONKey :: FromJSONKeyFunction CurrencyType FromJSONKey) instance Show CurrencyType where show :: CurrencyType -> String show (CurrencyType Text c) = Text -> String unpack Text c deriveJSON defaultOptions { fieldLabelModifier = snakeCase , unwrapUnaryRecords = True } ''CurrencyType data Currency = Currency { Currency -> Text id :: Text , Currency -> Text name :: Text , Currency -> Double minSize :: Double , Currency -> Text status :: Text , Currency -> Maybe Text message :: Maybe Text , Currency -> CurrencyDetails details :: CurrencyDetails } 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) instance FromJSON Currency where parseJSON :: Value -> Parser Currency parseJSON = String -> (Object -> Parser Currency) -> Value -> Parser Currency forall a. String -> (Object -> Parser a) -> Value -> Parser a withObject String "currency" ((Object -> Parser Currency) -> Value -> Parser Currency) -> (Object -> Parser Currency) -> Value -> Parser Currency forall a b. (a -> b) -> a -> b $ \Object o -> Text -> Text -> Double -> Text -> Maybe Text -> CurrencyDetails -> Currency Currency (Text -> Text -> Double -> Text -> Maybe Text -> CurrencyDetails -> Currency) -> Parser Text -> Parser (Text -> Double -> Text -> Maybe Text -> CurrencyDetails -> 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 "id" Parser (Text -> Double -> Text -> Maybe Text -> CurrencyDetails -> Currency) -> Parser Text -> Parser (Double -> Text -> Maybe Text -> CurrencyDetails -> Currency) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> Object o Object -> Text -> Parser Text forall a. FromJSON a => Object -> Text -> Parser a .: Text "name" Parser (Double -> Text -> Maybe Text -> CurrencyDetails -> Currency) -> Parser Double -> Parser (Text -> Maybe Text -> CurrencyDetails -> Currency) 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 "min_size") Parser (Text -> Maybe Text -> CurrencyDetails -> Currency) -> Parser Text -> Parser (Maybe Text -> CurrencyDetails -> Currency) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> Object o Object -> Text -> Parser Text forall a. FromJSON a => Object -> Text -> Parser a .: Text "status" Parser (Maybe Text -> CurrencyDetails -> Currency) -> Parser (Maybe Text) -> Parser (CurrencyDetails -> Currency) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> Object o Object -> Text -> Parser (Maybe Text) forall a. FromJSON a => Object -> Text -> Parser (Maybe a) .:? Text "message" Parser (CurrencyDetails -> Currency) -> Parser CurrencyDetails -> Parser Currency forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> Object o Object -> Text -> Parser CurrencyDetails forall a. FromJSON a => Object -> Text -> Parser a .: Text "details" newtype CryptoAddress = CryptoAddress Text deriving CryptoAddress -> ByteString CryptoAddress -> Builder CryptoAddress -> Text (CryptoAddress -> Text) -> (CryptoAddress -> Builder) -> (CryptoAddress -> ByteString) -> (CryptoAddress -> Text) -> ToHttpApiData CryptoAddress forall a. (a -> Text) -> (a -> Builder) -> (a -> ByteString) -> (a -> Text) -> ToHttpApiData a toQueryParam :: CryptoAddress -> Text $ctoQueryParam :: CryptoAddress -> Text toHeader :: CryptoAddress -> ByteString $ctoHeader :: CryptoAddress -> ByteString toEncodedUrlPiece :: CryptoAddress -> Builder $ctoEncodedUrlPiece :: CryptoAddress -> Builder toUrlPiece :: CryptoAddress -> Text $ctoUrlPiece :: CryptoAddress -> Text ToHttpApiData instance Show CryptoAddress where show :: CryptoAddress -> String show (CryptoAddress Text ca) = Text -> String unpack Text ca deriveJSON defaultOptions { fieldLabelModifier = snakeCase , unwrapUnaryRecords = True } ''CryptoAddress