{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveFoldable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DeriveTraversable #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE TypeFamilies #-}
{-# OPTIONS_GHC -fno-warn-unused-matches -fno-warn-unused-binds -fno-warn-unused-imports #-}
module BitMEX.Model where
import BitMEX.Core
import BitMEX.MimeTypes
import Data.Aeson ((.:),(.:!),(.:?),(.=))
import qualified Control.Arrow as P (left)
import qualified Data.Aeson as A
import qualified Data.ByteString as B
import qualified Data.ByteString.Lazy as BL
import qualified Data.Data as P (Data, Typeable)
import qualified Data.Foldable as P
import qualified Data.HashMap.Lazy as HM
import qualified Data.Map as Map
import qualified Data.Maybe as P
import qualified Data.Set as Set
import qualified Data.Text as T
import qualified Data.Text.Encoding as T
import qualified Data.Time as TI
import qualified Web.FormUrlEncoded as WH
import qualified Web.HttpApiData as WH
import Control.Applicative ((<|>))
import Control.Applicative (Alternative)
import Data.Text (Text)
import Prelude (($), (.),(<$>),(<*>),(>>=),(=<<),Maybe(..),Bool(..),Char,Double,FilePath,Float,Int,Integer,String,fmap,undefined,mempty,maybe,pure,Monad,Applicative,Functor)
import qualified Prelude as P
data APIKey = APIKey
{ aPIKeyId :: !(Text)
, aPIKeySecret :: !(Text)
, aPIKeyName :: !(Text)
, aPIKeyNonce :: !(Double)
, aPIKeyCidr :: !(Maybe Text)
, aPIKeyPermissions :: !(Maybe [XAny])
, aPIKeyEnabled :: !(Maybe Bool)
, aPIKeyUserId :: !(Double)
, aPIKeyCreated :: !(Maybe DateTime)
} deriving (P.Show, P.Eq, P.Typeable)
instance A.FromJSON APIKey where
parseJSON = A.withObject "APIKey" $ \o ->
APIKey
<$> (o .: "id")
<*> (o .: "secret")
<*> (o .: "name")
<*> (o .: "nonce")
<*> (o .:? "cidr")
<*> (o .:? "permissions")
<*> (o .:? "enabled")
<*> (o .: "userId")
<*> (o .:? "created")
instance A.ToJSON APIKey where
toJSON APIKey {..} =
_omitNulls
[ "id" .= aPIKeyId
, "secret" .= aPIKeySecret
, "name" .= aPIKeyName
, "nonce" .= aPIKeyNonce
, "cidr" .= aPIKeyCidr
, "permissions" .= aPIKeyPermissions
, "enabled" .= aPIKeyEnabled
, "userId" .= aPIKeyUserId
, "created" .= aPIKeyCreated
]
mkAPIKey
:: Text
-> Text
-> Text
-> Double
-> Double
-> APIKey
mkAPIKey aPIKeyId aPIKeySecret aPIKeyName aPIKeyNonce aPIKeyUserId =
APIKey
{ aPIKeyId
, aPIKeySecret
, aPIKeyName
, aPIKeyNonce
, aPIKeyCidr = Nothing
, aPIKeyPermissions = Nothing
, aPIKeyEnabled = Nothing
, aPIKeyUserId
, aPIKeyCreated = Nothing
}
data AccessToken = AccessToken
{ accessTokenId :: !(Text)
, accessTokenTtl :: !(Maybe Double)
, accessTokenCreated :: !(Maybe DateTime)
, accessTokenUserId :: !(Maybe Double)
} deriving (P.Show, P.Eq, P.Typeable)
instance A.FromJSON AccessToken where
parseJSON = A.withObject "AccessToken" $ \o ->
AccessToken
<$> (o .: "id")
<*> (o .:? "ttl")
<*> (o .:? "created")
<*> (o .:? "userId")
instance A.ToJSON AccessToken where
toJSON AccessToken {..} =
_omitNulls
[ "id" .= accessTokenId
, "ttl" .= accessTokenTtl
, "created" .= accessTokenCreated
, "userId" .= accessTokenUserId
]
mkAccessToken
:: Text
-> AccessToken
mkAccessToken accessTokenId =
AccessToken
{ accessTokenId
, accessTokenTtl = Nothing
, accessTokenCreated = Nothing
, accessTokenUserId = Nothing
}
data Affiliate = Affiliate
{ affiliateAccount :: !(Double)
, affiliateCurrency :: !(Text)
, affiliatePrevPayout :: !(Maybe Double)
, affiliatePrevTurnover :: !(Maybe Double)
, affiliatePrevComm :: !(Maybe Double)
, affiliatePrevTimestamp :: !(Maybe DateTime)
, affiliateExecTurnover :: !(Maybe Double)
, affiliateExecComm :: !(Maybe Double)
, affiliateTotalReferrals :: !(Maybe Double)
, affiliateTotalTurnover :: !(Maybe Double)
, affiliateTotalComm :: !(Maybe Double)
, affiliatePayoutPcnt :: !(Maybe Double)
, affiliatePendingPayout :: !(Maybe Double)
, affiliateTimestamp :: !(Maybe DateTime)
, affiliateReferrerAccount :: !(Maybe Double)
} deriving (P.Show, P.Eq, P.Typeable)
instance A.FromJSON Affiliate where
parseJSON = A.withObject "Affiliate" $ \o ->
Affiliate
<$> (o .: "account")
<*> (o .: "currency")
<*> (o .:? "prevPayout")
<*> (o .:? "prevTurnover")
<*> (o .:? "prevComm")
<*> (o .:? "prevTimestamp")
<*> (o .:? "execTurnover")
<*> (o .:? "execComm")
<*> (o .:? "totalReferrals")
<*> (o .:? "totalTurnover")
<*> (o .:? "totalComm")
<*> (o .:? "payoutPcnt")
<*> (o .:? "pendingPayout")
<*> (o .:? "timestamp")
<*> (o .:? "referrerAccount")
instance A.ToJSON Affiliate where
toJSON Affiliate {..} =
_omitNulls
[ "account" .= affiliateAccount
, "currency" .= affiliateCurrency
, "prevPayout" .= affiliatePrevPayout
, "prevTurnover" .= affiliatePrevTurnover
, "prevComm" .= affiliatePrevComm
, "prevTimestamp" .= affiliatePrevTimestamp
, "execTurnover" .= affiliateExecTurnover
, "execComm" .= affiliateExecComm
, "totalReferrals" .= affiliateTotalReferrals
, "totalTurnover" .= affiliateTotalTurnover
, "totalComm" .= affiliateTotalComm
, "payoutPcnt" .= affiliatePayoutPcnt
, "pendingPayout" .= affiliatePendingPayout
, "timestamp" .= affiliateTimestamp
, "referrerAccount" .= affiliateReferrerAccount
]
mkAffiliate
:: Double
-> Text
-> Affiliate
mkAffiliate affiliateAccount affiliateCurrency =
Affiliate
{ affiliateAccount
, affiliateCurrency
, affiliatePrevPayout = Nothing
, affiliatePrevTurnover = Nothing
, affiliatePrevComm = Nothing
, affiliatePrevTimestamp = Nothing
, affiliateExecTurnover = Nothing
, affiliateExecComm = Nothing
, affiliateTotalReferrals = Nothing
, affiliateTotalTurnover = Nothing
, affiliateTotalComm = Nothing
, affiliatePayoutPcnt = Nothing
, affiliatePendingPayout = Nothing
, affiliateTimestamp = Nothing
, affiliateReferrerAccount = Nothing
}
data Announcement = Announcement
{ announcementId :: !(Double)
, announcementLink :: !(Maybe Text)
, announcementTitle :: !(Maybe Text)
, announcementContent :: !(Maybe Text)
, announcementDate :: !(Maybe DateTime)
} deriving (P.Show, P.Eq, P.Typeable)
instance A.FromJSON Announcement where
parseJSON = A.withObject "Announcement" $ \o ->
Announcement
<$> (o .: "id")
<*> (o .:? "link")
<*> (o .:? "title")
<*> (o .:? "content")
<*> (o .:? "date")
instance A.ToJSON Announcement where
toJSON Announcement {..} =
_omitNulls
[ "id" .= announcementId
, "link" .= announcementLink
, "title" .= announcementTitle
, "content" .= announcementContent
, "date" .= announcementDate
]
mkAnnouncement
:: Double
-> Announcement
mkAnnouncement announcementId =
Announcement
{ announcementId
, announcementLink = Nothing
, announcementTitle = Nothing
, announcementContent = Nothing
, announcementDate = Nothing
}
data Chat = Chat
{ chatId :: !(Maybe Double)
, chatDate :: !(DateTime)
, chatUser :: !(Text)
, chatMessage :: !(Text)
, chatHtml :: !(Text)
, chatFromBot :: !(Maybe Bool)
, chatChannelId :: !(Maybe Double)
} deriving (P.Show, P.Eq, P.Typeable)
instance A.FromJSON Chat where
parseJSON = A.withObject "Chat" $ \o ->
Chat
<$> (o .:? "id")
<*> (o .: "date")
<*> (o .: "user")
<*> (o .: "message")
<*> (o .: "html")
<*> (o .:? "fromBot")
<*> (o .:? "channelID")
instance A.ToJSON Chat where
toJSON Chat {..} =
_omitNulls
[ "id" .= chatId
, "date" .= chatDate
, "user" .= chatUser
, "message" .= chatMessage
, "html" .= chatHtml
, "fromBot" .= chatFromBot
, "channelID" .= chatChannelId
]
mkChat
:: DateTime
-> Text
-> Text
-> Text
-> Chat
mkChat chatDate chatUser chatMessage chatHtml =
Chat
{ chatId = Nothing
, chatDate
, chatUser
, chatMessage
, chatHtml
, chatFromBot = Nothing
, chatChannelId = Nothing
}
data ChatChannels = ChatChannels
{ chatChannelsId :: !(Maybe Double)
, chatChannelsName :: !(Text)
} deriving (P.Show, P.Eq, P.Typeable)
instance A.FromJSON ChatChannels where
parseJSON = A.withObject "ChatChannels" $ \o ->
ChatChannels
<$> (o .:? "id")
<*> (o .: "name")
instance A.ToJSON ChatChannels where
toJSON ChatChannels {..} =
_omitNulls
[ "id" .= chatChannelsId
, "name" .= chatChannelsName
]
mkChatChannels
:: Text
-> ChatChannels
mkChatChannels chatChannelsName =
ChatChannels
{ chatChannelsId = Nothing
, chatChannelsName
}
data ConnectedUsers = ConnectedUsers
{ connectedUsersUsers :: !(Maybe Double)
, connectedUsersBots :: !(Maybe Double)
} deriving (P.Show, P.Eq, P.Typeable)
instance A.FromJSON ConnectedUsers where
parseJSON = A.withObject "ConnectedUsers" $ \o ->
ConnectedUsers
<$> (o .:? "users")
<*> (o .:? "bots")
instance A.ToJSON ConnectedUsers where
toJSON ConnectedUsers {..} =
_omitNulls
[ "users" .= connectedUsersUsers
, "bots" .= connectedUsersBots
]
mkConnectedUsers
:: ConnectedUsers
mkConnectedUsers =
ConnectedUsers
{ connectedUsersUsers = Nothing
, connectedUsersBots = Nothing
}
data Error = Error
{ errorError :: !(ErrorError)
} deriving (P.Show, P.Eq, P.Typeable)
instance A.FromJSON Error where
parseJSON = A.withObject "Error" $ \o ->
Error
<$> (o .: "error")
instance A.ToJSON Error where
toJSON Error {..} =
_omitNulls
[ "error" .= errorError
]
mkError
:: ErrorError
-> Error
mkError errorError =
Error
{ errorError
}
data ErrorError = ErrorError
{ errorErrorMessage :: !(Maybe Text)
, errorErrorName :: !(Maybe Text)
} deriving (P.Show, P.Eq, P.Typeable)
instance A.FromJSON ErrorError where
parseJSON = A.withObject "ErrorError" $ \o ->
ErrorError
<$> (o .:? "message")
<*> (o .:? "name")
instance A.ToJSON ErrorError where
toJSON ErrorError {..} =
_omitNulls
[ "message" .= errorErrorMessage
, "name" .= errorErrorName
]
mkErrorError
:: ErrorError
mkErrorError =
ErrorError
{ errorErrorMessage = Nothing
, errorErrorName = Nothing
}
data Execution = Execution
{ executionExecId :: !(Text)
, executionOrderId :: !(Maybe Text)
, executionClOrdId :: !(Maybe Text)
, executionClOrdLinkId :: !(Maybe Text)
, executionAccount :: !(Maybe Double)
, executionSymbol :: !(Maybe Text)
, executionSide :: !(Maybe Text)
, executionLastQty :: !(Maybe Double)
, executionLastPx :: !(Maybe Double)
, executionUnderlyingLastPx :: !(Maybe Double)
, executionLastMkt :: !(Maybe Text)
, executionLastLiquidityInd :: !(Maybe Text)
, executionSimpleOrderQty :: !(Maybe Double)
, executionOrderQty :: !(Maybe Double)
, executionPrice :: !(Maybe Double)
, executionDisplayQty :: !(Maybe Double)
, executionStopPx :: !(Maybe Double)
, executionPegOffsetValue :: !(Maybe Double)
, executionPegPriceType :: !(Maybe Text)
, executionCurrency :: !(Maybe Text)
, executionSettlCurrency :: !(Maybe Text)
, executionExecType :: !(Maybe Text)
, executionOrdType :: !(Maybe Text)
, executionTimeInForce :: !(Maybe Text)
, executionExecInst :: !(Maybe Text)
, executionContingencyType :: !(Maybe Text)
, executionExDestination :: !(Maybe Text)
, executionOrdStatus :: !(Maybe Text)
, executionTriggered :: !(Maybe Text)
, executionWorkingIndicator :: !(Maybe Bool)
, executionOrdRejReason :: !(Maybe Text)
, executionSimpleLeavesQty :: !(Maybe Double)
, executionLeavesQty :: !(Maybe Double)
, executionSimpleCumQty :: !(Maybe Double)
, executionCumQty :: !(Maybe Double)
, executionAvgPx :: !(Maybe Double)
, executionCommission :: !(Maybe Double)
, executionTradePublishIndicator :: !(Maybe Text)
, executionMultiLegReportingType :: !(Maybe Text)
, executionText :: !(Maybe Text)
, executionTrdMatchId :: !(Maybe Text)
, executionExecCost :: !(Maybe Double)
, executionExecComm :: !(Maybe Double)
, executionHomeNotional :: !(Maybe Double)
, executionForeignNotional :: !(Maybe Double)
, executionTransactTime :: !(Maybe DateTime)
, executionTimestamp :: !(Maybe DateTime)
} deriving (P.Show, P.Eq, P.Typeable)
instance A.FromJSON Execution where
parseJSON = A.withObject "Execution" $ \o ->
Execution
<$> (o .: "execID")
<*> (o .:? "orderID")
<*> (o .:? "clOrdID")
<*> (o .:? "clOrdLinkID")
<*> (o .:? "account")
<*> (o .:? "symbol")
<*> (o .:? "side")
<*> (o .:? "lastQty")
<*> (o .:? "lastPx")
<*> (o .:? "underlyingLastPx")
<*> (o .:? "lastMkt")
<*> (o .:? "lastLiquidityInd")
<*> (o .:? "simpleOrderQty")
<*> (o .:? "orderQty")
<*> (o .:? "price")
<*> (o .:? "displayQty")
<*> (o .:? "stopPx")
<*> (o .:? "pegOffsetValue")
<*> (o .:? "pegPriceType")
<*> (o .:? "currency")
<*> (o .:? "settlCurrency")
<*> (o .:? "execType")
<*> (o .:? "ordType")
<*> (o .:? "timeInForce")
<*> (o .:? "execInst")
<*> (o .:? "contingencyType")
<*> (o .:? "exDestination")
<*> (o .:? "ordStatus")
<*> (o .:? "triggered")
<*> (o .:? "workingIndicator")
<*> (o .:? "ordRejReason")
<*> (o .:? "simpleLeavesQty")
<*> (o .:? "leavesQty")
<*> (o .:? "simpleCumQty")
<*> (o .:? "cumQty")
<*> (o .:? "avgPx")
<*> (o .:? "commission")
<*> (o .:? "tradePublishIndicator")
<*> (o .:? "multiLegReportingType")
<*> (o .:? "text")
<*> (o .:? "trdMatchID")
<*> (o .:? "execCost")
<*> (o .:? "execComm")
<*> (o .:? "homeNotional")
<*> (o .:? "foreignNotional")
<*> (o .:? "transactTime")
<*> (o .:? "timestamp")
instance A.ToJSON Execution where
toJSON Execution {..} =
_omitNulls
[ "execID" .= executionExecId
, "orderID" .= executionOrderId
, "clOrdID" .= executionClOrdId
, "clOrdLinkID" .= executionClOrdLinkId
, "account" .= executionAccount
, "symbol" .= executionSymbol
, "side" .= executionSide
, "lastQty" .= executionLastQty
, "lastPx" .= executionLastPx
, "underlyingLastPx" .= executionUnderlyingLastPx
, "lastMkt" .= executionLastMkt
, "lastLiquidityInd" .= executionLastLiquidityInd
, "simpleOrderQty" .= executionSimpleOrderQty
, "orderQty" .= executionOrderQty
, "price" .= executionPrice
, "displayQty" .= executionDisplayQty
, "stopPx" .= executionStopPx
, "pegOffsetValue" .= executionPegOffsetValue
, "pegPriceType" .= executionPegPriceType
, "currency" .= executionCurrency
, "settlCurrency" .= executionSettlCurrency
, "execType" .= executionExecType
, "ordType" .= executionOrdType
, "timeInForce" .= executionTimeInForce
, "execInst" .= executionExecInst
, "contingencyType" .= executionContingencyType
, "exDestination" .= executionExDestination
, "ordStatus" .= executionOrdStatus
, "triggered" .= executionTriggered
, "workingIndicator" .= executionWorkingIndicator
, "ordRejReason" .= executionOrdRejReason
, "simpleLeavesQty" .= executionSimpleLeavesQty
, "leavesQty" .= executionLeavesQty
, "simpleCumQty" .= executionSimpleCumQty
, "cumQty" .= executionCumQty
, "avgPx" .= executionAvgPx
, "commission" .= executionCommission
, "tradePublishIndicator" .= executionTradePublishIndicator
, "multiLegReportingType" .= executionMultiLegReportingType
, "text" .= executionText
, "trdMatchID" .= executionTrdMatchId
, "execCost" .= executionExecCost
, "execComm" .= executionExecComm
, "homeNotional" .= executionHomeNotional
, "foreignNotional" .= executionForeignNotional
, "transactTime" .= executionTransactTime
, "timestamp" .= executionTimestamp
]
mkExecution
:: Text
-> Execution
mkExecution executionExecId =
Execution
{ executionExecId
, executionOrderId = Nothing
, executionClOrdId = Nothing
, executionClOrdLinkId = Nothing
, executionAccount = Nothing
, executionSymbol = Nothing
, executionSide = Nothing
, executionLastQty = Nothing
, executionLastPx = Nothing
, executionUnderlyingLastPx = Nothing
, executionLastMkt = Nothing
, executionLastLiquidityInd = Nothing
, executionSimpleOrderQty = Nothing
, executionOrderQty = Nothing
, executionPrice = Nothing
, executionDisplayQty = Nothing
, executionStopPx = Nothing
, executionPegOffsetValue = Nothing
, executionPegPriceType = Nothing
, executionCurrency = Nothing
, executionSettlCurrency = Nothing
, executionExecType = Nothing
, executionOrdType = Nothing
, executionTimeInForce = Nothing
, executionExecInst = Nothing
, executionContingencyType = Nothing
, executionExDestination = Nothing
, executionOrdStatus = Nothing
, executionTriggered = Nothing
, executionWorkingIndicator = Nothing
, executionOrdRejReason = Nothing
, executionSimpleLeavesQty = Nothing
, executionLeavesQty = Nothing
, executionSimpleCumQty = Nothing
, executionCumQty = Nothing
, executionAvgPx = Nothing
, executionCommission = Nothing
, executionTradePublishIndicator = Nothing
, executionMultiLegReportingType = Nothing
, executionText = Nothing
, executionTrdMatchId = Nothing
, executionExecCost = Nothing
, executionExecComm = Nothing
, executionHomeNotional = Nothing
, executionForeignNotional = Nothing
, executionTransactTime = Nothing
, executionTimestamp = Nothing
}
data Funding = Funding
{ fundingTimestamp :: !(DateTime)
, fundingSymbol :: !(Text)
, fundingFundingInterval :: !(Maybe DateTime)
, fundingFundingRate :: !(Maybe Double)
, fundingFundingRateDaily :: !(Maybe Double)
} deriving (P.Show, P.Eq, P.Typeable)
instance A.FromJSON Funding where
parseJSON = A.withObject "Funding" $ \o ->
Funding
<$> (o .: "timestamp")
<*> (o .: "symbol")
<*> (o .:? "fundingInterval")
<*> (o .:? "fundingRate")
<*> (o .:? "fundingRateDaily")
instance A.ToJSON Funding where
toJSON Funding {..} =
_omitNulls
[ "timestamp" .= fundingTimestamp
, "symbol" .= fundingSymbol
, "fundingInterval" .= fundingFundingInterval
, "fundingRate" .= fundingFundingRate
, "fundingRateDaily" .= fundingFundingRateDaily
]
mkFunding
:: DateTime
-> Text
-> Funding
mkFunding fundingTimestamp fundingSymbol =
Funding
{ fundingTimestamp
, fundingSymbol
, fundingFundingInterval = Nothing
, fundingFundingRate = Nothing
, fundingFundingRateDaily = Nothing
}
data IndexComposite = IndexComposite
{ indexCompositeTimestamp :: !(DateTime)
, indexCompositeSymbol :: !(Maybe Text)
, indexCompositeIndexSymbol :: !(Maybe Text)
, indexCompositeReference :: !(Maybe Text)
, indexCompositeLastPrice :: !(Maybe Double)
, indexCompositeWeight :: !(Maybe Double)
, indexCompositeLogged :: !(Maybe DateTime)
} deriving (P.Show, P.Eq, P.Typeable)
instance A.FromJSON IndexComposite where
parseJSON = A.withObject "IndexComposite" $ \o ->
IndexComposite
<$> (o .: "timestamp")
<*> (o .:? "symbol")
<*> (o .:? "indexSymbol")
<*> (o .:? "reference")
<*> (o .:? "lastPrice")
<*> (o .:? "weight")
<*> (o .:? "logged")
instance A.ToJSON IndexComposite where
toJSON IndexComposite {..} =
_omitNulls
[ "timestamp" .= indexCompositeTimestamp
, "symbol" .= indexCompositeSymbol
, "indexSymbol" .= indexCompositeIndexSymbol
, "reference" .= indexCompositeReference
, "lastPrice" .= indexCompositeLastPrice
, "weight" .= indexCompositeWeight
, "logged" .= indexCompositeLogged
]
mkIndexComposite
:: DateTime
-> IndexComposite
mkIndexComposite indexCompositeTimestamp =
IndexComposite
{ indexCompositeTimestamp
, indexCompositeSymbol = Nothing
, indexCompositeIndexSymbol = Nothing
, indexCompositeReference = Nothing
, indexCompositeLastPrice = Nothing
, indexCompositeWeight = Nothing
, indexCompositeLogged = Nothing
}
data InlineResponse200 = InlineResponse200
{ inlineResponse200Success :: !(Maybe Bool)
} deriving (P.Show, P.Eq, P.Typeable)
instance A.FromJSON InlineResponse200 where
parseJSON = A.withObject "InlineResponse200" $ \o ->
InlineResponse200
<$> (o .:? "success")
instance A.ToJSON InlineResponse200 where
toJSON InlineResponse200 {..} =
_omitNulls
[ "success" .= inlineResponse200Success
]
mkInlineResponse200
:: InlineResponse200
mkInlineResponse200 =
InlineResponse200
{ inlineResponse200Success = Nothing
}
data Instrument = Instrument
{ instrumentSymbol :: !(Text)
, instrumentRootSymbol :: !(Maybe Text)
, instrumentState :: !(Maybe Text)
, instrumentTyp :: !(Maybe Text)
, instrumentListing :: !(Maybe DateTime)
, instrumentFront :: !(Maybe DateTime)
, instrumentExpiry :: !(Maybe DateTime)
, instrumentSettle :: !(Maybe DateTime)
, instrumentRelistInterval :: !(Maybe DateTime)
, instrumentInverseLeg :: !(Maybe Text)
, instrumentSellLeg :: !(Maybe Text)
, instrumentBuyLeg :: !(Maybe Text)
, instrumentPositionCurrency :: !(Maybe Text)
, instrumentUnderlying :: !(Maybe Text)
, instrumentQuoteCurrency :: !(Maybe Text)
, instrumentUnderlyingSymbol :: !(Maybe Text)
, instrumentReference :: !(Maybe Text)
, instrumentReferenceSymbol :: !(Maybe Text)
, instrumentCalcInterval :: !(Maybe DateTime)
, instrumentPublishInterval :: !(Maybe DateTime)
, instrumentPublishTime :: !(Maybe DateTime)
, instrumentMaxOrderQty :: !(Maybe Double)
, instrumentMaxPrice :: !(Maybe Double)
, instrumentLotSize :: !(Maybe Double)
, instrumentTickSize :: !(Maybe Double)
, instrumentMultiplier :: !(Maybe Double)
, instrumentSettlCurrency :: !(Maybe Text)
, instrumentUnderlyingToPositionMultiplier :: !(Maybe Double)
, instrumentUnderlyingToSettleMultiplier :: !(Maybe Double)
, instrumentQuoteToSettleMultiplier :: !(Maybe Double)
, instrumentIsQuanto :: !(Maybe Bool)
, instrumentIsInverse :: !(Maybe Bool)
, instrumentInitMargin :: !(Maybe Double)
, instrumentMaintMargin :: !(Maybe Double)
, instrumentRiskLimit :: !(Maybe Double)
, instrumentRiskStep :: !(Maybe Double)
, instrumentLimit :: !(Maybe Double)
, instrumentCapped :: !(Maybe Bool)
, instrumentTaxed :: !(Maybe Bool)
, instrumentDeleverage :: !(Maybe Bool)
, instrumentMakerFee :: !(Maybe Double)
, instrumentTakerFee :: !(Maybe Double)
, instrumentSettlementFee :: !(Maybe Double)
, instrumentInsuranceFee :: !(Maybe Double)
, instrumentFundingBaseSymbol :: !(Maybe Text)
, instrumentFundingQuoteSymbol :: !(Maybe Text)
, instrumentFundingPremiumSymbol :: !(Maybe Text)
, instrumentFundingTimestamp :: !(Maybe DateTime)
, instrumentFundingInterval :: !(Maybe DateTime)
, instrumentFundingRate :: !(Maybe Double)
, instrumentIndicativeFundingRate :: !(Maybe Double)
, instrumentRebalanceTimestamp :: !(Maybe DateTime)
, instrumentRebalanceInterval :: !(Maybe DateTime)
, instrumentOpeningTimestamp :: !(Maybe DateTime)
, instrumentClosingTimestamp :: !(Maybe DateTime)
, instrumentSessionInterval :: !(Maybe DateTime)
, instrumentPrevClosePrice :: !(Maybe Double)
, instrumentLimitDownPrice :: !(Maybe Double)
, instrumentLimitUpPrice :: !(Maybe Double)
, instrumentBankruptLimitDownPrice :: !(Maybe Double)
, instrumentBankruptLimitUpPrice :: !(Maybe Double)
, instrumentPrevTotalVolume :: !(Maybe Double)
, instrumentTotalVolume :: !(Maybe Double)
, instrumentVolume :: !(Maybe Double)
, instrumentVolume24h :: !(Maybe Double)
, instrumentPrevTotalTurnover :: !(Maybe Double)
, instrumentTotalTurnover :: !(Maybe Double)
, instrumentTurnover :: !(Maybe Double)
, instrumentTurnover24h :: !(Maybe Double)
, instrumentPrevPrice24h :: !(Maybe Double)
, instrumentVwap :: !(Maybe Double)
, instrumentHighPrice :: !(Maybe Double)
, instrumentLowPrice :: !(Maybe Double)
, instrumentLastPrice :: !(Maybe Double)
, instrumentLastPriceProtected :: !(Maybe Double)
, instrumentLastTickDirection :: !(Maybe Text)
, instrumentLastChangePcnt :: !(Maybe Double)
, instrumentBidPrice :: !(Maybe Double)
, instrumentMidPrice :: !(Maybe Double)
, instrumentAskPrice :: !(Maybe Double)
, instrumentImpactBidPrice :: !(Maybe Double)
, instrumentImpactMidPrice :: !(Maybe Double)
, instrumentImpactAskPrice :: !(Maybe Double)
, instrumentHasLiquidity :: !(Maybe Bool)
, instrumentOpenInterest :: !(Maybe Double)
, instrumentOpenValue :: !(Maybe Double)
, instrumentFairMethod :: !(Maybe Text)
, instrumentFairBasisRate :: !(Maybe Double)
, instrumentFairBasis :: !(Maybe Double)
, instrumentFairPrice :: !(Maybe Double)
, instrumentMarkMethod :: !(Maybe Text)
, instrumentMarkPrice :: !(Maybe Double)
, instrumentIndicativeTaxRate :: !(Maybe Double)
, instrumentIndicativeSettlePrice :: !(Maybe Double)
, instrumentSettledPrice :: !(Maybe Double)
, instrumentTimestamp :: !(Maybe DateTime)
} deriving (P.Show, P.Eq, P.Typeable)
instance A.FromJSON Instrument where
parseJSON = A.withObject "Instrument" $ \o ->
Instrument
<$> (o .: "symbol")
<*> (o .:? "rootSymbol")
<*> (o .:? "state")
<*> (o .:? "typ")
<*> (o .:? "listing")
<*> (o .:? "front")
<*> (o .:? "expiry")
<*> (o .:? "settle")
<*> (o .:? "relistInterval")
<*> (o .:? "inverseLeg")
<*> (o .:? "sellLeg")
<*> (o .:? "buyLeg")
<*> (o .:? "positionCurrency")
<*> (o .:? "underlying")
<*> (o .:? "quoteCurrency")
<*> (o .:? "underlyingSymbol")
<*> (o .:? "reference")
<*> (o .:? "referenceSymbol")
<*> (o .:? "calcInterval")
<*> (o .:? "publishInterval")
<*> (o .:? "publishTime")
<*> (o .:? "maxOrderQty")
<*> (o .:? "maxPrice")
<*> (o .:? "lotSize")
<*> (o .:? "tickSize")
<*> (o .:? "multiplier")
<*> (o .:? "settlCurrency")
<*> (o .:? "underlyingToPositionMultiplier")
<*> (o .:? "underlyingToSettleMultiplier")
<*> (o .:? "quoteToSettleMultiplier")
<*> (o .:? "isQuanto")
<*> (o .:? "isInverse")
<*> (o .:? "initMargin")
<*> (o .:? "maintMargin")
<*> (o .:? "riskLimit")
<*> (o .:? "riskStep")
<*> (o .:? "limit")
<*> (o .:? "capped")
<*> (o .:? "taxed")
<*> (o .:? "deleverage")
<*> (o .:? "makerFee")
<*> (o .:? "takerFee")
<*> (o .:? "settlementFee")
<*> (o .:? "insuranceFee")
<*> (o .:? "fundingBaseSymbol")
<*> (o .:? "fundingQuoteSymbol")
<*> (o .:? "fundingPremiumSymbol")
<*> (o .:? "fundingTimestamp")
<*> (o .:? "fundingInterval")
<*> (o .:? "fundingRate")
<*> (o .:? "indicativeFundingRate")
<*> (o .:? "rebalanceTimestamp")
<*> (o .:? "rebalanceInterval")
<*> (o .:? "openingTimestamp")
<*> (o .:? "closingTimestamp")
<*> (o .:? "sessionInterval")
<*> (o .:? "prevClosePrice")
<*> (o .:? "limitDownPrice")
<*> (o .:? "limitUpPrice")
<*> (o .:? "bankruptLimitDownPrice")
<*> (o .:? "bankruptLimitUpPrice")
<*> (o .:? "prevTotalVolume")
<*> (o .:? "totalVolume")
<*> (o .:? "volume")
<*> (o .:? "volume24h")
<*> (o .:? "prevTotalTurnover")
<*> (o .:? "totalTurnover")
<*> (o .:? "turnover")
<*> (o .:? "turnover24h")
<*> (o .:? "prevPrice24h")
<*> (o .:? "vwap")
<*> (o .:? "highPrice")
<*> (o .:? "lowPrice")
<*> (o .:? "lastPrice")
<*> (o .:? "lastPriceProtected")
<*> (o .:? "lastTickDirection")
<*> (o .:? "lastChangePcnt")
<*> (o .:? "bidPrice")
<*> (o .:? "midPrice")
<*> (o .:? "askPrice")
<*> (o .:? "impactBidPrice")
<*> (o .:? "impactMidPrice")
<*> (o .:? "impactAskPrice")
<*> (o .:? "hasLiquidity")
<*> (o .:? "openInterest")
<*> (o .:? "openValue")
<*> (o .:? "fairMethod")
<*> (o .:? "fairBasisRate")
<*> (o .:? "fairBasis")
<*> (o .:? "fairPrice")
<*> (o .:? "markMethod")
<*> (o .:? "markPrice")
<*> (o .:? "indicativeTaxRate")
<*> (o .:? "indicativeSettlePrice")
<*> (o .:? "settledPrice")
<*> (o .:? "timestamp")
instance A.ToJSON Instrument where
toJSON Instrument {..} =
_omitNulls
[ "symbol" .= instrumentSymbol
, "rootSymbol" .= instrumentRootSymbol
, "state" .= instrumentState
, "typ" .= instrumentTyp
, "listing" .= instrumentListing
, "front" .= instrumentFront
, "expiry" .= instrumentExpiry
, "settle" .= instrumentSettle
, "relistInterval" .= instrumentRelistInterval
, "inverseLeg" .= instrumentInverseLeg
, "sellLeg" .= instrumentSellLeg
, "buyLeg" .= instrumentBuyLeg
, "positionCurrency" .= instrumentPositionCurrency
, "underlying" .= instrumentUnderlying
, "quoteCurrency" .= instrumentQuoteCurrency
, "underlyingSymbol" .= instrumentUnderlyingSymbol
, "reference" .= instrumentReference
, "referenceSymbol" .= instrumentReferenceSymbol
, "calcInterval" .= instrumentCalcInterval
, "publishInterval" .= instrumentPublishInterval
, "publishTime" .= instrumentPublishTime
, "maxOrderQty" .= instrumentMaxOrderQty
, "maxPrice" .= instrumentMaxPrice
, "lotSize" .= instrumentLotSize
, "tickSize" .= instrumentTickSize
, "multiplier" .= instrumentMultiplier
, "settlCurrency" .= instrumentSettlCurrency
, "underlyingToPositionMultiplier" .= instrumentUnderlyingToPositionMultiplier
, "underlyingToSettleMultiplier" .= instrumentUnderlyingToSettleMultiplier
, "quoteToSettleMultiplier" .= instrumentQuoteToSettleMultiplier
, "isQuanto" .= instrumentIsQuanto
, "isInverse" .= instrumentIsInverse
, "initMargin" .= instrumentInitMargin
, "maintMargin" .= instrumentMaintMargin
, "riskLimit" .= instrumentRiskLimit
, "riskStep" .= instrumentRiskStep
, "limit" .= instrumentLimit
, "capped" .= instrumentCapped
, "taxed" .= instrumentTaxed
, "deleverage" .= instrumentDeleverage
, "makerFee" .= instrumentMakerFee
, "takerFee" .= instrumentTakerFee
, "settlementFee" .= instrumentSettlementFee
, "insuranceFee" .= instrumentInsuranceFee
, "fundingBaseSymbol" .= instrumentFundingBaseSymbol
, "fundingQuoteSymbol" .= instrumentFundingQuoteSymbol
, "fundingPremiumSymbol" .= instrumentFundingPremiumSymbol
, "fundingTimestamp" .= instrumentFundingTimestamp
, "fundingInterval" .= instrumentFundingInterval
, "fundingRate" .= instrumentFundingRate
, "indicativeFundingRate" .= instrumentIndicativeFundingRate
, "rebalanceTimestamp" .= instrumentRebalanceTimestamp
, "rebalanceInterval" .= instrumentRebalanceInterval
, "openingTimestamp" .= instrumentOpeningTimestamp
, "closingTimestamp" .= instrumentClosingTimestamp
, "sessionInterval" .= instrumentSessionInterval
, "prevClosePrice" .= instrumentPrevClosePrice
, "limitDownPrice" .= instrumentLimitDownPrice
, "limitUpPrice" .= instrumentLimitUpPrice
, "bankruptLimitDownPrice" .= instrumentBankruptLimitDownPrice
, "bankruptLimitUpPrice" .= instrumentBankruptLimitUpPrice
, "prevTotalVolume" .= instrumentPrevTotalVolume
, "totalVolume" .= instrumentTotalVolume
, "volume" .= instrumentVolume
, "volume24h" .= instrumentVolume24h
, "prevTotalTurnover" .= instrumentPrevTotalTurnover
, "totalTurnover" .= instrumentTotalTurnover
, "turnover" .= instrumentTurnover
, "turnover24h" .= instrumentTurnover24h
, "prevPrice24h" .= instrumentPrevPrice24h
, "vwap" .= instrumentVwap
, "highPrice" .= instrumentHighPrice
, "lowPrice" .= instrumentLowPrice
, "lastPrice" .= instrumentLastPrice
, "lastPriceProtected" .= instrumentLastPriceProtected
, "lastTickDirection" .= instrumentLastTickDirection
, "lastChangePcnt" .= instrumentLastChangePcnt
, "bidPrice" .= instrumentBidPrice
, "midPrice" .= instrumentMidPrice
, "askPrice" .= instrumentAskPrice
, "impactBidPrice" .= instrumentImpactBidPrice
, "impactMidPrice" .= instrumentImpactMidPrice
, "impactAskPrice" .= instrumentImpactAskPrice
, "hasLiquidity" .= instrumentHasLiquidity
, "openInterest" .= instrumentOpenInterest
, "openValue" .= instrumentOpenValue
, "fairMethod" .= instrumentFairMethod
, "fairBasisRate" .= instrumentFairBasisRate
, "fairBasis" .= instrumentFairBasis
, "fairPrice" .= instrumentFairPrice
, "markMethod" .= instrumentMarkMethod
, "markPrice" .= instrumentMarkPrice
, "indicativeTaxRate" .= instrumentIndicativeTaxRate
, "indicativeSettlePrice" .= instrumentIndicativeSettlePrice
, "settledPrice" .= instrumentSettledPrice
, "timestamp" .= instrumentTimestamp
]
mkInstrument
:: Text
-> Instrument
mkInstrument instrumentSymbol =
Instrument
{ instrumentSymbol
, instrumentRootSymbol = Nothing
, instrumentState = Nothing
, instrumentTyp = Nothing
, instrumentListing = Nothing
, instrumentFront = Nothing
, instrumentExpiry = Nothing
, instrumentSettle = Nothing
, instrumentRelistInterval = Nothing
, instrumentInverseLeg = Nothing
, instrumentSellLeg = Nothing
, instrumentBuyLeg = Nothing
, instrumentPositionCurrency = Nothing
, instrumentUnderlying = Nothing
, instrumentQuoteCurrency = Nothing
, instrumentUnderlyingSymbol = Nothing
, instrumentReference = Nothing
, instrumentReferenceSymbol = Nothing
, instrumentCalcInterval = Nothing
, instrumentPublishInterval = Nothing
, instrumentPublishTime = Nothing
, instrumentMaxOrderQty = Nothing
, instrumentMaxPrice = Nothing
, instrumentLotSize = Nothing
, instrumentTickSize = Nothing
, instrumentMultiplier = Nothing
, instrumentSettlCurrency = Nothing
, instrumentUnderlyingToPositionMultiplier = Nothing
, instrumentUnderlyingToSettleMultiplier = Nothing
, instrumentQuoteToSettleMultiplier = Nothing
, instrumentIsQuanto = Nothing
, instrumentIsInverse = Nothing
, instrumentInitMargin = Nothing
, instrumentMaintMargin = Nothing
, instrumentRiskLimit = Nothing
, instrumentRiskStep = Nothing
, instrumentLimit = Nothing
, instrumentCapped = Nothing
, instrumentTaxed = Nothing
, instrumentDeleverage = Nothing
, instrumentMakerFee = Nothing
, instrumentTakerFee = Nothing
, instrumentSettlementFee = Nothing
, instrumentInsuranceFee = Nothing
, instrumentFundingBaseSymbol = Nothing
, instrumentFundingQuoteSymbol = Nothing
, instrumentFundingPremiumSymbol = Nothing
, instrumentFundingTimestamp = Nothing
, instrumentFundingInterval = Nothing
, instrumentFundingRate = Nothing
, instrumentIndicativeFundingRate = Nothing
, instrumentRebalanceTimestamp = Nothing
, instrumentRebalanceInterval = Nothing
, instrumentOpeningTimestamp = Nothing
, instrumentClosingTimestamp = Nothing
, instrumentSessionInterval = Nothing
, instrumentPrevClosePrice = Nothing
, instrumentLimitDownPrice = Nothing
, instrumentLimitUpPrice = Nothing
, instrumentBankruptLimitDownPrice = Nothing
, instrumentBankruptLimitUpPrice = Nothing
, instrumentPrevTotalVolume = Nothing
, instrumentTotalVolume = Nothing
, instrumentVolume = Nothing
, instrumentVolume24h = Nothing
, instrumentPrevTotalTurnover = Nothing
, instrumentTotalTurnover = Nothing
, instrumentTurnover = Nothing
, instrumentTurnover24h = Nothing
, instrumentPrevPrice24h = Nothing
, instrumentVwap = Nothing
, instrumentHighPrice = Nothing
, instrumentLowPrice = Nothing
, instrumentLastPrice = Nothing
, instrumentLastPriceProtected = Nothing
, instrumentLastTickDirection = Nothing
, instrumentLastChangePcnt = Nothing
, instrumentBidPrice = Nothing
, instrumentMidPrice = Nothing
, instrumentAskPrice = Nothing
, instrumentImpactBidPrice = Nothing
, instrumentImpactMidPrice = Nothing
, instrumentImpactAskPrice = Nothing
, instrumentHasLiquidity = Nothing
, instrumentOpenInterest = Nothing
, instrumentOpenValue = Nothing
, instrumentFairMethod = Nothing
, instrumentFairBasisRate = Nothing
, instrumentFairBasis = Nothing
, instrumentFairPrice = Nothing
, instrumentMarkMethod = Nothing
, instrumentMarkPrice = Nothing
, instrumentIndicativeTaxRate = Nothing
, instrumentIndicativeSettlePrice = Nothing
, instrumentSettledPrice = Nothing
, instrumentTimestamp = Nothing
}
data InstrumentInterval = InstrumentInterval
{ instrumentIntervalIntervals :: !([Text])
, instrumentIntervalSymbols :: !([Text])
} deriving (P.Show, P.Eq, P.Typeable)
instance A.FromJSON InstrumentInterval where
parseJSON = A.withObject "InstrumentInterval" $ \o ->
InstrumentInterval
<$> (o .: "intervals")
<*> (o .: "symbols")
instance A.ToJSON InstrumentInterval where
toJSON InstrumentInterval {..} =
_omitNulls
[ "intervals" .= instrumentIntervalIntervals
, "symbols" .= instrumentIntervalSymbols
]
mkInstrumentInterval
:: [Text]
-> [Text]
-> InstrumentInterval
mkInstrumentInterval instrumentIntervalIntervals instrumentIntervalSymbols =
InstrumentInterval
{ instrumentIntervalIntervals
, instrumentIntervalSymbols
}
data Insurance = Insurance
{ insuranceCurrency :: !(Text)
, insuranceTimestamp :: !(DateTime)
, insuranceWalletBalance :: !(Maybe Double)
} deriving (P.Show, P.Eq, P.Typeable)
instance A.FromJSON Insurance where
parseJSON = A.withObject "Insurance" $ \o ->
Insurance
<$> (o .: "currency")
<*> (o .: "timestamp")
<*> (o .:? "walletBalance")
instance A.ToJSON Insurance where
toJSON Insurance {..} =
_omitNulls
[ "currency" .= insuranceCurrency
, "timestamp" .= insuranceTimestamp
, "walletBalance" .= insuranceWalletBalance
]
mkInsurance
:: Text
-> DateTime
-> Insurance
mkInsurance insuranceCurrency insuranceTimestamp =
Insurance
{ insuranceCurrency
, insuranceTimestamp
, insuranceWalletBalance = Nothing
}
data Leaderboard = Leaderboard
{ leaderboardName :: !(Text)
, leaderboardIsRealName :: !(Maybe Bool)
, leaderboardIsMe :: !(Maybe Bool)
, leaderboardProfit :: !(Maybe Double)
} deriving (P.Show, P.Eq, P.Typeable)
instance A.FromJSON Leaderboard where
parseJSON = A.withObject "Leaderboard" $ \o ->
Leaderboard
<$> (o .: "name")
<*> (o .:? "isRealName")
<*> (o .:? "isMe")
<*> (o .:? "profit")
instance A.ToJSON Leaderboard where
toJSON Leaderboard {..} =
_omitNulls
[ "name" .= leaderboardName
, "isRealName" .= leaderboardIsRealName
, "isMe" .= leaderboardIsMe
, "profit" .= leaderboardProfit
]
mkLeaderboard
:: Text
-> Leaderboard
mkLeaderboard leaderboardName =
Leaderboard
{ leaderboardName
, leaderboardIsRealName = Nothing
, leaderboardIsMe = Nothing
, leaderboardProfit = Nothing
}
data Liquidation = Liquidation
{ liquidationOrderId :: !(Text)
, liquidationSymbol :: !(Maybe Text)
, liquidationSide :: !(Maybe Text)
, liquidationPrice :: !(Maybe Double)
, liquidationLeavesQty :: !(Maybe Double)
} deriving (P.Show, P.Eq, P.Typeable)
instance A.FromJSON Liquidation where
parseJSON = A.withObject "Liquidation" $ \o ->
Liquidation
<$> (o .: "orderID")
<*> (o .:? "symbol")
<*> (o .:? "side")
<*> (o .:? "price")
<*> (o .:? "leavesQty")
instance A.ToJSON Liquidation where
toJSON Liquidation {..} =
_omitNulls
[ "orderID" .= liquidationOrderId
, "symbol" .= liquidationSymbol
, "side" .= liquidationSide
, "price" .= liquidationPrice
, "leavesQty" .= liquidationLeavesQty
]
mkLiquidation
:: Text
-> Liquidation
mkLiquidation liquidationOrderId =
Liquidation
{ liquidationOrderId
, liquidationSymbol = Nothing
, liquidationSide = Nothing
, liquidationPrice = Nothing
, liquidationLeavesQty = Nothing
}
data Margin = Margin
{ marginAccount :: !(Double)
, marginCurrency :: !(Text)
, marginRiskLimit :: !(Maybe Double)
, marginPrevState :: !(Maybe Text)
, marginState :: !(Maybe Text)
, marginAction :: !(Maybe Text)
, marginAmount :: !(Maybe Double)
, marginPendingCredit :: !(Maybe Double)
, marginPendingDebit :: !(Maybe Double)
, marginConfirmedDebit :: !(Maybe Double)
, marginPrevRealisedPnl :: !(Maybe Double)
, marginPrevUnrealisedPnl :: !(Maybe Double)
, marginGrossComm :: !(Maybe Double)
, marginGrossOpenCost :: !(Maybe Double)
, marginGrossOpenPremium :: !(Maybe Double)
, marginGrossExecCost :: !(Maybe Double)
, marginGrossMarkValue :: !(Maybe Double)
, marginRiskValue :: !(Maybe Double)
, marginTaxableMargin :: !(Maybe Double)
, marginInitMargin :: !(Maybe Double)
, marginMaintMargin :: !(Maybe Double)
, marginSessionMargin :: !(Maybe Double)
, marginTargetExcessMargin :: !(Maybe Double)
, marginVarMargin :: !(Maybe Double)
, marginRealisedPnl :: !(Maybe Double)
, marginUnrealisedPnl :: !(Maybe Double)
, marginIndicativeTax :: !(Maybe Double)
, marginUnrealisedProfit :: !(Maybe Double)
, marginSyntheticMargin :: !(Maybe Double)
, marginWalletBalance :: !(Maybe Double)
, marginMarginBalance :: !(Maybe Double)
, marginMarginBalancePcnt :: !(Maybe Double)
, marginMarginLeverage :: !(Maybe Double)
, marginMarginUsedPcnt :: !(Maybe Double)
, marginExcessMargin :: !(Maybe Double)
, marginExcessMarginPcnt :: !(Maybe Double)
, marginAvailableMargin :: !(Maybe Double)
, marginWithdrawableMargin :: !(Maybe Double)
, marginTimestamp :: !(Maybe DateTime)
, marginGrossLastValue :: !(Maybe Double)
, marginCommission :: !(Maybe Double)
} deriving (P.Show, P.Eq, P.Typeable)
instance A.FromJSON Margin where
parseJSON = A.withObject "Margin" $ \o ->
Margin
<$> (o .: "account")
<*> (o .: "currency")
<*> (o .:? "riskLimit")
<*> (o .:? "prevState")
<*> (o .:? "state")
<*> (o .:? "action")
<*> (o .:? "amount")
<*> (o .:? "pendingCredit")
<*> (o .:? "pendingDebit")
<*> (o .:? "confirmedDebit")
<*> (o .:? "prevRealisedPnl")
<*> (o .:? "prevUnrealisedPnl")
<*> (o .:? "grossComm")
<*> (o .:? "grossOpenCost")
<*> (o .:? "grossOpenPremium")
<*> (o .:? "grossExecCost")
<*> (o .:? "grossMarkValue")
<*> (o .:? "riskValue")
<*> (o .:? "taxableMargin")
<*> (o .:? "initMargin")
<*> (o .:? "maintMargin")
<*> (o .:? "sessionMargin")
<*> (o .:? "targetExcessMargin")
<*> (o .:? "varMargin")
<*> (o .:? "realisedPnl")
<*> (o .:? "unrealisedPnl")
<*> (o .:? "indicativeTax")
<*> (o .:? "unrealisedProfit")
<*> (o .:? "syntheticMargin")
<*> (o .:? "walletBalance")
<*> (o .:? "marginBalance")
<*> (o .:? "marginBalancePcnt")
<*> (o .:? "marginLeverage")
<*> (o .:? "marginUsedPcnt")
<*> (o .:? "excessMargin")
<*> (o .:? "excessMarginPcnt")
<*> (o .:? "availableMargin")
<*> (o .:? "withdrawableMargin")
<*> (o .:? "timestamp")
<*> (o .:? "grossLastValue")
<*> (o .:? "commission")
instance A.ToJSON Margin where
toJSON Margin {..} =
_omitNulls
[ "account" .= marginAccount
, "currency" .= marginCurrency
, "riskLimit" .= marginRiskLimit
, "prevState" .= marginPrevState
, "state" .= marginState
, "action" .= marginAction
, "amount" .= marginAmount
, "pendingCredit" .= marginPendingCredit
, "pendingDebit" .= marginPendingDebit
, "confirmedDebit" .= marginConfirmedDebit
, "prevRealisedPnl" .= marginPrevRealisedPnl
, "prevUnrealisedPnl" .= marginPrevUnrealisedPnl
, "grossComm" .= marginGrossComm
, "grossOpenCost" .= marginGrossOpenCost
, "grossOpenPremium" .= marginGrossOpenPremium
, "grossExecCost" .= marginGrossExecCost
, "grossMarkValue" .= marginGrossMarkValue
, "riskValue" .= marginRiskValue
, "taxableMargin" .= marginTaxableMargin
, "initMargin" .= marginInitMargin
, "maintMargin" .= marginMaintMargin
, "sessionMargin" .= marginSessionMargin
, "targetExcessMargin" .= marginTargetExcessMargin
, "varMargin" .= marginVarMargin
, "realisedPnl" .= marginRealisedPnl
, "unrealisedPnl" .= marginUnrealisedPnl
, "indicativeTax" .= marginIndicativeTax
, "unrealisedProfit" .= marginUnrealisedProfit
, "syntheticMargin" .= marginSyntheticMargin
, "walletBalance" .= marginWalletBalance
, "marginBalance" .= marginMarginBalance
, "marginBalancePcnt" .= marginMarginBalancePcnt
, "marginLeverage" .= marginMarginLeverage
, "marginUsedPcnt" .= marginMarginUsedPcnt
, "excessMargin" .= marginExcessMargin
, "excessMarginPcnt" .= marginExcessMarginPcnt
, "availableMargin" .= marginAvailableMargin
, "withdrawableMargin" .= marginWithdrawableMargin
, "timestamp" .= marginTimestamp
, "grossLastValue" .= marginGrossLastValue
, "commission" .= marginCommission
]
mkMargin
:: Double
-> Text
-> Margin
mkMargin marginAccount marginCurrency =
Margin
{ marginAccount
, marginCurrency
, marginRiskLimit = Nothing
, marginPrevState = Nothing
, marginState = Nothing
, marginAction = Nothing
, marginAmount = Nothing
, marginPendingCredit = Nothing
, marginPendingDebit = Nothing
, marginConfirmedDebit = Nothing
, marginPrevRealisedPnl = Nothing
, marginPrevUnrealisedPnl = Nothing
, marginGrossComm = Nothing
, marginGrossOpenCost = Nothing
, marginGrossOpenPremium = Nothing
, marginGrossExecCost = Nothing
, marginGrossMarkValue = Nothing
, marginRiskValue = Nothing
, marginTaxableMargin = Nothing
, marginInitMargin = Nothing
, marginMaintMargin = Nothing
, marginSessionMargin = Nothing
, marginTargetExcessMargin = Nothing
, marginVarMargin = Nothing
, marginRealisedPnl = Nothing
, marginUnrealisedPnl = Nothing
, marginIndicativeTax = Nothing
, marginUnrealisedProfit = Nothing
, marginSyntheticMargin = Nothing
, marginWalletBalance = Nothing
, marginMarginBalance = Nothing
, marginMarginBalancePcnt = Nothing
, marginMarginLeverage = Nothing
, marginMarginUsedPcnt = Nothing
, marginExcessMargin = Nothing
, marginExcessMarginPcnt = Nothing
, marginAvailableMargin = Nothing
, marginWithdrawableMargin = Nothing
, marginTimestamp = Nothing
, marginGrossLastValue = Nothing
, marginCommission = Nothing
}
data Notification = Notification
{ notificationId :: !(Maybe Double)
, notificationDate :: !(DateTime)
, notificationTitle :: !(Text)
, notificationBody :: !(Text)
, notificationTtl :: !(Double)
, notificationType :: !(Maybe E'Type)
, notificationClosable :: !(Maybe Bool)
, notificationPersist :: !(Maybe Bool)
, notificationWaitForVisibility :: !(Maybe Bool)
, notificationSound :: !(Maybe Text)
} deriving (P.Show, P.Eq, P.Typeable)
instance A.FromJSON Notification where
parseJSON = A.withObject "Notification" $ \o ->
Notification
<$> (o .:? "id")
<*> (o .: "date")
<*> (o .: "title")
<*> (o .: "body")
<*> (o .: "ttl")
<*> (o .:? "type")
<*> (o .:? "closable")
<*> (o .:? "persist")
<*> (o .:? "waitForVisibility")
<*> (o .:? "sound")
instance A.ToJSON Notification where
toJSON Notification {..} =
_omitNulls
[ "id" .= notificationId
, "date" .= notificationDate
, "title" .= notificationTitle
, "body" .= notificationBody
, "ttl" .= notificationTtl
, "type" .= notificationType
, "closable" .= notificationClosable
, "persist" .= notificationPersist
, "waitForVisibility" .= notificationWaitForVisibility
, "sound" .= notificationSound
]
mkNotification
:: DateTime
-> Text
-> Text
-> Double
-> Notification
mkNotification notificationDate notificationTitle notificationBody notificationTtl =
Notification
{ notificationId = Nothing
, notificationDate
, notificationTitle
, notificationBody
, notificationTtl
, notificationType = Nothing
, notificationClosable = Nothing
, notificationPersist = Nothing
, notificationWaitForVisibility = Nothing
, notificationSound = Nothing
}
data Order = Order
{ orderOrderId :: !(Text)
, orderClOrdId :: !(Maybe Text)
, orderClOrdLinkId :: !(Maybe Text)
, orderAccount :: !(Maybe Double)
, orderSymbol :: !(Maybe Text)
, orderSide :: !(Maybe Text)
, orderSimpleOrderQty :: !(Maybe Double)
, orderOrderQty :: !(Maybe Double)
, orderPrice :: !(Maybe Double)
, orderDisplayQty :: !(Maybe Double)
, orderStopPx :: !(Maybe Double)
, orderPegOffsetValue :: !(Maybe Double)
, orderPegPriceType :: !(Maybe Text)
, orderCurrency :: !(Maybe Text)
, orderSettlCurrency :: !(Maybe Text)
, orderOrdType :: !(Maybe Text)
, orderTimeInForce :: !(Maybe Text)
, orderExecInst :: !(Maybe Text)
, orderContingencyType :: !(Maybe Text)
, orderExDestination :: !(Maybe Text)
, orderOrdStatus :: !(Maybe Text)
, orderTriggered :: !(Maybe Text)
, orderWorkingIndicator :: !(Maybe Bool)
, orderOrdRejReason :: !(Maybe Text)
, orderSimpleLeavesQty :: !(Maybe Double)
, orderLeavesQty :: !(Maybe Double)
, orderSimpleCumQty :: !(Maybe Double)
, orderCumQty :: !(Maybe Double)
, orderAvgPx :: !(Maybe Double)
, orderMultiLegReportingType :: !(Maybe Text)
, orderText :: !(Maybe Text)
, orderTransactTime :: !(Maybe DateTime)
, orderTimestamp :: !(Maybe DateTime)
} deriving (P.Show, P.Eq, P.Typeable)
instance A.FromJSON Order where
parseJSON = A.withObject "Order" $ \o ->
Order
<$> (o .: "orderID")
<*> (o .:? "clOrdID")
<*> (o .:? "clOrdLinkID")
<*> (o .:? "account")
<*> (o .:? "symbol")
<*> (o .:? "side")
<*> (o .:? "simpleOrderQty")
<*> (o .:? "orderQty")
<*> (o .:? "price")
<*> (o .:? "displayQty")
<*> (o .:? "stopPx")
<*> (o .:? "pegOffsetValue")
<*> (o .:? "pegPriceType")
<*> (o .:? "currency")
<*> (o .:? "settlCurrency")
<*> (o .:? "ordType")
<*> (o .:? "timeInForce")
<*> (o .:? "execInst")
<*> (o .:? "contingencyType")
<*> (o .:? "exDestination")
<*> (o .:? "ordStatus")
<*> (o .:? "triggered")
<*> (o .:? "workingIndicator")
<*> (o .:? "ordRejReason")
<*> (o .:? "simpleLeavesQty")
<*> (o .:? "leavesQty")
<*> (o .:? "simpleCumQty")
<*> (o .:? "cumQty")
<*> (o .:? "avgPx")
<*> (o .:? "multiLegReportingType")
<*> (o .:? "text")
<*> (o .:? "transactTime")
<*> (o .:? "timestamp")
instance A.ToJSON Order where
toJSON Order {..} =
_omitNulls
[ "orderID" .= orderOrderId
, "clOrdID" .= orderClOrdId
, "clOrdLinkID" .= orderClOrdLinkId
, "account" .= orderAccount
, "symbol" .= orderSymbol
, "side" .= orderSide
, "simpleOrderQty" .= orderSimpleOrderQty
, "orderQty" .= orderOrderQty
, "price" .= orderPrice
, "displayQty" .= orderDisplayQty
, "stopPx" .= orderStopPx
, "pegOffsetValue" .= orderPegOffsetValue
, "pegPriceType" .= orderPegPriceType
, "currency" .= orderCurrency
, "settlCurrency" .= orderSettlCurrency
, "ordType" .= orderOrdType
, "timeInForce" .= orderTimeInForce
, "execInst" .= orderExecInst
, "contingencyType" .= orderContingencyType
, "exDestination" .= orderExDestination
, "ordStatus" .= orderOrdStatus
, "triggered" .= orderTriggered
, "workingIndicator" .= orderWorkingIndicator
, "ordRejReason" .= orderOrdRejReason
, "simpleLeavesQty" .= orderSimpleLeavesQty
, "leavesQty" .= orderLeavesQty
, "simpleCumQty" .= orderSimpleCumQty
, "cumQty" .= orderCumQty
, "avgPx" .= orderAvgPx
, "multiLegReportingType" .= orderMultiLegReportingType
, "text" .= orderText
, "transactTime" .= orderTransactTime
, "timestamp" .= orderTimestamp
]
mkOrder
:: Text
-> Order
mkOrder orderOrderId =
Order
{ orderOrderId
, orderClOrdId = Nothing
, orderClOrdLinkId = Nothing
, orderAccount = Nothing
, orderSymbol = Nothing
, orderSide = Nothing
, orderSimpleOrderQty = Nothing
, orderOrderQty = Nothing
, orderPrice = Nothing
, orderDisplayQty = Nothing
, orderStopPx = Nothing
, orderPegOffsetValue = Nothing
, orderPegPriceType = Nothing
, orderCurrency = Nothing
, orderSettlCurrency = Nothing
, orderOrdType = Nothing
, orderTimeInForce = Nothing
, orderExecInst = Nothing
, orderContingencyType = Nothing
, orderExDestination = Nothing
, orderOrdStatus = Nothing
, orderTriggered = Nothing
, orderWorkingIndicator = Nothing
, orderOrdRejReason = Nothing
, orderSimpleLeavesQty = Nothing
, orderLeavesQty = Nothing
, orderSimpleCumQty = Nothing
, orderCumQty = Nothing
, orderAvgPx = Nothing
, orderMultiLegReportingType = Nothing
, orderText = Nothing
, orderTransactTime = Nothing
, orderTimestamp = Nothing
}
data OrderBook = OrderBook
{ orderBookSymbol :: !(Text)
, orderBookLevel :: !(Double)
, orderBookBidSize :: !(Maybe Double)
, orderBookBidPrice :: !(Maybe Double)
, orderBookAskPrice :: !(Maybe Double)
, orderBookAskSize :: !(Maybe Double)
, orderBookTimestamp :: !(Maybe DateTime)
} deriving (P.Show, P.Eq, P.Typeable)
instance A.FromJSON OrderBook where
parseJSON = A.withObject "OrderBook" $ \o ->
OrderBook
<$> (o .: "symbol")
<*> (o .: "level")
<*> (o .:? "bidSize")
<*> (o .:? "bidPrice")
<*> (o .:? "askPrice")
<*> (o .:? "askSize")
<*> (o .:? "timestamp")
instance A.ToJSON OrderBook where
toJSON OrderBook {..} =
_omitNulls
[ "symbol" .= orderBookSymbol
, "level" .= orderBookLevel
, "bidSize" .= orderBookBidSize
, "bidPrice" .= orderBookBidPrice
, "askPrice" .= orderBookAskPrice
, "askSize" .= orderBookAskSize
, "timestamp" .= orderBookTimestamp
]
mkOrderBook
:: Text
-> Double
-> OrderBook
mkOrderBook orderBookSymbol orderBookLevel =
OrderBook
{ orderBookSymbol
, orderBookLevel
, orderBookBidSize = Nothing
, orderBookBidPrice = Nothing
, orderBookAskPrice = Nothing
, orderBookAskSize = Nothing
, orderBookTimestamp = Nothing
}
data OrderBookL2 = OrderBookL2
{ orderBookL2Symbol :: !(Text)
, orderBookL2Id :: !(Double)
, orderBookL2Side :: !(Text)
, orderBookL2Size :: !(Maybe Double)
, orderBookL2Price :: !(Maybe Double)
} deriving (P.Show, P.Eq, P.Typeable)
instance A.FromJSON OrderBookL2 where
parseJSON = A.withObject "OrderBookL2" $ \o ->
OrderBookL2
<$> (o .: "symbol")
<*> (o .: "id")
<*> (o .: "side")
<*> (o .:? "size")
<*> (o .:? "price")
instance A.ToJSON OrderBookL2 where
toJSON OrderBookL2 {..} =
_omitNulls
[ "symbol" .= orderBookL2Symbol
, "id" .= orderBookL2Id
, "side" .= orderBookL2Side
, "size" .= orderBookL2Size
, "price" .= orderBookL2Price
]
mkOrderBookL2
:: Text
-> Double
-> Text
-> OrderBookL2
mkOrderBookL2 orderBookL2Symbol orderBookL2Id orderBookL2Side =
OrderBookL2
{ orderBookL2Symbol
, orderBookL2Id
, orderBookL2Side
, orderBookL2Size = Nothing
, orderBookL2Price = Nothing
}
data Position = Position
{ positionAccount :: !(Double)
, positionSymbol :: !(Text)
, positionCurrency :: !(Text)
, positionUnderlying :: !(Maybe Text)
, positionQuoteCurrency :: !(Maybe Text)
, positionCommission :: !(Maybe Double)
, positionInitMarginReq :: !(Maybe Double)
, positionMaintMarginReq :: !(Maybe Double)
, positionRiskLimit :: !(Maybe Double)
, positionLeverage :: !(Maybe Double)
, positionCrossMargin :: !(Maybe Bool)
, positionDeleveragePercentile :: !(Maybe Double)
, positionRebalancedPnl :: !(Maybe Double)
, positionPrevRealisedPnl :: !(Maybe Double)
, positionPrevUnrealisedPnl :: !(Maybe Double)
, positionPrevClosePrice :: !(Maybe Double)
, positionOpeningTimestamp :: !(Maybe DateTime)
, positionOpeningQty :: !(Maybe Double)
, positionOpeningCost :: !(Maybe Double)
, positionOpeningComm :: !(Maybe Double)
, positionOpenOrderBuyQty :: !(Maybe Double)
, positionOpenOrderBuyCost :: !(Maybe Double)
, positionOpenOrderBuyPremium :: !(Maybe Double)
, positionOpenOrderSellQty :: !(Maybe Double)
, positionOpenOrderSellCost :: !(Maybe Double)
, positionOpenOrderSellPremium :: !(Maybe Double)
, positionExecBuyQty :: !(Maybe Double)
, positionExecBuyCost :: !(Maybe Double)
, positionExecSellQty :: !(Maybe Double)
, positionExecSellCost :: !(Maybe Double)
, positionExecQty :: !(Maybe Double)
, positionExecCost :: !(Maybe Double)
, positionExecComm :: !(Maybe Double)
, positionCurrentTimestamp :: !(Maybe DateTime)
, positionCurrentQty :: !(Maybe Double)
, positionCurrentCost :: !(Maybe Double)
, positionCurrentComm :: !(Maybe Double)
, positionRealisedCost :: !(Maybe Double)
, positionUnrealisedCost :: !(Maybe Double)
, positionGrossOpenCost :: !(Maybe Double)
, positionGrossOpenPremium :: !(Maybe Double)
, positionGrossExecCost :: !(Maybe Double)
, positionIsOpen :: !(Maybe Bool)
, positionMarkPrice :: !(Maybe Double)
, positionMarkValue :: !(Maybe Double)
, positionRiskValue :: !(Maybe Double)
, positionHomeNotional :: !(Maybe Double)
, positionForeignNotional :: !(Maybe Double)
, positionPosState :: !(Maybe Text)
, positionPosCost :: !(Maybe Double)
, positionPosCost2 :: !(Maybe Double)
, positionPosCross :: !(Maybe Double)
, positionPosInit :: !(Maybe Double)
, positionPosComm :: !(Maybe Double)
, positionPosLoss :: !(Maybe Double)
, positionPosMargin :: !(Maybe Double)
, positionPosMaint :: !(Maybe Double)
, positionPosAllowance :: !(Maybe Double)
, positionTaxableMargin :: !(Maybe Double)
, positionInitMargin :: !(Maybe Double)
, positionMaintMargin :: !(Maybe Double)
, positionSessionMargin :: !(Maybe Double)
, positionTargetExcessMargin :: !(Maybe Double)
, positionVarMargin :: !(Maybe Double)
, positionRealisedGrossPnl :: !(Maybe Double)
, positionRealisedTax :: !(Maybe Double)
, positionRealisedPnl :: !(Maybe Double)
, positionUnrealisedGrossPnl :: !(Maybe Double)
, positionLongBankrupt :: !(Maybe Double)
, positionShortBankrupt :: !(Maybe Double)
, positionTaxBase :: !(Maybe Double)
, positionIndicativeTaxRate :: !(Maybe Double)
, positionIndicativeTax :: !(Maybe Double)
, positionUnrealisedTax :: !(Maybe Double)
, positionUnrealisedPnl :: !(Maybe Double)
, positionUnrealisedPnlPcnt :: !(Maybe Double)
, positionUnrealisedRoePcnt :: !(Maybe Double)
, positionSimpleQty :: !(Maybe Double)
, positionSimpleCost :: !(Maybe Double)
, positionSimpleValue :: !(Maybe Double)
, positionSimplePnl :: !(Maybe Double)
, positionSimplePnlPcnt :: !(Maybe Double)
, positionAvgCostPrice :: !(Maybe Double)
, positionAvgEntryPrice :: !(Maybe Double)
, positionBreakEvenPrice :: !(Maybe Double)
, positionMarginCallPrice :: !(Maybe Double)
, positionLiquidationPrice :: !(Maybe Double)
, positionBankruptPrice :: !(Maybe Double)
, positionTimestamp :: !(Maybe DateTime)
, positionLastPrice :: !(Maybe Double)
, positionLastValue :: !(Maybe Double)
} deriving (P.Show, P.Eq, P.Typeable)
instance A.FromJSON Position where
parseJSON = A.withObject "Position" $ \o ->
Position
<$> (o .: "account")
<*> (o .: "symbol")
<*> (o .: "currency")
<*> (o .:? "underlying")
<*> (o .:? "quoteCurrency")
<*> (o .:? "commission")
<*> (o .:? "initMarginReq")
<*> (o .:? "maintMarginReq")
<*> (o .:? "riskLimit")
<*> (o .:? "leverage")
<*> (o .:? "crossMargin")
<*> (o .:? "deleveragePercentile")
<*> (o .:? "rebalancedPnl")
<*> (o .:? "prevRealisedPnl")
<*> (o .:? "prevUnrealisedPnl")
<*> (o .:? "prevClosePrice")
<*> (o .:? "openingTimestamp")
<*> (o .:? "openingQty")
<*> (o .:? "openingCost")
<*> (o .:? "openingComm")
<*> (o .:? "openOrderBuyQty")
<*> (o .:? "openOrderBuyCost")
<*> (o .:? "openOrderBuyPremium")
<*> (o .:? "openOrderSellQty")
<*> (o .:? "openOrderSellCost")
<*> (o .:? "openOrderSellPremium")
<*> (o .:? "execBuyQty")
<*> (o .:? "execBuyCost")
<*> (o .:? "execSellQty")
<*> (o .:? "execSellCost")
<*> (o .:? "execQty")
<*> (o .:? "execCost")
<*> (o .:? "execComm")
<*> (o .:? "currentTimestamp")
<*> (o .:? "currentQty")
<*> (o .:? "currentCost")
<*> (o .:? "currentComm")
<*> (o .:? "realisedCost")
<*> (o .:? "unrealisedCost")
<*> (o .:? "grossOpenCost")
<*> (o .:? "grossOpenPremium")
<*> (o .:? "grossExecCost")
<*> (o .:? "isOpen")
<*> (o .:? "markPrice")
<*> (o .:? "markValue")
<*> (o .:? "riskValue")
<*> (o .:? "homeNotional")
<*> (o .:? "foreignNotional")
<*> (o .:? "posState")
<*> (o .:? "posCost")
<*> (o .:? "posCost2")
<*> (o .:? "posCross")
<*> (o .:? "posInit")
<*> (o .:? "posComm")
<*> (o .:? "posLoss")
<*> (o .:? "posMargin")
<*> (o .:? "posMaint")
<*> (o .:? "posAllowance")
<*> (o .:? "taxableMargin")
<*> (o .:? "initMargin")
<*> (o .:? "maintMargin")
<*> (o .:? "sessionMargin")
<*> (o .:? "targetExcessMargin")
<*> (o .:? "varMargin")
<*> (o .:? "realisedGrossPnl")
<*> (o .:? "realisedTax")
<*> (o .:? "realisedPnl")
<*> (o .:? "unrealisedGrossPnl")
<*> (o .:? "longBankrupt")
<*> (o .:? "shortBankrupt")
<*> (o .:? "taxBase")
<*> (o .:? "indicativeTaxRate")
<*> (o .:? "indicativeTax")
<*> (o .:? "unrealisedTax")
<*> (o .:? "unrealisedPnl")
<*> (o .:? "unrealisedPnlPcnt")
<*> (o .:? "unrealisedRoePcnt")
<*> (o .:? "simpleQty")
<*> (o .:? "simpleCost")
<*> (o .:? "simpleValue")
<*> (o .:? "simplePnl")
<*> (o .:? "simplePnlPcnt")
<*> (o .:? "avgCostPrice")
<*> (o .:? "avgEntryPrice")
<*> (o .:? "breakEvenPrice")
<*> (o .:? "marginCallPrice")
<*> (o .:? "liquidationPrice")
<*> (o .:? "bankruptPrice")
<*> (o .:? "timestamp")
<*> (o .:? "lastPrice")
<*> (o .:? "lastValue")
instance A.ToJSON Position where
toJSON Position {..} =
_omitNulls
[ "account" .= positionAccount
, "symbol" .= positionSymbol
, "currency" .= positionCurrency
, "underlying" .= positionUnderlying
, "quoteCurrency" .= positionQuoteCurrency
, "commission" .= positionCommission
, "initMarginReq" .= positionInitMarginReq
, "maintMarginReq" .= positionMaintMarginReq
, "riskLimit" .= positionRiskLimit
, "leverage" .= positionLeverage
, "crossMargin" .= positionCrossMargin
, "deleveragePercentile" .= positionDeleveragePercentile
, "rebalancedPnl" .= positionRebalancedPnl
, "prevRealisedPnl" .= positionPrevRealisedPnl
, "prevUnrealisedPnl" .= positionPrevUnrealisedPnl
, "prevClosePrice" .= positionPrevClosePrice
, "openingTimestamp" .= positionOpeningTimestamp
, "openingQty" .= positionOpeningQty
, "openingCost" .= positionOpeningCost
, "openingComm" .= positionOpeningComm
, "openOrderBuyQty" .= positionOpenOrderBuyQty
, "openOrderBuyCost" .= positionOpenOrderBuyCost
, "openOrderBuyPremium" .= positionOpenOrderBuyPremium
, "openOrderSellQty" .= positionOpenOrderSellQty
, "openOrderSellCost" .= positionOpenOrderSellCost
, "openOrderSellPremium" .= positionOpenOrderSellPremium
, "execBuyQty" .= positionExecBuyQty
, "execBuyCost" .= positionExecBuyCost
, "execSellQty" .= positionExecSellQty
, "execSellCost" .= positionExecSellCost
, "execQty" .= positionExecQty
, "execCost" .= positionExecCost
, "execComm" .= positionExecComm
, "currentTimestamp" .= positionCurrentTimestamp
, "currentQty" .= positionCurrentQty
, "currentCost" .= positionCurrentCost
, "currentComm" .= positionCurrentComm
, "realisedCost" .= positionRealisedCost
, "unrealisedCost" .= positionUnrealisedCost
, "grossOpenCost" .= positionGrossOpenCost
, "grossOpenPremium" .= positionGrossOpenPremium
, "grossExecCost" .= positionGrossExecCost
, "isOpen" .= positionIsOpen
, "markPrice" .= positionMarkPrice
, "markValue" .= positionMarkValue
, "riskValue" .= positionRiskValue
, "homeNotional" .= positionHomeNotional
, "foreignNotional" .= positionForeignNotional
, "posState" .= positionPosState
, "posCost" .= positionPosCost
, "posCost2" .= positionPosCost2
, "posCross" .= positionPosCross
, "posInit" .= positionPosInit
, "posComm" .= positionPosComm
, "posLoss" .= positionPosLoss
, "posMargin" .= positionPosMargin
, "posMaint" .= positionPosMaint
, "posAllowance" .= positionPosAllowance
, "taxableMargin" .= positionTaxableMargin
, "initMargin" .= positionInitMargin
, "maintMargin" .= positionMaintMargin
, "sessionMargin" .= positionSessionMargin
, "targetExcessMargin" .= positionTargetExcessMargin
, "varMargin" .= positionVarMargin
, "realisedGrossPnl" .= positionRealisedGrossPnl
, "realisedTax" .= positionRealisedTax
, "realisedPnl" .= positionRealisedPnl
, "unrealisedGrossPnl" .= positionUnrealisedGrossPnl
, "longBankrupt" .= positionLongBankrupt
, "shortBankrupt" .= positionShortBankrupt
, "taxBase" .= positionTaxBase
, "indicativeTaxRate" .= positionIndicativeTaxRate
, "indicativeTax" .= positionIndicativeTax
, "unrealisedTax" .= positionUnrealisedTax
, "unrealisedPnl" .= positionUnrealisedPnl
, "unrealisedPnlPcnt" .= positionUnrealisedPnlPcnt
, "unrealisedRoePcnt" .= positionUnrealisedRoePcnt
, "simpleQty" .= positionSimpleQty
, "simpleCost" .= positionSimpleCost
, "simpleValue" .= positionSimpleValue
, "simplePnl" .= positionSimplePnl
, "simplePnlPcnt" .= positionSimplePnlPcnt
, "avgCostPrice" .= positionAvgCostPrice
, "avgEntryPrice" .= positionAvgEntryPrice
, "breakEvenPrice" .= positionBreakEvenPrice
, "marginCallPrice" .= positionMarginCallPrice
, "liquidationPrice" .= positionLiquidationPrice
, "bankruptPrice" .= positionBankruptPrice
, "timestamp" .= positionTimestamp
, "lastPrice" .= positionLastPrice
, "lastValue" .= positionLastValue
]
mkPosition
:: Double
-> Text
-> Text
-> Position
mkPosition positionAccount positionSymbol positionCurrency =
Position
{ positionAccount
, positionSymbol
, positionCurrency
, positionUnderlying = Nothing
, positionQuoteCurrency = Nothing
, positionCommission = Nothing
, positionInitMarginReq = Nothing
, positionMaintMarginReq = Nothing
, positionRiskLimit = Nothing
, positionLeverage = Nothing
, positionCrossMargin = Nothing
, positionDeleveragePercentile = Nothing
, positionRebalancedPnl = Nothing
, positionPrevRealisedPnl = Nothing
, positionPrevUnrealisedPnl = Nothing
, positionPrevClosePrice = Nothing
, positionOpeningTimestamp = Nothing
, positionOpeningQty = Nothing
, positionOpeningCost = Nothing
, positionOpeningComm = Nothing
, positionOpenOrderBuyQty = Nothing
, positionOpenOrderBuyCost = Nothing
, positionOpenOrderBuyPremium = Nothing
, positionOpenOrderSellQty = Nothing
, positionOpenOrderSellCost = Nothing
, positionOpenOrderSellPremium = Nothing
, positionExecBuyQty = Nothing
, positionExecBuyCost = Nothing
, positionExecSellQty = Nothing
, positionExecSellCost = Nothing
, positionExecQty = Nothing
, positionExecCost = Nothing
, positionExecComm = Nothing
, positionCurrentTimestamp = Nothing
, positionCurrentQty = Nothing
, positionCurrentCost = Nothing
, positionCurrentComm = Nothing
, positionRealisedCost = Nothing
, positionUnrealisedCost = Nothing
, positionGrossOpenCost = Nothing
, positionGrossOpenPremium = Nothing
, positionGrossExecCost = Nothing
, positionIsOpen = Nothing
, positionMarkPrice = Nothing
, positionMarkValue = Nothing
, positionRiskValue = Nothing
, positionHomeNotional = Nothing
, positionForeignNotional = Nothing
, positionPosState = Nothing
, positionPosCost = Nothing
, positionPosCost2 = Nothing
, positionPosCross = Nothing
, positionPosInit = Nothing
, positionPosComm = Nothing
, positionPosLoss = Nothing
, positionPosMargin = Nothing
, positionPosMaint = Nothing
, positionPosAllowance = Nothing
, positionTaxableMargin = Nothing
, positionInitMargin = Nothing
, positionMaintMargin = Nothing
, positionSessionMargin = Nothing
, positionTargetExcessMargin = Nothing
, positionVarMargin = Nothing
, positionRealisedGrossPnl = Nothing
, positionRealisedTax = Nothing
, positionRealisedPnl = Nothing
, positionUnrealisedGrossPnl = Nothing
, positionLongBankrupt = Nothing
, positionShortBankrupt = Nothing
, positionTaxBase = Nothing
, positionIndicativeTaxRate = Nothing
, positionIndicativeTax = Nothing
, positionUnrealisedTax = Nothing
, positionUnrealisedPnl = Nothing
, positionUnrealisedPnlPcnt = Nothing
, positionUnrealisedRoePcnt = Nothing
, positionSimpleQty = Nothing
, positionSimpleCost = Nothing
, positionSimpleValue = Nothing
, positionSimplePnl = Nothing
, positionSimplePnlPcnt = Nothing
, positionAvgCostPrice = Nothing
, positionAvgEntryPrice = Nothing
, positionBreakEvenPrice = Nothing
, positionMarginCallPrice = Nothing
, positionLiquidationPrice = Nothing
, positionBankruptPrice = Nothing
, positionTimestamp = Nothing
, positionLastPrice = Nothing
, positionLastValue = Nothing
}
data Quote = Quote
{ quoteTimestamp :: !(DateTime)
, quoteSymbol :: !(Text)
, quoteBidSize :: !(Maybe Double)
, quoteBidPrice :: !(Maybe Double)
, quoteAskPrice :: !(Maybe Double)
, quoteAskSize :: !(Maybe Double)
} deriving (P.Show, P.Eq, P.Typeable)
instance A.FromJSON Quote where
parseJSON = A.withObject "Quote" $ \o ->
Quote
<$> (o .: "timestamp")
<*> (o .: "symbol")
<*> (o .:? "bidSize")
<*> (o .:? "bidPrice")
<*> (o .:? "askPrice")
<*> (o .:? "askSize")
instance A.ToJSON Quote where
toJSON Quote {..} =
_omitNulls
[ "timestamp" .= quoteTimestamp
, "symbol" .= quoteSymbol
, "bidSize" .= quoteBidSize
, "bidPrice" .= quoteBidPrice
, "askPrice" .= quoteAskPrice
, "askSize" .= quoteAskSize
]
mkQuote
:: DateTime
-> Text
-> Quote
mkQuote quoteTimestamp quoteSymbol =
Quote
{ quoteTimestamp
, quoteSymbol
, quoteBidSize = Nothing
, quoteBidPrice = Nothing
, quoteAskPrice = Nothing
, quoteAskSize = Nothing
}
data Settlement = Settlement
{ settlementTimestamp :: !(DateTime)
, settlementSymbol :: !(Text)
, settlementSettlementType :: !(Maybe Text)
, settlementSettledPrice :: !(Maybe Double)
, settlementBankrupt :: !(Maybe Double)
, settlementTaxBase :: !(Maybe Double)
, settlementTaxRate :: !(Maybe Double)
} deriving (P.Show, P.Eq, P.Typeable)
instance A.FromJSON Settlement where
parseJSON = A.withObject "Settlement" $ \o ->
Settlement
<$> (o .: "timestamp")
<*> (o .: "symbol")
<*> (o .:? "settlementType")
<*> (o .:? "settledPrice")
<*> (o .:? "bankrupt")
<*> (o .:? "taxBase")
<*> (o .:? "taxRate")
instance A.ToJSON Settlement where
toJSON Settlement {..} =
_omitNulls
[ "timestamp" .= settlementTimestamp
, "symbol" .= settlementSymbol
, "settlementType" .= settlementSettlementType
, "settledPrice" .= settlementSettledPrice
, "bankrupt" .= settlementBankrupt
, "taxBase" .= settlementTaxBase
, "taxRate" .= settlementTaxRate
]
mkSettlement
:: DateTime
-> Text
-> Settlement
mkSettlement settlementTimestamp settlementSymbol =
Settlement
{ settlementTimestamp
, settlementSymbol
, settlementSettlementType = Nothing
, settlementSettledPrice = Nothing
, settlementBankrupt = Nothing
, settlementTaxBase = Nothing
, settlementTaxRate = Nothing
}
data Stats = Stats
{ statsRootSymbol :: !(Text)
, statsCurrency :: !(Maybe Text)
, statsVolume24h :: !(Maybe Double)
, statsTurnover24h :: !(Maybe Double)
, statsOpenInterest :: !(Maybe Double)
, statsOpenValue :: !(Maybe Double)
} deriving (P.Show, P.Eq, P.Typeable)
instance A.FromJSON Stats where
parseJSON = A.withObject "Stats" $ \o ->
Stats
<$> (o .: "rootSymbol")
<*> (o .:? "currency")
<*> (o .:? "volume24h")
<*> (o .:? "turnover24h")
<*> (o .:? "openInterest")
<*> (o .:? "openValue")
instance A.ToJSON Stats where
toJSON Stats {..} =
_omitNulls
[ "rootSymbol" .= statsRootSymbol
, "currency" .= statsCurrency
, "volume24h" .= statsVolume24h
, "turnover24h" .= statsTurnover24h
, "openInterest" .= statsOpenInterest
, "openValue" .= statsOpenValue
]
mkStats
:: Text
-> Stats
mkStats statsRootSymbol =
Stats
{ statsRootSymbol
, statsCurrency = Nothing
, statsVolume24h = Nothing
, statsTurnover24h = Nothing
, statsOpenInterest = Nothing
, statsOpenValue = Nothing
}
data StatsHistory = StatsHistory
{ statsHistoryDate :: !(DateTime)
, statsHistoryRootSymbol :: !(Text)
, statsHistoryCurrency :: !(Maybe Text)
, statsHistoryVolume :: !(Maybe Double)
, statsHistoryTurnover :: !(Maybe Double)
} deriving (P.Show, P.Eq, P.Typeable)
instance A.FromJSON StatsHistory where
parseJSON = A.withObject "StatsHistory" $ \o ->
StatsHistory
<$> (o .: "date")
<*> (o .: "rootSymbol")
<*> (o .:? "currency")
<*> (o .:? "volume")
<*> (o .:? "turnover")
instance A.ToJSON StatsHistory where
toJSON StatsHistory {..} =
_omitNulls
[ "date" .= statsHistoryDate
, "rootSymbol" .= statsHistoryRootSymbol
, "currency" .= statsHistoryCurrency
, "volume" .= statsHistoryVolume
, "turnover" .= statsHistoryTurnover
]
mkStatsHistory
:: DateTime
-> Text
-> StatsHistory
mkStatsHistory statsHistoryDate statsHistoryRootSymbol =
StatsHistory
{ statsHistoryDate
, statsHistoryRootSymbol
, statsHistoryCurrency = Nothing
, statsHistoryVolume = Nothing
, statsHistoryTurnover = Nothing
}
data StatsUSD = StatsUSD
{ statsUSDRootSymbol :: !(Text)
, statsUSDCurrency :: !(Maybe Text)
, statsUSDTurnover24h :: !(Maybe Double)
, statsUSDTurnover30d :: !(Maybe Double)
, statsUSDTurnover365d :: !(Maybe Double)
, statsUSDTurnover :: !(Maybe Double)
} deriving (P.Show, P.Eq, P.Typeable)
instance A.FromJSON StatsUSD where
parseJSON = A.withObject "StatsUSD" $ \o ->
StatsUSD
<$> (o .: "rootSymbol")
<*> (o .:? "currency")
<*> (o .:? "turnover24h")
<*> (o .:? "turnover30d")
<*> (o .:? "turnover365d")
<*> (o .:? "turnover")
instance A.ToJSON StatsUSD where
toJSON StatsUSD {..} =
_omitNulls
[ "rootSymbol" .= statsUSDRootSymbol
, "currency" .= statsUSDCurrency
, "turnover24h" .= statsUSDTurnover24h
, "turnover30d" .= statsUSDTurnover30d
, "turnover365d" .= statsUSDTurnover365d
, "turnover" .= statsUSDTurnover
]
mkStatsUSD
:: Text
-> StatsUSD
mkStatsUSD statsUSDRootSymbol =
StatsUSD
{ statsUSDRootSymbol
, statsUSDCurrency = Nothing
, statsUSDTurnover24h = Nothing
, statsUSDTurnover30d = Nothing
, statsUSDTurnover365d = Nothing
, statsUSDTurnover = Nothing
}
data Trade = Trade
{ tradeTimestamp :: !(DateTime)
, tradeSymbol :: !(Text)
, tradeSide :: !(Maybe Text)
, tradeSize :: !(Maybe Double)
, tradePrice :: !(Maybe Double)
, tradeTickDirection :: !(Maybe Text)
, tradeTrdMatchId :: !(Maybe Text)
, tradeGrossValue :: !(Maybe Double)
, tradeHomeNotional :: !(Maybe Double)
, tradeForeignNotional :: !(Maybe Double)
} deriving (P.Show, P.Eq, P.Typeable)
instance A.FromJSON Trade where
parseJSON = A.withObject "Trade" $ \o ->
Trade
<$> (o .: "timestamp")
<*> (o .: "symbol")
<*> (o .:? "side")
<*> (o .:? "size")
<*> (o .:? "price")
<*> (o .:? "tickDirection")
<*> (o .:? "trdMatchID")
<*> (o .:? "grossValue")
<*> (o .:? "homeNotional")
<*> (o .:? "foreignNotional")
instance A.ToJSON Trade where
toJSON Trade {..} =
_omitNulls
[ "timestamp" .= tradeTimestamp
, "symbol" .= tradeSymbol
, "side" .= tradeSide
, "size" .= tradeSize
, "price" .= tradePrice
, "tickDirection" .= tradeTickDirection
, "trdMatchID" .= tradeTrdMatchId
, "grossValue" .= tradeGrossValue
, "homeNotional" .= tradeHomeNotional
, "foreignNotional" .= tradeForeignNotional
]
mkTrade
:: DateTime
-> Text
-> Trade
mkTrade tradeTimestamp tradeSymbol =
Trade
{ tradeTimestamp
, tradeSymbol
, tradeSide = Nothing
, tradeSize = Nothing
, tradePrice = Nothing
, tradeTickDirection = Nothing
, tradeTrdMatchId = Nothing
, tradeGrossValue = Nothing
, tradeHomeNotional = Nothing
, tradeForeignNotional = Nothing
}
data TradeBin = TradeBin
{ tradeBinTimestamp :: !(DateTime)
, tradeBinSymbol :: !(Text)
, tradeBinOpen :: !(Maybe Double)
, tradeBinHigh :: !(Maybe Double)
, tradeBinLow :: !(Maybe Double)
, tradeBinClose :: !(Maybe Double)
, tradeBinTrades :: !(Maybe Double)
, tradeBinVolume :: !(Maybe Double)
, tradeBinVwap :: !(Maybe Double)
, tradeBinLastSize :: !(Maybe Double)
, tradeBinTurnover :: !(Maybe Double)
, tradeBinHomeNotional :: !(Maybe Double)
, tradeBinForeignNotional :: !(Maybe Double)
} deriving (P.Show, P.Eq, P.Typeable)
instance A.FromJSON TradeBin where
parseJSON = A.withObject "TradeBin" $ \o ->
TradeBin
<$> (o .: "timestamp")
<*> (o .: "symbol")
<*> (o .:? "open")
<*> (o .:? "high")
<*> (o .:? "low")
<*> (o .:? "close")
<*> (o .:? "trades")
<*> (o .:? "volume")
<*> (o .:? "vwap")
<*> (o .:? "lastSize")
<*> (o .:? "turnover")
<*> (o .:? "homeNotional")
<*> (o .:? "foreignNotional")
instance A.ToJSON TradeBin where
toJSON TradeBin {..} =
_omitNulls
[ "timestamp" .= tradeBinTimestamp
, "symbol" .= tradeBinSymbol
, "open" .= tradeBinOpen
, "high" .= tradeBinHigh
, "low" .= tradeBinLow
, "close" .= tradeBinClose
, "trades" .= tradeBinTrades
, "volume" .= tradeBinVolume
, "vwap" .= tradeBinVwap
, "lastSize" .= tradeBinLastSize
, "turnover" .= tradeBinTurnover
, "homeNotional" .= tradeBinHomeNotional
, "foreignNotional" .= tradeBinForeignNotional
]
mkTradeBin
:: DateTime
-> Text
-> TradeBin
mkTradeBin tradeBinTimestamp tradeBinSymbol =
TradeBin
{ tradeBinTimestamp
, tradeBinSymbol
, tradeBinOpen = Nothing
, tradeBinHigh = Nothing
, tradeBinLow = Nothing
, tradeBinClose = Nothing
, tradeBinTrades = Nothing
, tradeBinVolume = Nothing
, tradeBinVwap = Nothing
, tradeBinLastSize = Nothing
, tradeBinTurnover = Nothing
, tradeBinHomeNotional = Nothing
, tradeBinForeignNotional = Nothing
}
data Transaction = Transaction
{ transactionTransactId :: !(Text)
, transactionAccount :: !(Maybe Double)
, transactionCurrency :: !(Maybe Text)
, transactionTransactType :: !(Maybe Text)
, transactionAmount :: !(Maybe Double)
, transactionFee :: !(Maybe Double)
, transactionTransactStatus :: !(Maybe Text)
, transactionAddress :: !(Maybe Text)
, transactionTx :: !(Maybe Text)
, transactionText :: !(Maybe Text)
, transactionTransactTime :: !(Maybe DateTime)
, transactionTimestamp :: !(Maybe DateTime)
} deriving (P.Show, P.Eq, P.Typeable)
instance A.FromJSON Transaction where
parseJSON = A.withObject "Transaction" $ \o ->
Transaction
<$> (o .: "transactID")
<*> (o .:? "account")
<*> (o .:? "currency")
<*> (o .:? "transactType")
<*> (o .:? "amount")
<*> (o .:? "fee")
<*> (o .:? "transactStatus")
<*> (o .:? "address")
<*> (o .:? "tx")
<*> (o .:? "text")
<*> (o .:? "transactTime")
<*> (o .:? "timestamp")
instance A.ToJSON Transaction where
toJSON Transaction {..} =
_omitNulls
[ "transactID" .= transactionTransactId
, "account" .= transactionAccount
, "currency" .= transactionCurrency
, "transactType" .= transactionTransactType
, "amount" .= transactionAmount
, "fee" .= transactionFee
, "transactStatus" .= transactionTransactStatus
, "address" .= transactionAddress
, "tx" .= transactionTx
, "text" .= transactionText
, "transactTime" .= transactionTransactTime
, "timestamp" .= transactionTimestamp
]
mkTransaction
:: Text
-> Transaction
mkTransaction transactionTransactId =
Transaction
{ transactionTransactId
, transactionAccount = Nothing
, transactionCurrency = Nothing
, transactionTransactType = Nothing
, transactionAmount = Nothing
, transactionFee = Nothing
, transactionTransactStatus = Nothing
, transactionAddress = Nothing
, transactionTx = Nothing
, transactionText = Nothing
, transactionTransactTime = Nothing
, transactionTimestamp = Nothing
}
data User = User
{ userId :: !(Maybe Double)
, userOwnerId :: !(Maybe Double)
, userFirstname :: !(Maybe Text)
, userLastname :: !(Maybe Text)
, userUsername :: !(Text)
, userEmail :: !(Text)
, userPhone :: !(Maybe Text)
, userCreated :: !(Maybe DateTime)
, userLastUpdated :: !(Maybe DateTime)
, userPreferences :: !(Maybe UserPreferences)
, userTfaEnabled :: !(Maybe Text)
, userAffiliateId :: !(Maybe Text)
, userPgpPubKey :: !(Maybe Text)
, userCountry :: !(Maybe Text)
} deriving (P.Show, P.Eq, P.Typeable)
instance A.FromJSON User where
parseJSON = A.withObject "User" $ \o ->
User
<$> (o .:? "id")
<*> (o .:? "ownerId")
<*> (o .:? "firstname")
<*> (o .:? "lastname")
<*> (o .: "username")
<*> (o .: "email")
<*> (o .:? "phone")
<*> (o .:? "created")
<*> (o .:? "lastUpdated")
<*> (o .:? "preferences")
<*> (o .:? "TFAEnabled")
<*> (o .:? "affiliateID")
<*> (o .:? "pgpPubKey")
<*> (o .:? "country")
instance A.ToJSON User where
toJSON User {..} =
_omitNulls
[ "id" .= userId
, "ownerId" .= userOwnerId
, "firstname" .= userFirstname
, "lastname" .= userLastname
, "username" .= userUsername
, "email" .= userEmail
, "phone" .= userPhone
, "created" .= userCreated
, "lastUpdated" .= userLastUpdated
, "preferences" .= userPreferences
, "TFAEnabled" .= userTfaEnabled
, "affiliateID" .= userAffiliateId
, "pgpPubKey" .= userPgpPubKey
, "country" .= userCountry
]
mkUser
:: Text
-> Text
-> User
mkUser userUsername userEmail =
User
{ userId = Nothing
, userOwnerId = Nothing
, userFirstname = Nothing
, userLastname = Nothing
, userUsername
, userEmail
, userPhone = Nothing
, userCreated = Nothing
, userLastUpdated = Nothing
, userPreferences = Nothing
, userTfaEnabled = Nothing
, userAffiliateId = Nothing
, userPgpPubKey = Nothing
, userCountry = Nothing
}
data UserCommission = UserCommission
{ userCommissionMakerFee :: !(Maybe Double)
, userCommissionTakerFee :: !(Maybe Double)
, userCommissionSettlementFee :: !(Maybe Double)
, userCommissionMaxFee :: !(Maybe Double)
} deriving (P.Show, P.Eq, P.Typeable)
instance A.FromJSON UserCommission where
parseJSON = A.withObject "UserCommission" $ \o ->
UserCommission
<$> (o .:? "makerFee")
<*> (o .:? "takerFee")
<*> (o .:? "settlementFee")
<*> (o .:? "maxFee")
instance A.ToJSON UserCommission where
toJSON UserCommission {..} =
_omitNulls
[ "makerFee" .= userCommissionMakerFee
, "takerFee" .= userCommissionTakerFee
, "settlementFee" .= userCommissionSettlementFee
, "maxFee" .= userCommissionMaxFee
]
mkUserCommission
:: UserCommission
mkUserCommission =
UserCommission
{ userCommissionMakerFee = Nothing
, userCommissionTakerFee = Nothing
, userCommissionSettlementFee = Nothing
, userCommissionMaxFee = Nothing
}
data UserPreferences = UserPreferences
{ userPreferencesAlertOnLiquidations :: !(Maybe Bool)
, userPreferencesAnimationsEnabled :: !(Maybe Bool)
, userPreferencesAnnouncementsLastSeen :: !(Maybe DateTime)
, userPreferencesChatChannelId :: !(Maybe Double)
, userPreferencesColorTheme :: !(Maybe Text)
, userPreferencesCurrency :: !(Maybe Text)
, userPreferencesDebug :: !(Maybe Bool)
, userPreferencesDisableEmails :: !(Maybe [Text])
, userPreferencesHideConfirmDialogs :: !(Maybe [Text])
, userPreferencesHideConnectionModal :: !(Maybe Bool)
, userPreferencesHideFromLeaderboard :: !(Maybe Bool)
, userPreferencesHideNameFromLeaderboard :: !(Maybe Bool)
, userPreferencesHideNotifications :: !(Maybe [Text])
, userPreferencesLocale :: !(Maybe Text)
, userPreferencesMsgsSeen :: !(Maybe [Text])
, userPreferencesOrderBookBinning :: !(Maybe A.Value)
, userPreferencesOrderBookType :: !(Maybe Text)
, userPreferencesOrderClearImmediate :: !(Maybe Bool)
, userPreferencesOrderControlsPlusMinus :: !(Maybe Bool)
, userPreferencesSounds :: !(Maybe [Text])
, userPreferencesStrictIpCheck :: !(Maybe Bool)
, userPreferencesStrictTimeout :: !(Maybe Bool)
, userPreferencesTickerGroup :: !(Maybe Text)
, userPreferencesTickerPinned :: !(Maybe Bool)
, userPreferencesTradeLayout :: !(Maybe Text)
} deriving (P.Show, P.Eq, P.Typeable)
instance A.FromJSON UserPreferences where
parseJSON = A.withObject "UserPreferences" $ \o ->
UserPreferences
<$> (o .:? "alertOnLiquidations")
<*> (o .:? "animationsEnabled")
<*> (o .:? "announcementsLastSeen")
<*> (o .:? "chatChannelID")
<*> (o .:? "colorTheme")
<*> (o .:? "currency")
<*> (o .:? "debug")
<*> (o .:? "disableEmails")
<*> (o .:? "hideConfirmDialogs")
<*> (o .:? "hideConnectionModal")
<*> (o .:? "hideFromLeaderboard")
<*> (o .:? "hideNameFromLeaderboard")
<*> (o .:? "hideNotifications")
<*> (o .:? "locale")
<*> (o .:? "msgsSeen")
<*> (o .:? "orderBookBinning")
<*> (o .:? "orderBookType")
<*> (o .:? "orderClearImmediate")
<*> (o .:? "orderControlsPlusMinus")
<*> (o .:? "sounds")
<*> (o .:? "strictIPCheck")
<*> (o .:? "strictTimeout")
<*> (o .:? "tickerGroup")
<*> (o .:? "tickerPinned")
<*> (o .:? "tradeLayout")
instance A.ToJSON UserPreferences where
toJSON UserPreferences {..} =
_omitNulls
[ "alertOnLiquidations" .= userPreferencesAlertOnLiquidations
, "animationsEnabled" .= userPreferencesAnimationsEnabled
, "announcementsLastSeen" .= userPreferencesAnnouncementsLastSeen
, "chatChannelID" .= userPreferencesChatChannelId
, "colorTheme" .= userPreferencesColorTheme
, "currency" .= userPreferencesCurrency
, "debug" .= userPreferencesDebug
, "disableEmails" .= userPreferencesDisableEmails
, "hideConfirmDialogs" .= userPreferencesHideConfirmDialogs
, "hideConnectionModal" .= userPreferencesHideConnectionModal
, "hideFromLeaderboard" .= userPreferencesHideFromLeaderboard
, "hideNameFromLeaderboard" .= userPreferencesHideNameFromLeaderboard
, "hideNotifications" .= userPreferencesHideNotifications
, "locale" .= userPreferencesLocale
, "msgsSeen" .= userPreferencesMsgsSeen
, "orderBookBinning" .= userPreferencesOrderBookBinning
, "orderBookType" .= userPreferencesOrderBookType
, "orderClearImmediate" .= userPreferencesOrderClearImmediate
, "orderControlsPlusMinus" .= userPreferencesOrderControlsPlusMinus
, "sounds" .= userPreferencesSounds
, "strictIPCheck" .= userPreferencesStrictIpCheck
, "strictTimeout" .= userPreferencesStrictTimeout
, "tickerGroup" .= userPreferencesTickerGroup
, "tickerPinned" .= userPreferencesTickerPinned
, "tradeLayout" .= userPreferencesTradeLayout
]
mkUserPreferences
:: UserPreferences
mkUserPreferences =
UserPreferences
{ userPreferencesAlertOnLiquidations = Nothing
, userPreferencesAnimationsEnabled = Nothing
, userPreferencesAnnouncementsLastSeen = Nothing
, userPreferencesChatChannelId = Nothing
, userPreferencesColorTheme = Nothing
, userPreferencesCurrency = Nothing
, userPreferencesDebug = Nothing
, userPreferencesDisableEmails = Nothing
, userPreferencesHideConfirmDialogs = Nothing
, userPreferencesHideConnectionModal = Nothing
, userPreferencesHideFromLeaderboard = Nothing
, userPreferencesHideNameFromLeaderboard = Nothing
, userPreferencesHideNotifications = Nothing
, userPreferencesLocale = Nothing
, userPreferencesMsgsSeen = Nothing
, userPreferencesOrderBookBinning = Nothing
, userPreferencesOrderBookType = Nothing
, userPreferencesOrderClearImmediate = Nothing
, userPreferencesOrderControlsPlusMinus = Nothing
, userPreferencesSounds = Nothing
, userPreferencesStrictIpCheck = Nothing
, userPreferencesStrictTimeout = Nothing
, userPreferencesTickerGroup = Nothing
, userPreferencesTickerPinned = Nothing
, userPreferencesTradeLayout = Nothing
}
data Wallet = Wallet
{ walletAccount :: !(Double)
, walletCurrency :: !(Text)
, walletPrevDeposited :: !(Maybe Double)
, walletPrevWithdrawn :: !(Maybe Double)
, walletPrevTransferIn :: !(Maybe Double)
, walletPrevTransferOut :: !(Maybe Double)
, walletPrevAmount :: !(Maybe Double)
, walletPrevTimestamp :: !(Maybe DateTime)
, walletDeltaDeposited :: !(Maybe Double)
, walletDeltaWithdrawn :: !(Maybe Double)
, walletDeltaTransferIn :: !(Maybe Double)
, walletDeltaTransferOut :: !(Maybe Double)
, walletDeltaAmount :: !(Maybe Double)
, walletDeposited :: !(Maybe Double)
, walletWithdrawn :: !(Maybe Double)
, walletTransferIn :: !(Maybe Double)
, walletTransferOut :: !(Maybe Double)
, walletAmount :: !(Maybe Double)
, walletPendingCredit :: !(Maybe Double)
, walletPendingDebit :: !(Maybe Double)
, walletConfirmedDebit :: !(Maybe Double)
, walletTimestamp :: !(Maybe DateTime)
, walletAddr :: !(Maybe Text)
, walletScript :: !(Maybe Text)
, walletWithdrawalLock :: !(Maybe [Text])
} deriving (P.Show, P.Eq, P.Typeable)
instance A.FromJSON Wallet where
parseJSON = A.withObject "Wallet" $ \o ->
Wallet
<$> (o .: "account")
<*> (o .: "currency")
<*> (o .:? "prevDeposited")
<*> (o .:? "prevWithdrawn")
<*> (o .:? "prevTransferIn")
<*> (o .:? "prevTransferOut")
<*> (o .:? "prevAmount")
<*> (o .:? "prevTimestamp")
<*> (o .:? "deltaDeposited")
<*> (o .:? "deltaWithdrawn")
<*> (o .:? "deltaTransferIn")
<*> (o .:? "deltaTransferOut")
<*> (o .:? "deltaAmount")
<*> (o .:? "deposited")
<*> (o .:? "withdrawn")
<*> (o .:? "transferIn")
<*> (o .:? "transferOut")
<*> (o .:? "amount")
<*> (o .:? "pendingCredit")
<*> (o .:? "pendingDebit")
<*> (o .:? "confirmedDebit")
<*> (o .:? "timestamp")
<*> (o .:? "addr")
<*> (o .:? "script")
<*> (o .:? "withdrawalLock")
instance A.ToJSON Wallet where
toJSON Wallet {..} =
_omitNulls
[ "account" .= walletAccount
, "currency" .= walletCurrency
, "prevDeposited" .= walletPrevDeposited
, "prevWithdrawn" .= walletPrevWithdrawn
, "prevTransferIn" .= walletPrevTransferIn
, "prevTransferOut" .= walletPrevTransferOut
, "prevAmount" .= walletPrevAmount
, "prevTimestamp" .= walletPrevTimestamp
, "deltaDeposited" .= walletDeltaDeposited
, "deltaWithdrawn" .= walletDeltaWithdrawn
, "deltaTransferIn" .= walletDeltaTransferIn
, "deltaTransferOut" .= walletDeltaTransferOut
, "deltaAmount" .= walletDeltaAmount
, "deposited" .= walletDeposited
, "withdrawn" .= walletWithdrawn
, "transferIn" .= walletTransferIn
, "transferOut" .= walletTransferOut
, "amount" .= walletAmount
, "pendingCredit" .= walletPendingCredit
, "pendingDebit" .= walletPendingDebit
, "confirmedDebit" .= walletConfirmedDebit
, "timestamp" .= walletTimestamp
, "addr" .= walletAddr
, "script" .= walletScript
, "withdrawalLock" .= walletWithdrawalLock
]
mkWallet
:: Double
-> Text
-> Wallet
mkWallet walletAccount walletCurrency =
Wallet
{ walletAccount
, walletCurrency
, walletPrevDeposited = Nothing
, walletPrevWithdrawn = Nothing
, walletPrevTransferIn = Nothing
, walletPrevTransferOut = Nothing
, walletPrevAmount = Nothing
, walletPrevTimestamp = Nothing
, walletDeltaDeposited = Nothing
, walletDeltaWithdrawn = Nothing
, walletDeltaTransferIn = Nothing
, walletDeltaTransferOut = Nothing
, walletDeltaAmount = Nothing
, walletDeposited = Nothing
, walletWithdrawn = Nothing
, walletTransferIn = Nothing
, walletTransferOut = Nothing
, walletAmount = Nothing
, walletPendingCredit = Nothing
, walletPendingDebit = Nothing
, walletConfirmedDebit = Nothing
, walletTimestamp = Nothing
, walletAddr = Nothing
, walletScript = Nothing
, walletWithdrawalLock = Nothing
}
data XAny = XAny
{
} deriving (P.Show, P.Eq, P.Typeable)
instance A.FromJSON XAny where
parseJSON = A.withObject "XAny" $ \o ->
pure XAny
instance A.ToJSON XAny where
toJSON XAny =
_omitNulls
[
]
mkXAny
:: XAny
mkXAny =
XAny
{
}
data E'Type
= E'Type'Success
| E'Type'Error
| E'Type'Info
deriving (P.Show, P.Eq, P.Typeable, P.Ord, P.Bounded, P.Enum)
instance A.ToJSON E'Type where toJSON = A.toJSON . fromE'Type
instance A.FromJSON E'Type where parseJSON o = P.either P.fail (pure . P.id) . toE'Type =<< A.parseJSON o
instance WH.ToHttpApiData E'Type where toQueryParam = WH.toQueryParam . fromE'Type
instance WH.FromHttpApiData E'Type where parseQueryParam o = WH.parseQueryParam o >>= P.left T.pack . toE'Type
instance MimeRender MimeMultipartFormData E'Type where mimeRender _ = mimeRenderDefaultMultipartFormData
fromE'Type :: E'Type -> Text
fromE'Type = \case
E'Type'Success -> "success"
E'Type'Error -> "error"
E'Type'Info -> "info"
toE'Type :: Text -> P.Either String E'Type
toE'Type = \case
"success" -> P.Right E'Type'Success
"error" -> P.Right E'Type'Error
"info" -> P.Right E'Type'Info
s -> P.Left $ "toE'Type: enum parse failure: " P.++ P.show s