{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE RecordWildCards #-}
{-# OPTIONS_GHC -fno-warn-name-shadowing -fno-warn-unused-matches -fno-warn-unused-binds -fno-warn-unused-imports #-}
module BitMEX.ModelLens where
import qualified Data.Aeson as A
import qualified Data.ByteString.Lazy as BL
import qualified Data.Data as P (Data, Typeable)
import qualified Data.Map as Map
import qualified Data.Set as Set
import qualified Data.Time as TI
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
import BitMEX.Model
import BitMEX.Core
aPIKeyIdL :: Lens_' APIKey (Text)
aPIKeyIdL f APIKey{..} = (\aPIKeyId -> APIKey { aPIKeyId, ..} ) <$> f aPIKeyId
{-# INLINE aPIKeyIdL #-}
aPIKeySecretL :: Lens_' APIKey (Text)
aPIKeySecretL f APIKey{..} = (\aPIKeySecret -> APIKey { aPIKeySecret, ..} ) <$> f aPIKeySecret
{-# INLINE aPIKeySecretL #-}
aPIKeyNameL :: Lens_' APIKey (Text)
aPIKeyNameL f APIKey{..} = (\aPIKeyName -> APIKey { aPIKeyName, ..} ) <$> f aPIKeyName
{-# INLINE aPIKeyNameL #-}
aPIKeyNonceL :: Lens_' APIKey (Double)
aPIKeyNonceL f APIKey{..} = (\aPIKeyNonce -> APIKey { aPIKeyNonce, ..} ) <$> f aPIKeyNonce
{-# INLINE aPIKeyNonceL #-}
aPIKeyCidrL :: Lens_' APIKey (Maybe Text)
aPIKeyCidrL f APIKey{..} = (\aPIKeyCidr -> APIKey { aPIKeyCidr, ..} ) <$> f aPIKeyCidr
{-# INLINE aPIKeyCidrL #-}
aPIKeyPermissionsL :: Lens_' APIKey (Maybe [XAny])
aPIKeyPermissionsL f APIKey{..} = (\aPIKeyPermissions -> APIKey { aPIKeyPermissions, ..} ) <$> f aPIKeyPermissions
{-# INLINE aPIKeyPermissionsL #-}
aPIKeyEnabledL :: Lens_' APIKey (Maybe Bool)
aPIKeyEnabledL f APIKey{..} = (\aPIKeyEnabled -> APIKey { aPIKeyEnabled, ..} ) <$> f aPIKeyEnabled
{-# INLINE aPIKeyEnabledL #-}
aPIKeyUserIdL :: Lens_' APIKey (Double)
aPIKeyUserIdL f APIKey{..} = (\aPIKeyUserId -> APIKey { aPIKeyUserId, ..} ) <$> f aPIKeyUserId
{-# INLINE aPIKeyUserIdL #-}
aPIKeyCreatedL :: Lens_' APIKey (Maybe DateTime)
aPIKeyCreatedL f APIKey{..} = (\aPIKeyCreated -> APIKey { aPIKeyCreated, ..} ) <$> f aPIKeyCreated
{-# INLINE aPIKeyCreatedL #-}
accessTokenIdL :: Lens_' AccessToken (Text)
accessTokenIdL f AccessToken{..} = (\accessTokenId -> AccessToken { accessTokenId, ..} ) <$> f accessTokenId
{-# INLINE accessTokenIdL #-}
accessTokenTtlL :: Lens_' AccessToken (Maybe Double)
accessTokenTtlL f AccessToken{..} = (\accessTokenTtl -> AccessToken { accessTokenTtl, ..} ) <$> f accessTokenTtl
{-# INLINE accessTokenTtlL #-}
accessTokenCreatedL :: Lens_' AccessToken (Maybe DateTime)
accessTokenCreatedL f AccessToken{..} = (\accessTokenCreated -> AccessToken { accessTokenCreated, ..} ) <$> f accessTokenCreated
{-# INLINE accessTokenCreatedL #-}
accessTokenUserIdL :: Lens_' AccessToken (Maybe Double)
accessTokenUserIdL f AccessToken{..} = (\accessTokenUserId -> AccessToken { accessTokenUserId, ..} ) <$> f accessTokenUserId
{-# INLINE accessTokenUserIdL #-}
affiliateAccountL :: Lens_' Affiliate (Double)
affiliateAccountL f Affiliate{..} = (\affiliateAccount -> Affiliate { affiliateAccount, ..} ) <$> f affiliateAccount
{-# INLINE affiliateAccountL #-}
affiliateCurrencyL :: Lens_' Affiliate (Text)
affiliateCurrencyL f Affiliate{..} = (\affiliateCurrency -> Affiliate { affiliateCurrency, ..} ) <$> f affiliateCurrency
{-# INLINE affiliateCurrencyL #-}
affiliatePrevPayoutL :: Lens_' Affiliate (Maybe Double)
affiliatePrevPayoutL f Affiliate{..} = (\affiliatePrevPayout -> Affiliate { affiliatePrevPayout, ..} ) <$> f affiliatePrevPayout
{-# INLINE affiliatePrevPayoutL #-}
affiliatePrevTurnoverL :: Lens_' Affiliate (Maybe Double)
affiliatePrevTurnoverL f Affiliate{..} = (\affiliatePrevTurnover -> Affiliate { affiliatePrevTurnover, ..} ) <$> f affiliatePrevTurnover
{-# INLINE affiliatePrevTurnoverL #-}
affiliatePrevCommL :: Lens_' Affiliate (Maybe Double)
affiliatePrevCommL f Affiliate{..} = (\affiliatePrevComm -> Affiliate { affiliatePrevComm, ..} ) <$> f affiliatePrevComm
{-# INLINE affiliatePrevCommL #-}
affiliatePrevTimestampL :: Lens_' Affiliate (Maybe DateTime)
affiliatePrevTimestampL f Affiliate{..} = (\affiliatePrevTimestamp -> Affiliate { affiliatePrevTimestamp, ..} ) <$> f affiliatePrevTimestamp
{-# INLINE affiliatePrevTimestampL #-}
affiliateExecTurnoverL :: Lens_' Affiliate (Maybe Double)
affiliateExecTurnoverL f Affiliate{..} = (\affiliateExecTurnover -> Affiliate { affiliateExecTurnover, ..} ) <$> f affiliateExecTurnover
{-# INLINE affiliateExecTurnoverL #-}
affiliateExecCommL :: Lens_' Affiliate (Maybe Double)
affiliateExecCommL f Affiliate{..} = (\affiliateExecComm -> Affiliate { affiliateExecComm, ..} ) <$> f affiliateExecComm
{-# INLINE affiliateExecCommL #-}
affiliateTotalReferralsL :: Lens_' Affiliate (Maybe Double)
affiliateTotalReferralsL f Affiliate{..} = (\affiliateTotalReferrals -> Affiliate { affiliateTotalReferrals, ..} ) <$> f affiliateTotalReferrals
{-# INLINE affiliateTotalReferralsL #-}
affiliateTotalTurnoverL :: Lens_' Affiliate (Maybe Double)
affiliateTotalTurnoverL f Affiliate{..} = (\affiliateTotalTurnover -> Affiliate { affiliateTotalTurnover, ..} ) <$> f affiliateTotalTurnover
{-# INLINE affiliateTotalTurnoverL #-}
affiliateTotalCommL :: Lens_' Affiliate (Maybe Double)
affiliateTotalCommL f Affiliate{..} = (\affiliateTotalComm -> Affiliate { affiliateTotalComm, ..} ) <$> f affiliateTotalComm
{-# INLINE affiliateTotalCommL #-}
affiliatePayoutPcntL :: Lens_' Affiliate (Maybe Double)
affiliatePayoutPcntL f Affiliate{..} = (\affiliatePayoutPcnt -> Affiliate { affiliatePayoutPcnt, ..} ) <$> f affiliatePayoutPcnt
{-# INLINE affiliatePayoutPcntL #-}
affiliatePendingPayoutL :: Lens_' Affiliate (Maybe Double)
affiliatePendingPayoutL f Affiliate{..} = (\affiliatePendingPayout -> Affiliate { affiliatePendingPayout, ..} ) <$> f affiliatePendingPayout
{-# INLINE affiliatePendingPayoutL #-}
affiliateTimestampL :: Lens_' Affiliate (Maybe DateTime)
affiliateTimestampL f Affiliate{..} = (\affiliateTimestamp -> Affiliate { affiliateTimestamp, ..} ) <$> f affiliateTimestamp
{-# INLINE affiliateTimestampL #-}
affiliateReferrerAccountL :: Lens_' Affiliate (Maybe Double)
affiliateReferrerAccountL f Affiliate{..} = (\affiliateReferrerAccount -> Affiliate { affiliateReferrerAccount, ..} ) <$> f affiliateReferrerAccount
{-# INLINE affiliateReferrerAccountL #-}
announcementIdL :: Lens_' Announcement (Double)
announcementIdL f Announcement{..} = (\announcementId -> Announcement { announcementId, ..} ) <$> f announcementId
{-# INLINE announcementIdL #-}
announcementLinkL :: Lens_' Announcement (Maybe Text)
announcementLinkL f Announcement{..} = (\announcementLink -> Announcement { announcementLink, ..} ) <$> f announcementLink
{-# INLINE announcementLinkL #-}
announcementTitleL :: Lens_' Announcement (Maybe Text)
announcementTitleL f Announcement{..} = (\announcementTitle -> Announcement { announcementTitle, ..} ) <$> f announcementTitle
{-# INLINE announcementTitleL #-}
announcementContentL :: Lens_' Announcement (Maybe Text)
announcementContentL f Announcement{..} = (\announcementContent -> Announcement { announcementContent, ..} ) <$> f announcementContent
{-# INLINE announcementContentL #-}
announcementDateL :: Lens_' Announcement (Maybe DateTime)
announcementDateL f Announcement{..} = (\announcementDate -> Announcement { announcementDate, ..} ) <$> f announcementDate
{-# INLINE announcementDateL #-}
chatIdL :: Lens_' Chat (Maybe Double)
chatIdL f Chat{..} = (\chatId -> Chat { chatId, ..} ) <$> f chatId
{-# INLINE chatIdL #-}
chatDateL :: Lens_' Chat (DateTime)
chatDateL f Chat{..} = (\chatDate -> Chat { chatDate, ..} ) <$> f chatDate
{-# INLINE chatDateL #-}
chatUserL :: Lens_' Chat (Text)
chatUserL f Chat{..} = (\chatUser -> Chat { chatUser, ..} ) <$> f chatUser
{-# INLINE chatUserL #-}
chatMessageL :: Lens_' Chat (Text)
chatMessageL f Chat{..} = (\chatMessage -> Chat { chatMessage, ..} ) <$> f chatMessage
{-# INLINE chatMessageL #-}
chatHtmlL :: Lens_' Chat (Text)
chatHtmlL f Chat{..} = (\chatHtml -> Chat { chatHtml, ..} ) <$> f chatHtml
{-# INLINE chatHtmlL #-}
chatFromBotL :: Lens_' Chat (Maybe Bool)
chatFromBotL f Chat{..} = (\chatFromBot -> Chat { chatFromBot, ..} ) <$> f chatFromBot
{-# INLINE chatFromBotL #-}
chatChannelIdL :: Lens_' Chat (Maybe Double)
chatChannelIdL f Chat{..} = (\chatChannelId -> Chat { chatChannelId, ..} ) <$> f chatChannelId
{-# INLINE chatChannelIdL #-}
chatChannelsIdL :: Lens_' ChatChannels (Maybe Double)
chatChannelsIdL f ChatChannels{..} = (\chatChannelsId -> ChatChannels { chatChannelsId, ..} ) <$> f chatChannelsId
{-# INLINE chatChannelsIdL #-}
chatChannelsNameL :: Lens_' ChatChannels (Text)
chatChannelsNameL f ChatChannels{..} = (\chatChannelsName -> ChatChannels { chatChannelsName, ..} ) <$> f chatChannelsName
{-# INLINE chatChannelsNameL #-}
connectedUsersUsersL :: Lens_' ConnectedUsers (Maybe Double)
connectedUsersUsersL f ConnectedUsers{..} = (\connectedUsersUsers -> ConnectedUsers { connectedUsersUsers, ..} ) <$> f connectedUsersUsers
{-# INLINE connectedUsersUsersL #-}
connectedUsersBotsL :: Lens_' ConnectedUsers (Maybe Double)
connectedUsersBotsL f ConnectedUsers{..} = (\connectedUsersBots -> ConnectedUsers { connectedUsersBots, ..} ) <$> f connectedUsersBots
{-# INLINE connectedUsersBotsL #-}
errorErrorL :: Lens_' Error (ErrorError)
errorErrorL f Error{..} = (\errorError -> Error { errorError, ..} ) <$> f errorError
{-# INLINE errorErrorL #-}
errorErrorMessageL :: Lens_' ErrorError (Maybe Text)
errorErrorMessageL f ErrorError{..} = (\errorErrorMessage -> ErrorError { errorErrorMessage, ..} ) <$> f errorErrorMessage
{-# INLINE errorErrorMessageL #-}
errorErrorNameL :: Lens_' ErrorError (Maybe Text)
errorErrorNameL f ErrorError{..} = (\errorErrorName -> ErrorError { errorErrorName, ..} ) <$> f errorErrorName
{-# INLINE errorErrorNameL #-}
executionExecIdL :: Lens_' Execution (Text)
executionExecIdL f Execution{..} = (\executionExecId -> Execution { executionExecId, ..} ) <$> f executionExecId
{-# INLINE executionExecIdL #-}
executionOrderIdL :: Lens_' Execution (Maybe Text)
executionOrderIdL f Execution{..} = (\executionOrderId -> Execution { executionOrderId, ..} ) <$> f executionOrderId
{-# INLINE executionOrderIdL #-}
executionClOrdIdL :: Lens_' Execution (Maybe Text)
executionClOrdIdL f Execution{..} = (\executionClOrdId -> Execution { executionClOrdId, ..} ) <$> f executionClOrdId
{-# INLINE executionClOrdIdL #-}
executionClOrdLinkIdL :: Lens_' Execution (Maybe Text)
executionClOrdLinkIdL f Execution{..} = (\executionClOrdLinkId -> Execution { executionClOrdLinkId, ..} ) <$> f executionClOrdLinkId
{-# INLINE executionClOrdLinkIdL #-}
executionAccountL :: Lens_' Execution (Maybe Double)
executionAccountL f Execution{..} = (\executionAccount -> Execution { executionAccount, ..} ) <$> f executionAccount
{-# INLINE executionAccountL #-}
executionSymbolL :: Lens_' Execution (Maybe Text)
executionSymbolL f Execution{..} = (\executionSymbol -> Execution { executionSymbol, ..} ) <$> f executionSymbol
{-# INLINE executionSymbolL #-}
executionSideL :: Lens_' Execution (Maybe Text)
executionSideL f Execution{..} = (\executionSide -> Execution { executionSide, ..} ) <$> f executionSide
{-# INLINE executionSideL #-}
executionLastQtyL :: Lens_' Execution (Maybe Double)
executionLastQtyL f Execution{..} = (\executionLastQty -> Execution { executionLastQty, ..} ) <$> f executionLastQty
{-# INLINE executionLastQtyL #-}
executionLastPxL :: Lens_' Execution (Maybe Double)
executionLastPxL f Execution{..} = (\executionLastPx -> Execution { executionLastPx, ..} ) <$> f executionLastPx
{-# INLINE executionLastPxL #-}
executionUnderlyingLastPxL :: Lens_' Execution (Maybe Double)
executionUnderlyingLastPxL f Execution{..} = (\executionUnderlyingLastPx -> Execution { executionUnderlyingLastPx, ..} ) <$> f executionUnderlyingLastPx
{-# INLINE executionUnderlyingLastPxL #-}
executionLastMktL :: Lens_' Execution (Maybe Text)
executionLastMktL f Execution{..} = (\executionLastMkt -> Execution { executionLastMkt, ..} ) <$> f executionLastMkt
{-# INLINE executionLastMktL #-}
executionLastLiquidityIndL :: Lens_' Execution (Maybe Text)
executionLastLiquidityIndL f Execution{..} = (\executionLastLiquidityInd -> Execution { executionLastLiquidityInd, ..} ) <$> f executionLastLiquidityInd
{-# INLINE executionLastLiquidityIndL #-}
executionSimpleOrderQtyL :: Lens_' Execution (Maybe Double)
executionSimpleOrderQtyL f Execution{..} = (\executionSimpleOrderQty -> Execution { executionSimpleOrderQty, ..} ) <$> f executionSimpleOrderQty
{-# INLINE executionSimpleOrderQtyL #-}
executionOrderQtyL :: Lens_' Execution (Maybe Double)
executionOrderQtyL f Execution{..} = (\executionOrderQty -> Execution { executionOrderQty, ..} ) <$> f executionOrderQty
{-# INLINE executionOrderQtyL #-}
executionPriceL :: Lens_' Execution (Maybe Double)
executionPriceL f Execution{..} = (\executionPrice -> Execution { executionPrice, ..} ) <$> f executionPrice
{-# INLINE executionPriceL #-}
executionDisplayQtyL :: Lens_' Execution (Maybe Double)
executionDisplayQtyL f Execution{..} = (\executionDisplayQty -> Execution { executionDisplayQty, ..} ) <$> f executionDisplayQty
{-# INLINE executionDisplayQtyL #-}
executionStopPxL :: Lens_' Execution (Maybe Double)
executionStopPxL f Execution{..} = (\executionStopPx -> Execution { executionStopPx, ..} ) <$> f executionStopPx
{-# INLINE executionStopPxL #-}
executionPegOffsetValueL :: Lens_' Execution (Maybe Double)
executionPegOffsetValueL f Execution{..} = (\executionPegOffsetValue -> Execution { executionPegOffsetValue, ..} ) <$> f executionPegOffsetValue
{-# INLINE executionPegOffsetValueL #-}
executionPegPriceTypeL :: Lens_' Execution (Maybe Text)
executionPegPriceTypeL f Execution{..} = (\executionPegPriceType -> Execution { executionPegPriceType, ..} ) <$> f executionPegPriceType
{-# INLINE executionPegPriceTypeL #-}
executionCurrencyL :: Lens_' Execution (Maybe Text)
executionCurrencyL f Execution{..} = (\executionCurrency -> Execution { executionCurrency, ..} ) <$> f executionCurrency
{-# INLINE executionCurrencyL #-}
executionSettlCurrencyL :: Lens_' Execution (Maybe Text)
executionSettlCurrencyL f Execution{..} = (\executionSettlCurrency -> Execution { executionSettlCurrency, ..} ) <$> f executionSettlCurrency
{-# INLINE executionSettlCurrencyL #-}
executionExecTypeL :: Lens_' Execution (Maybe Text)
executionExecTypeL f Execution{..} = (\executionExecType -> Execution { executionExecType, ..} ) <$> f executionExecType
{-# INLINE executionExecTypeL #-}
executionOrdTypeL :: Lens_' Execution (Maybe Text)
executionOrdTypeL f Execution{..} = (\executionOrdType -> Execution { executionOrdType, ..} ) <$> f executionOrdType
{-# INLINE executionOrdTypeL #-}
executionTimeInForceL :: Lens_' Execution (Maybe Text)
executionTimeInForceL f Execution{..} = (\executionTimeInForce -> Execution { executionTimeInForce, ..} ) <$> f executionTimeInForce
{-# INLINE executionTimeInForceL #-}
executionExecInstL :: Lens_' Execution (Maybe Text)
executionExecInstL f Execution{..} = (\executionExecInst -> Execution { executionExecInst, ..} ) <$> f executionExecInst
{-# INLINE executionExecInstL #-}
executionContingencyTypeL :: Lens_' Execution (Maybe Text)
executionContingencyTypeL f Execution{..} = (\executionContingencyType -> Execution { executionContingencyType, ..} ) <$> f executionContingencyType
{-# INLINE executionContingencyTypeL #-}
executionExDestinationL :: Lens_' Execution (Maybe Text)
executionExDestinationL f Execution{..} = (\executionExDestination -> Execution { executionExDestination, ..} ) <$> f executionExDestination
{-# INLINE executionExDestinationL #-}
executionOrdStatusL :: Lens_' Execution (Maybe Text)
executionOrdStatusL f Execution{..} = (\executionOrdStatus -> Execution { executionOrdStatus, ..} ) <$> f executionOrdStatus
{-# INLINE executionOrdStatusL #-}
executionTriggeredL :: Lens_' Execution (Maybe Text)
executionTriggeredL f Execution{..} = (\executionTriggered -> Execution { executionTriggered, ..} ) <$> f executionTriggered
{-# INLINE executionTriggeredL #-}
executionWorkingIndicatorL :: Lens_' Execution (Maybe Bool)
executionWorkingIndicatorL f Execution{..} = (\executionWorkingIndicator -> Execution { executionWorkingIndicator, ..} ) <$> f executionWorkingIndicator
{-# INLINE executionWorkingIndicatorL #-}
executionOrdRejReasonL :: Lens_' Execution (Maybe Text)
executionOrdRejReasonL f Execution{..} = (\executionOrdRejReason -> Execution { executionOrdRejReason, ..} ) <$> f executionOrdRejReason
{-# INLINE executionOrdRejReasonL #-}
executionSimpleLeavesQtyL :: Lens_' Execution (Maybe Double)
executionSimpleLeavesQtyL f Execution{..} = (\executionSimpleLeavesQty -> Execution { executionSimpleLeavesQty, ..} ) <$> f executionSimpleLeavesQty
{-# INLINE executionSimpleLeavesQtyL #-}
executionLeavesQtyL :: Lens_' Execution (Maybe Double)
executionLeavesQtyL f Execution{..} = (\executionLeavesQty -> Execution { executionLeavesQty, ..} ) <$> f executionLeavesQty
{-# INLINE executionLeavesQtyL #-}
executionSimpleCumQtyL :: Lens_' Execution (Maybe Double)
executionSimpleCumQtyL f Execution{..} = (\executionSimpleCumQty -> Execution { executionSimpleCumQty, ..} ) <$> f executionSimpleCumQty
{-# INLINE executionSimpleCumQtyL #-}
executionCumQtyL :: Lens_' Execution (Maybe Double)
executionCumQtyL f Execution{..} = (\executionCumQty -> Execution { executionCumQty, ..} ) <$> f executionCumQty
{-# INLINE executionCumQtyL #-}
executionAvgPxL :: Lens_' Execution (Maybe Double)
executionAvgPxL f Execution{..} = (\executionAvgPx -> Execution { executionAvgPx, ..} ) <$> f executionAvgPx
{-# INLINE executionAvgPxL #-}
executionCommissionL :: Lens_' Execution (Maybe Double)
executionCommissionL f Execution{..} = (\executionCommission -> Execution { executionCommission, ..} ) <$> f executionCommission
{-# INLINE executionCommissionL #-}
executionTradePublishIndicatorL :: Lens_' Execution (Maybe Text)
executionTradePublishIndicatorL f Execution{..} = (\executionTradePublishIndicator -> Execution { executionTradePublishIndicator, ..} ) <$> f executionTradePublishIndicator
{-# INLINE executionTradePublishIndicatorL #-}
executionMultiLegReportingTypeL :: Lens_' Execution (Maybe Text)
executionMultiLegReportingTypeL f Execution{..} = (\executionMultiLegReportingType -> Execution { executionMultiLegReportingType, ..} ) <$> f executionMultiLegReportingType
{-# INLINE executionMultiLegReportingTypeL #-}
executionTextL :: Lens_' Execution (Maybe Text)
executionTextL f Execution{..} = (\executionText -> Execution { executionText, ..} ) <$> f executionText
{-# INLINE executionTextL #-}
executionTrdMatchIdL :: Lens_' Execution (Maybe Text)
executionTrdMatchIdL f Execution{..} = (\executionTrdMatchId -> Execution { executionTrdMatchId, ..} ) <$> f executionTrdMatchId
{-# INLINE executionTrdMatchIdL #-}
executionExecCostL :: Lens_' Execution (Maybe Double)
executionExecCostL f Execution{..} = (\executionExecCost -> Execution { executionExecCost, ..} ) <$> f executionExecCost
{-# INLINE executionExecCostL #-}
executionExecCommL :: Lens_' Execution (Maybe Double)
executionExecCommL f Execution{..} = (\executionExecComm -> Execution { executionExecComm, ..} ) <$> f executionExecComm
{-# INLINE executionExecCommL #-}
executionHomeNotionalL :: Lens_' Execution (Maybe Double)
executionHomeNotionalL f Execution{..} = (\executionHomeNotional -> Execution { executionHomeNotional, ..} ) <$> f executionHomeNotional
{-# INLINE executionHomeNotionalL #-}
executionForeignNotionalL :: Lens_' Execution (Maybe Double)
executionForeignNotionalL f Execution{..} = (\executionForeignNotional -> Execution { executionForeignNotional, ..} ) <$> f executionForeignNotional
{-# INLINE executionForeignNotionalL #-}
executionTransactTimeL :: Lens_' Execution (Maybe DateTime)
executionTransactTimeL f Execution{..} = (\executionTransactTime -> Execution { executionTransactTime, ..} ) <$> f executionTransactTime
{-# INLINE executionTransactTimeL #-}
executionTimestampL :: Lens_' Execution (Maybe DateTime)
executionTimestampL f Execution{..} = (\executionTimestamp -> Execution { executionTimestamp, ..} ) <$> f executionTimestamp
{-# INLINE executionTimestampL #-}
fundingTimestampL :: Lens_' Funding (DateTime)
fundingTimestampL f Funding{..} = (\fundingTimestamp -> Funding { fundingTimestamp, ..} ) <$> f fundingTimestamp
{-# INLINE fundingTimestampL #-}
fundingSymbolL :: Lens_' Funding (Text)
fundingSymbolL f Funding{..} = (\fundingSymbol -> Funding { fundingSymbol, ..} ) <$> f fundingSymbol
{-# INLINE fundingSymbolL #-}
fundingFundingIntervalL :: Lens_' Funding (Maybe DateTime)
fundingFundingIntervalL f Funding{..} = (\fundingFundingInterval -> Funding { fundingFundingInterval, ..} ) <$> f fundingFundingInterval
{-# INLINE fundingFundingIntervalL #-}
fundingFundingRateL :: Lens_' Funding (Maybe Double)
fundingFundingRateL f Funding{..} = (\fundingFundingRate -> Funding { fundingFundingRate, ..} ) <$> f fundingFundingRate
{-# INLINE fundingFundingRateL #-}
fundingFundingRateDailyL :: Lens_' Funding (Maybe Double)
fundingFundingRateDailyL f Funding{..} = (\fundingFundingRateDaily -> Funding { fundingFundingRateDaily, ..} ) <$> f fundingFundingRateDaily
{-# INLINE fundingFundingRateDailyL #-}
indexCompositeTimestampL :: Lens_' IndexComposite (DateTime)
indexCompositeTimestampL f IndexComposite{..} = (\indexCompositeTimestamp -> IndexComposite { indexCompositeTimestamp, ..} ) <$> f indexCompositeTimestamp
{-# INLINE indexCompositeTimestampL #-}
indexCompositeSymbolL :: Lens_' IndexComposite (Maybe Text)
indexCompositeSymbolL f IndexComposite{..} = (\indexCompositeSymbol -> IndexComposite { indexCompositeSymbol, ..} ) <$> f indexCompositeSymbol
{-# INLINE indexCompositeSymbolL #-}
indexCompositeIndexSymbolL :: Lens_' IndexComposite (Maybe Text)
indexCompositeIndexSymbolL f IndexComposite{..} = (\indexCompositeIndexSymbol -> IndexComposite { indexCompositeIndexSymbol, ..} ) <$> f indexCompositeIndexSymbol
{-# INLINE indexCompositeIndexSymbolL #-}
indexCompositeReferenceL :: Lens_' IndexComposite (Maybe Text)
indexCompositeReferenceL f IndexComposite{..} = (\indexCompositeReference -> IndexComposite { indexCompositeReference, ..} ) <$> f indexCompositeReference
{-# INLINE indexCompositeReferenceL #-}
indexCompositeLastPriceL :: Lens_' IndexComposite (Maybe Double)
indexCompositeLastPriceL f IndexComposite{..} = (\indexCompositeLastPrice -> IndexComposite { indexCompositeLastPrice, ..} ) <$> f indexCompositeLastPrice
{-# INLINE indexCompositeLastPriceL #-}
indexCompositeWeightL :: Lens_' IndexComposite (Maybe Double)
indexCompositeWeightL f IndexComposite{..} = (\indexCompositeWeight -> IndexComposite { indexCompositeWeight, ..} ) <$> f indexCompositeWeight
{-# INLINE indexCompositeWeightL #-}
indexCompositeLoggedL :: Lens_' IndexComposite (Maybe DateTime)
indexCompositeLoggedL f IndexComposite{..} = (\indexCompositeLogged -> IndexComposite { indexCompositeLogged, ..} ) <$> f indexCompositeLogged
{-# INLINE indexCompositeLoggedL #-}
inlineResponse200SuccessL :: Lens_' InlineResponse200 (Maybe Bool)
inlineResponse200SuccessL f InlineResponse200{..} = (\inlineResponse200Success -> InlineResponse200 { inlineResponse200Success, ..} ) <$> f inlineResponse200Success
{-# INLINE inlineResponse200SuccessL #-}
instrumentSymbolL :: Lens_' Instrument (Text)
instrumentSymbolL f Instrument{..} = (\instrumentSymbol -> Instrument { instrumentSymbol, ..} ) <$> f instrumentSymbol
{-# INLINE instrumentSymbolL #-}
instrumentRootSymbolL :: Lens_' Instrument (Maybe Text)
instrumentRootSymbolL f Instrument{..} = (\instrumentRootSymbol -> Instrument { instrumentRootSymbol, ..} ) <$> f instrumentRootSymbol
{-# INLINE instrumentRootSymbolL #-}
instrumentStateL :: Lens_' Instrument (Maybe Text)
instrumentStateL f Instrument{..} = (\instrumentState -> Instrument { instrumentState, ..} ) <$> f instrumentState
{-# INLINE instrumentStateL #-}
instrumentTypL :: Lens_' Instrument (Maybe Text)
instrumentTypL f Instrument{..} = (\instrumentTyp -> Instrument { instrumentTyp, ..} ) <$> f instrumentTyp
{-# INLINE instrumentTypL #-}
instrumentListingL :: Lens_' Instrument (Maybe DateTime)
instrumentListingL f Instrument{..} = (\instrumentListing -> Instrument { instrumentListing, ..} ) <$> f instrumentListing
{-# INLINE instrumentListingL #-}
instrumentFrontL :: Lens_' Instrument (Maybe DateTime)
instrumentFrontL f Instrument{..} = (\instrumentFront -> Instrument { instrumentFront, ..} ) <$> f instrumentFront
{-# INLINE instrumentFrontL #-}
instrumentExpiryL :: Lens_' Instrument (Maybe DateTime)
instrumentExpiryL f Instrument{..} = (\instrumentExpiry -> Instrument { instrumentExpiry, ..} ) <$> f instrumentExpiry
{-# INLINE instrumentExpiryL #-}
instrumentSettleL :: Lens_' Instrument (Maybe DateTime)
instrumentSettleL f Instrument{..} = (\instrumentSettle -> Instrument { instrumentSettle, ..} ) <$> f instrumentSettle
{-# INLINE instrumentSettleL #-}
instrumentRelistIntervalL :: Lens_' Instrument (Maybe DateTime)
instrumentRelistIntervalL f Instrument{..} = (\instrumentRelistInterval -> Instrument { instrumentRelistInterval, ..} ) <$> f instrumentRelistInterval
{-# INLINE instrumentRelistIntervalL #-}
instrumentInverseLegL :: Lens_' Instrument (Maybe Text)
instrumentInverseLegL f Instrument{..} = (\instrumentInverseLeg -> Instrument { instrumentInverseLeg, ..} ) <$> f instrumentInverseLeg
{-# INLINE instrumentInverseLegL #-}
instrumentSellLegL :: Lens_' Instrument (Maybe Text)
instrumentSellLegL f Instrument{..} = (\instrumentSellLeg -> Instrument { instrumentSellLeg, ..} ) <$> f instrumentSellLeg
{-# INLINE instrumentSellLegL #-}
instrumentBuyLegL :: Lens_' Instrument (Maybe Text)
instrumentBuyLegL f Instrument{..} = (\instrumentBuyLeg -> Instrument { instrumentBuyLeg, ..} ) <$> f instrumentBuyLeg
{-# INLINE instrumentBuyLegL #-}
instrumentPositionCurrencyL :: Lens_' Instrument (Maybe Text)
instrumentPositionCurrencyL f Instrument{..} = (\instrumentPositionCurrency -> Instrument { instrumentPositionCurrency, ..} ) <$> f instrumentPositionCurrency
{-# INLINE instrumentPositionCurrencyL #-}
instrumentUnderlyingL :: Lens_' Instrument (Maybe Text)
instrumentUnderlyingL f Instrument{..} = (\instrumentUnderlying -> Instrument { instrumentUnderlying, ..} ) <$> f instrumentUnderlying
{-# INLINE instrumentUnderlyingL #-}
instrumentQuoteCurrencyL :: Lens_' Instrument (Maybe Text)
instrumentQuoteCurrencyL f Instrument{..} = (\instrumentQuoteCurrency -> Instrument { instrumentQuoteCurrency, ..} ) <$> f instrumentQuoteCurrency
{-# INLINE instrumentQuoteCurrencyL #-}
instrumentUnderlyingSymbolL :: Lens_' Instrument (Maybe Text)
instrumentUnderlyingSymbolL f Instrument{..} = (\instrumentUnderlyingSymbol -> Instrument { instrumentUnderlyingSymbol, ..} ) <$> f instrumentUnderlyingSymbol
{-# INLINE instrumentUnderlyingSymbolL #-}
instrumentReferenceL :: Lens_' Instrument (Maybe Text)
instrumentReferenceL f Instrument{..} = (\instrumentReference -> Instrument { instrumentReference, ..} ) <$> f instrumentReference
{-# INLINE instrumentReferenceL #-}
instrumentReferenceSymbolL :: Lens_' Instrument (Maybe Text)
instrumentReferenceSymbolL f Instrument{..} = (\instrumentReferenceSymbol -> Instrument { instrumentReferenceSymbol, ..} ) <$> f instrumentReferenceSymbol
{-# INLINE instrumentReferenceSymbolL #-}
instrumentCalcIntervalL :: Lens_' Instrument (Maybe DateTime)
instrumentCalcIntervalL f Instrument{..} = (\instrumentCalcInterval -> Instrument { instrumentCalcInterval, ..} ) <$> f instrumentCalcInterval
{-# INLINE instrumentCalcIntervalL #-}
instrumentPublishIntervalL :: Lens_' Instrument (Maybe DateTime)
instrumentPublishIntervalL f Instrument{..} = (\instrumentPublishInterval -> Instrument { instrumentPublishInterval, ..} ) <$> f instrumentPublishInterval
{-# INLINE instrumentPublishIntervalL #-}
instrumentPublishTimeL :: Lens_' Instrument (Maybe DateTime)
instrumentPublishTimeL f Instrument{..} = (\instrumentPublishTime -> Instrument { instrumentPublishTime, ..} ) <$> f instrumentPublishTime
{-# INLINE instrumentPublishTimeL #-}
instrumentMaxOrderQtyL :: Lens_' Instrument (Maybe Double)
instrumentMaxOrderQtyL f Instrument{..} = (\instrumentMaxOrderQty -> Instrument { instrumentMaxOrderQty, ..} ) <$> f instrumentMaxOrderQty
{-# INLINE instrumentMaxOrderQtyL #-}
instrumentMaxPriceL :: Lens_' Instrument (Maybe Double)
instrumentMaxPriceL f Instrument{..} = (\instrumentMaxPrice -> Instrument { instrumentMaxPrice, ..} ) <$> f instrumentMaxPrice
{-# INLINE instrumentMaxPriceL #-}
instrumentLotSizeL :: Lens_' Instrument (Maybe Double)
instrumentLotSizeL f Instrument{..} = (\instrumentLotSize -> Instrument { instrumentLotSize, ..} ) <$> f instrumentLotSize
{-# INLINE instrumentLotSizeL #-}
instrumentTickSizeL :: Lens_' Instrument (Maybe Double)
instrumentTickSizeL f Instrument{..} = (\instrumentTickSize -> Instrument { instrumentTickSize, ..} ) <$> f instrumentTickSize
{-# INLINE instrumentTickSizeL #-}
instrumentMultiplierL :: Lens_' Instrument (Maybe Double)
instrumentMultiplierL f Instrument{..} = (\instrumentMultiplier -> Instrument { instrumentMultiplier, ..} ) <$> f instrumentMultiplier
{-# INLINE instrumentMultiplierL #-}
instrumentSettlCurrencyL :: Lens_' Instrument (Maybe Text)
instrumentSettlCurrencyL f Instrument{..} = (\instrumentSettlCurrency -> Instrument { instrumentSettlCurrency, ..} ) <$> f instrumentSettlCurrency
{-# INLINE instrumentSettlCurrencyL #-}
instrumentUnderlyingToPositionMultiplierL :: Lens_' Instrument (Maybe Double)
instrumentUnderlyingToPositionMultiplierL f Instrument{..} = (\instrumentUnderlyingToPositionMultiplier -> Instrument { instrumentUnderlyingToPositionMultiplier, ..} ) <$> f instrumentUnderlyingToPositionMultiplier
{-# INLINE instrumentUnderlyingToPositionMultiplierL #-}
instrumentUnderlyingToSettleMultiplierL :: Lens_' Instrument (Maybe Double)
instrumentUnderlyingToSettleMultiplierL f Instrument{..} = (\instrumentUnderlyingToSettleMultiplier -> Instrument { instrumentUnderlyingToSettleMultiplier, ..} ) <$> f instrumentUnderlyingToSettleMultiplier
{-# INLINE instrumentUnderlyingToSettleMultiplierL #-}
instrumentQuoteToSettleMultiplierL :: Lens_' Instrument (Maybe Double)
instrumentQuoteToSettleMultiplierL f Instrument{..} = (\instrumentQuoteToSettleMultiplier -> Instrument { instrumentQuoteToSettleMultiplier, ..} ) <$> f instrumentQuoteToSettleMultiplier
{-# INLINE instrumentQuoteToSettleMultiplierL #-}
instrumentIsQuantoL :: Lens_' Instrument (Maybe Bool)
instrumentIsQuantoL f Instrument{..} = (\instrumentIsQuanto -> Instrument { instrumentIsQuanto, ..} ) <$> f instrumentIsQuanto
{-# INLINE instrumentIsQuantoL #-}
instrumentIsInverseL :: Lens_' Instrument (Maybe Bool)
instrumentIsInverseL f Instrument{..} = (\instrumentIsInverse -> Instrument { instrumentIsInverse, ..} ) <$> f instrumentIsInverse
{-# INLINE instrumentIsInverseL #-}
instrumentInitMarginL :: Lens_' Instrument (Maybe Double)
instrumentInitMarginL f Instrument{..} = (\instrumentInitMargin -> Instrument { instrumentInitMargin, ..} ) <$> f instrumentInitMargin
{-# INLINE instrumentInitMarginL #-}
instrumentMaintMarginL :: Lens_' Instrument (Maybe Double)
instrumentMaintMarginL f Instrument{..} = (\instrumentMaintMargin -> Instrument { instrumentMaintMargin, ..} ) <$> f instrumentMaintMargin
{-# INLINE instrumentMaintMarginL #-}
instrumentRiskLimitL :: Lens_' Instrument (Maybe Double)
instrumentRiskLimitL f Instrument{..} = (\instrumentRiskLimit -> Instrument { instrumentRiskLimit, ..} ) <$> f instrumentRiskLimit
{-# INLINE instrumentRiskLimitL #-}
instrumentRiskStepL :: Lens_' Instrument (Maybe Double)
instrumentRiskStepL f Instrument{..} = (\instrumentRiskStep -> Instrument { instrumentRiskStep, ..} ) <$> f instrumentRiskStep
{-# INLINE instrumentRiskStepL #-}
instrumentLimitL :: Lens_' Instrument (Maybe Double)
instrumentLimitL f Instrument{..} = (\instrumentLimit -> Instrument { instrumentLimit, ..} ) <$> f instrumentLimit
{-# INLINE instrumentLimitL #-}
instrumentCappedL :: Lens_' Instrument (Maybe Bool)
instrumentCappedL f Instrument{..} = (\instrumentCapped -> Instrument { instrumentCapped, ..} ) <$> f instrumentCapped
{-# INLINE instrumentCappedL #-}
instrumentTaxedL :: Lens_' Instrument (Maybe Bool)
instrumentTaxedL f Instrument{..} = (\instrumentTaxed -> Instrument { instrumentTaxed, ..} ) <$> f instrumentTaxed
{-# INLINE instrumentTaxedL #-}
instrumentDeleverageL :: Lens_' Instrument (Maybe Bool)
instrumentDeleverageL f Instrument{..} = (\instrumentDeleverage -> Instrument { instrumentDeleverage, ..} ) <$> f instrumentDeleverage
{-# INLINE instrumentDeleverageL #-}
instrumentMakerFeeL :: Lens_' Instrument (Maybe Double)
instrumentMakerFeeL f Instrument{..} = (\instrumentMakerFee -> Instrument { instrumentMakerFee, ..} ) <$> f instrumentMakerFee
{-# INLINE instrumentMakerFeeL #-}
instrumentTakerFeeL :: Lens_' Instrument (Maybe Double)
instrumentTakerFeeL f Instrument{..} = (\instrumentTakerFee -> Instrument { instrumentTakerFee, ..} ) <$> f instrumentTakerFee
{-# INLINE instrumentTakerFeeL #-}
instrumentSettlementFeeL :: Lens_' Instrument (Maybe Double)
instrumentSettlementFeeL f Instrument{..} = (\instrumentSettlementFee -> Instrument { instrumentSettlementFee, ..} ) <$> f instrumentSettlementFee
{-# INLINE instrumentSettlementFeeL #-}
instrumentInsuranceFeeL :: Lens_' Instrument (Maybe Double)
instrumentInsuranceFeeL f Instrument{..} = (\instrumentInsuranceFee -> Instrument { instrumentInsuranceFee, ..} ) <$> f instrumentInsuranceFee
{-# INLINE instrumentInsuranceFeeL #-}
instrumentFundingBaseSymbolL :: Lens_' Instrument (Maybe Text)
instrumentFundingBaseSymbolL f Instrument{..} = (\instrumentFundingBaseSymbol -> Instrument { instrumentFundingBaseSymbol, ..} ) <$> f instrumentFundingBaseSymbol
{-# INLINE instrumentFundingBaseSymbolL #-}
instrumentFundingQuoteSymbolL :: Lens_' Instrument (Maybe Text)
instrumentFundingQuoteSymbolL f Instrument{..} = (\instrumentFundingQuoteSymbol -> Instrument { instrumentFundingQuoteSymbol, ..} ) <$> f instrumentFundingQuoteSymbol
{-# INLINE instrumentFundingQuoteSymbolL #-}
instrumentFundingPremiumSymbolL :: Lens_' Instrument (Maybe Text)
instrumentFundingPremiumSymbolL f Instrument{..} = (\instrumentFundingPremiumSymbol -> Instrument { instrumentFundingPremiumSymbol, ..} ) <$> f instrumentFundingPremiumSymbol
{-# INLINE instrumentFundingPremiumSymbolL #-}
instrumentFundingTimestampL :: Lens_' Instrument (Maybe DateTime)
instrumentFundingTimestampL f Instrument{..} = (\instrumentFundingTimestamp -> Instrument { instrumentFundingTimestamp, ..} ) <$> f instrumentFundingTimestamp
{-# INLINE instrumentFundingTimestampL #-}
instrumentFundingIntervalL :: Lens_' Instrument (Maybe DateTime)
instrumentFundingIntervalL f Instrument{..} = (\instrumentFundingInterval -> Instrument { instrumentFundingInterval, ..} ) <$> f instrumentFundingInterval
{-# INLINE instrumentFundingIntervalL #-}
instrumentFundingRateL :: Lens_' Instrument (Maybe Double)
instrumentFundingRateL f Instrument{..} = (\instrumentFundingRate -> Instrument { instrumentFundingRate, ..} ) <$> f instrumentFundingRate
{-# INLINE instrumentFundingRateL #-}
instrumentIndicativeFundingRateL :: Lens_' Instrument (Maybe Double)
instrumentIndicativeFundingRateL f Instrument{..} = (\instrumentIndicativeFundingRate -> Instrument { instrumentIndicativeFundingRate, ..} ) <$> f instrumentIndicativeFundingRate
{-# INLINE instrumentIndicativeFundingRateL #-}
instrumentRebalanceTimestampL :: Lens_' Instrument (Maybe DateTime)
instrumentRebalanceTimestampL f Instrument{..} = (\instrumentRebalanceTimestamp -> Instrument { instrumentRebalanceTimestamp, ..} ) <$> f instrumentRebalanceTimestamp
{-# INLINE instrumentRebalanceTimestampL #-}
instrumentRebalanceIntervalL :: Lens_' Instrument (Maybe DateTime)
instrumentRebalanceIntervalL f Instrument{..} = (\instrumentRebalanceInterval -> Instrument { instrumentRebalanceInterval, ..} ) <$> f instrumentRebalanceInterval
{-# INLINE instrumentRebalanceIntervalL #-}
instrumentOpeningTimestampL :: Lens_' Instrument (Maybe DateTime)
instrumentOpeningTimestampL f Instrument{..} = (\instrumentOpeningTimestamp -> Instrument { instrumentOpeningTimestamp, ..} ) <$> f instrumentOpeningTimestamp
{-# INLINE instrumentOpeningTimestampL #-}
instrumentClosingTimestampL :: Lens_' Instrument (Maybe DateTime)
instrumentClosingTimestampL f Instrument{..} = (\instrumentClosingTimestamp -> Instrument { instrumentClosingTimestamp, ..} ) <$> f instrumentClosingTimestamp
{-# INLINE instrumentClosingTimestampL #-}
instrumentSessionIntervalL :: Lens_' Instrument (Maybe DateTime)
instrumentSessionIntervalL f Instrument{..} = (\instrumentSessionInterval -> Instrument { instrumentSessionInterval, ..} ) <$> f instrumentSessionInterval
{-# INLINE instrumentSessionIntervalL #-}
instrumentPrevClosePriceL :: Lens_' Instrument (Maybe Double)
instrumentPrevClosePriceL f Instrument{..} = (\instrumentPrevClosePrice -> Instrument { instrumentPrevClosePrice, ..} ) <$> f instrumentPrevClosePrice
{-# INLINE instrumentPrevClosePriceL #-}
instrumentLimitDownPriceL :: Lens_' Instrument (Maybe Double)
instrumentLimitDownPriceL f Instrument{..} = (\instrumentLimitDownPrice -> Instrument { instrumentLimitDownPrice, ..} ) <$> f instrumentLimitDownPrice
{-# INLINE instrumentLimitDownPriceL #-}
instrumentLimitUpPriceL :: Lens_' Instrument (Maybe Double)
instrumentLimitUpPriceL f Instrument{..} = (\instrumentLimitUpPrice -> Instrument { instrumentLimitUpPrice, ..} ) <$> f instrumentLimitUpPrice
{-# INLINE instrumentLimitUpPriceL #-}
instrumentBankruptLimitDownPriceL :: Lens_' Instrument (Maybe Double)
instrumentBankruptLimitDownPriceL f Instrument{..} = (\instrumentBankruptLimitDownPrice -> Instrument { instrumentBankruptLimitDownPrice, ..} ) <$> f instrumentBankruptLimitDownPrice
{-# INLINE instrumentBankruptLimitDownPriceL #-}
instrumentBankruptLimitUpPriceL :: Lens_' Instrument (Maybe Double)
instrumentBankruptLimitUpPriceL f Instrument{..} = (\instrumentBankruptLimitUpPrice -> Instrument { instrumentBankruptLimitUpPrice, ..} ) <$> f instrumentBankruptLimitUpPrice
{-# INLINE instrumentBankruptLimitUpPriceL #-}
instrumentPrevTotalVolumeL :: Lens_' Instrument (Maybe Double)
instrumentPrevTotalVolumeL f Instrument{..} = (\instrumentPrevTotalVolume -> Instrument { instrumentPrevTotalVolume, ..} ) <$> f instrumentPrevTotalVolume
{-# INLINE instrumentPrevTotalVolumeL #-}
instrumentTotalVolumeL :: Lens_' Instrument (Maybe Double)
instrumentTotalVolumeL f Instrument{..} = (\instrumentTotalVolume -> Instrument { instrumentTotalVolume, ..} ) <$> f instrumentTotalVolume
{-# INLINE instrumentTotalVolumeL #-}
instrumentVolumeL :: Lens_' Instrument (Maybe Double)
instrumentVolumeL f Instrument{..} = (\instrumentVolume -> Instrument { instrumentVolume, ..} ) <$> f instrumentVolume
{-# INLINE instrumentVolumeL #-}
instrumentVolume24hL :: Lens_' Instrument (Maybe Double)
instrumentVolume24hL f Instrument{..} = (\instrumentVolume24h -> Instrument { instrumentVolume24h, ..} ) <$> f instrumentVolume24h
{-# INLINE instrumentVolume24hL #-}
instrumentPrevTotalTurnoverL :: Lens_' Instrument (Maybe Double)
instrumentPrevTotalTurnoverL f Instrument{..} = (\instrumentPrevTotalTurnover -> Instrument { instrumentPrevTotalTurnover, ..} ) <$> f instrumentPrevTotalTurnover
{-# INLINE instrumentPrevTotalTurnoverL #-}
instrumentTotalTurnoverL :: Lens_' Instrument (Maybe Double)
instrumentTotalTurnoverL f Instrument{..} = (\instrumentTotalTurnover -> Instrument { instrumentTotalTurnover, ..} ) <$> f instrumentTotalTurnover
{-# INLINE instrumentTotalTurnoverL #-}
instrumentTurnoverL :: Lens_' Instrument (Maybe Double)
instrumentTurnoverL f Instrument{..} = (\instrumentTurnover -> Instrument { instrumentTurnover, ..} ) <$> f instrumentTurnover
{-# INLINE instrumentTurnoverL #-}
instrumentTurnover24hL :: Lens_' Instrument (Maybe Double)
instrumentTurnover24hL f Instrument{..} = (\instrumentTurnover24h -> Instrument { instrumentTurnover24h, ..} ) <$> f instrumentTurnover24h
{-# INLINE instrumentTurnover24hL #-}
instrumentPrevPrice24hL :: Lens_' Instrument (Maybe Double)
instrumentPrevPrice24hL f Instrument{..} = (\instrumentPrevPrice24h -> Instrument { instrumentPrevPrice24h, ..} ) <$> f instrumentPrevPrice24h
{-# INLINE instrumentPrevPrice24hL #-}
instrumentVwapL :: Lens_' Instrument (Maybe Double)
instrumentVwapL f Instrument{..} = (\instrumentVwap -> Instrument { instrumentVwap, ..} ) <$> f instrumentVwap
{-# INLINE instrumentVwapL #-}
instrumentHighPriceL :: Lens_' Instrument (Maybe Double)
instrumentHighPriceL f Instrument{..} = (\instrumentHighPrice -> Instrument { instrumentHighPrice, ..} ) <$> f instrumentHighPrice
{-# INLINE instrumentHighPriceL #-}
instrumentLowPriceL :: Lens_' Instrument (Maybe Double)
instrumentLowPriceL f Instrument{..} = (\instrumentLowPrice -> Instrument { instrumentLowPrice, ..} ) <$> f instrumentLowPrice
{-# INLINE instrumentLowPriceL #-}
instrumentLastPriceL :: Lens_' Instrument (Maybe Double)
instrumentLastPriceL f Instrument{..} = (\instrumentLastPrice -> Instrument { instrumentLastPrice, ..} ) <$> f instrumentLastPrice
{-# INLINE instrumentLastPriceL #-}
instrumentLastPriceProtectedL :: Lens_' Instrument (Maybe Double)
instrumentLastPriceProtectedL f Instrument{..} = (\instrumentLastPriceProtected -> Instrument { instrumentLastPriceProtected, ..} ) <$> f instrumentLastPriceProtected
{-# INLINE instrumentLastPriceProtectedL #-}
instrumentLastTickDirectionL :: Lens_' Instrument (Maybe Text)
instrumentLastTickDirectionL f Instrument{..} = (\instrumentLastTickDirection -> Instrument { instrumentLastTickDirection, ..} ) <$> f instrumentLastTickDirection
{-# INLINE instrumentLastTickDirectionL #-}
instrumentLastChangePcntL :: Lens_' Instrument (Maybe Double)
instrumentLastChangePcntL f Instrument{..} = (\instrumentLastChangePcnt -> Instrument { instrumentLastChangePcnt, ..} ) <$> f instrumentLastChangePcnt
{-# INLINE instrumentLastChangePcntL #-}
instrumentBidPriceL :: Lens_' Instrument (Maybe Double)
instrumentBidPriceL f Instrument{..} = (\instrumentBidPrice -> Instrument { instrumentBidPrice, ..} ) <$> f instrumentBidPrice
{-# INLINE instrumentBidPriceL #-}
instrumentMidPriceL :: Lens_' Instrument (Maybe Double)
instrumentMidPriceL f Instrument{..} = (\instrumentMidPrice -> Instrument { instrumentMidPrice, ..} ) <$> f instrumentMidPrice
{-# INLINE instrumentMidPriceL #-}
instrumentAskPriceL :: Lens_' Instrument (Maybe Double)
instrumentAskPriceL f Instrument{..} = (\instrumentAskPrice -> Instrument { instrumentAskPrice, ..} ) <$> f instrumentAskPrice
{-# INLINE instrumentAskPriceL #-}
instrumentImpactBidPriceL :: Lens_' Instrument (Maybe Double)
instrumentImpactBidPriceL f Instrument{..} = (\instrumentImpactBidPrice -> Instrument { instrumentImpactBidPrice, ..} ) <$> f instrumentImpactBidPrice
{-# INLINE instrumentImpactBidPriceL #-}
instrumentImpactMidPriceL :: Lens_' Instrument (Maybe Double)
instrumentImpactMidPriceL f Instrument{..} = (\instrumentImpactMidPrice -> Instrument { instrumentImpactMidPrice, ..} ) <$> f instrumentImpactMidPrice
{-# INLINE instrumentImpactMidPriceL #-}
instrumentImpactAskPriceL :: Lens_' Instrument (Maybe Double)
instrumentImpactAskPriceL f Instrument{..} = (\instrumentImpactAskPrice -> Instrument { instrumentImpactAskPrice, ..} ) <$> f instrumentImpactAskPrice
{-# INLINE instrumentImpactAskPriceL #-}
instrumentHasLiquidityL :: Lens_' Instrument (Maybe Bool)
instrumentHasLiquidityL f Instrument{..} = (\instrumentHasLiquidity -> Instrument { instrumentHasLiquidity, ..} ) <$> f instrumentHasLiquidity
{-# INLINE instrumentHasLiquidityL #-}
instrumentOpenInterestL :: Lens_' Instrument (Maybe Double)
instrumentOpenInterestL f Instrument{..} = (\instrumentOpenInterest -> Instrument { instrumentOpenInterest, ..} ) <$> f instrumentOpenInterest
{-# INLINE instrumentOpenInterestL #-}
instrumentOpenValueL :: Lens_' Instrument (Maybe Double)
instrumentOpenValueL f Instrument{..} = (\instrumentOpenValue -> Instrument { instrumentOpenValue, ..} ) <$> f instrumentOpenValue
{-# INLINE instrumentOpenValueL #-}
instrumentFairMethodL :: Lens_' Instrument (Maybe Text)
instrumentFairMethodL f Instrument{..} = (\instrumentFairMethod -> Instrument { instrumentFairMethod, ..} ) <$> f instrumentFairMethod
{-# INLINE instrumentFairMethodL #-}
instrumentFairBasisRateL :: Lens_' Instrument (Maybe Double)
instrumentFairBasisRateL f Instrument{..} = (\instrumentFairBasisRate -> Instrument { instrumentFairBasisRate, ..} ) <$> f instrumentFairBasisRate
{-# INLINE instrumentFairBasisRateL #-}
instrumentFairBasisL :: Lens_' Instrument (Maybe Double)
instrumentFairBasisL f Instrument{..} = (\instrumentFairBasis -> Instrument { instrumentFairBasis, ..} ) <$> f instrumentFairBasis
{-# INLINE instrumentFairBasisL #-}
instrumentFairPriceL :: Lens_' Instrument (Maybe Double)
instrumentFairPriceL f Instrument{..} = (\instrumentFairPrice -> Instrument { instrumentFairPrice, ..} ) <$> f instrumentFairPrice
{-# INLINE instrumentFairPriceL #-}
instrumentMarkMethodL :: Lens_' Instrument (Maybe Text)
instrumentMarkMethodL f Instrument{..} = (\instrumentMarkMethod -> Instrument { instrumentMarkMethod, ..} ) <$> f instrumentMarkMethod
{-# INLINE instrumentMarkMethodL #-}
instrumentMarkPriceL :: Lens_' Instrument (Maybe Double)
instrumentMarkPriceL f Instrument{..} = (\instrumentMarkPrice -> Instrument { instrumentMarkPrice, ..} ) <$> f instrumentMarkPrice
{-# INLINE instrumentMarkPriceL #-}
instrumentIndicativeTaxRateL :: Lens_' Instrument (Maybe Double)
instrumentIndicativeTaxRateL f Instrument{..} = (\instrumentIndicativeTaxRate -> Instrument { instrumentIndicativeTaxRate, ..} ) <$> f instrumentIndicativeTaxRate
{-# INLINE instrumentIndicativeTaxRateL #-}
instrumentIndicativeSettlePriceL :: Lens_' Instrument (Maybe Double)
instrumentIndicativeSettlePriceL f Instrument{..} = (\instrumentIndicativeSettlePrice -> Instrument { instrumentIndicativeSettlePrice, ..} ) <$> f instrumentIndicativeSettlePrice
{-# INLINE instrumentIndicativeSettlePriceL #-}
instrumentSettledPriceL :: Lens_' Instrument (Maybe Double)
instrumentSettledPriceL f Instrument{..} = (\instrumentSettledPrice -> Instrument { instrumentSettledPrice, ..} ) <$> f instrumentSettledPrice
{-# INLINE instrumentSettledPriceL #-}
instrumentTimestampL :: Lens_' Instrument (Maybe DateTime)
instrumentTimestampL f Instrument{..} = (\instrumentTimestamp -> Instrument { instrumentTimestamp, ..} ) <$> f instrumentTimestamp
{-# INLINE instrumentTimestampL #-}
instrumentIntervalIntervalsL :: Lens_' InstrumentInterval ([Text])
instrumentIntervalIntervalsL f InstrumentInterval{..} = (\instrumentIntervalIntervals -> InstrumentInterval { instrumentIntervalIntervals, ..} ) <$> f instrumentIntervalIntervals
{-# INLINE instrumentIntervalIntervalsL #-}
instrumentIntervalSymbolsL :: Lens_' InstrumentInterval ([Text])
instrumentIntervalSymbolsL f InstrumentInterval{..} = (\instrumentIntervalSymbols -> InstrumentInterval { instrumentIntervalSymbols, ..} ) <$> f instrumentIntervalSymbols
{-# INLINE instrumentIntervalSymbolsL #-}
insuranceCurrencyL :: Lens_' Insurance (Text)
insuranceCurrencyL f Insurance{..} = (\insuranceCurrency -> Insurance { insuranceCurrency, ..} ) <$> f insuranceCurrency
{-# INLINE insuranceCurrencyL #-}
insuranceTimestampL :: Lens_' Insurance (DateTime)
insuranceTimestampL f Insurance{..} = (\insuranceTimestamp -> Insurance { insuranceTimestamp, ..} ) <$> f insuranceTimestamp
{-# INLINE insuranceTimestampL #-}
insuranceWalletBalanceL :: Lens_' Insurance (Maybe Double)
insuranceWalletBalanceL f Insurance{..} = (\insuranceWalletBalance -> Insurance { insuranceWalletBalance, ..} ) <$> f insuranceWalletBalance
{-# INLINE insuranceWalletBalanceL #-}
leaderboardNameL :: Lens_' Leaderboard (Text)
leaderboardNameL f Leaderboard{..} = (\leaderboardName -> Leaderboard { leaderboardName, ..} ) <$> f leaderboardName
{-# INLINE leaderboardNameL #-}
leaderboardIsRealNameL :: Lens_' Leaderboard (Maybe Bool)
leaderboardIsRealNameL f Leaderboard{..} = (\leaderboardIsRealName -> Leaderboard { leaderboardIsRealName, ..} ) <$> f leaderboardIsRealName
{-# INLINE leaderboardIsRealNameL #-}
leaderboardIsMeL :: Lens_' Leaderboard (Maybe Bool)
leaderboardIsMeL f Leaderboard{..} = (\leaderboardIsMe -> Leaderboard { leaderboardIsMe, ..} ) <$> f leaderboardIsMe
{-# INLINE leaderboardIsMeL #-}
leaderboardProfitL :: Lens_' Leaderboard (Maybe Double)
leaderboardProfitL f Leaderboard{..} = (\leaderboardProfit -> Leaderboard { leaderboardProfit, ..} ) <$> f leaderboardProfit
{-# INLINE leaderboardProfitL #-}
liquidationOrderIdL :: Lens_' Liquidation (Text)
liquidationOrderIdL f Liquidation{..} = (\liquidationOrderId -> Liquidation { liquidationOrderId, ..} ) <$> f liquidationOrderId
{-# INLINE liquidationOrderIdL #-}
liquidationSymbolL :: Lens_' Liquidation (Maybe Text)
liquidationSymbolL f Liquidation{..} = (\liquidationSymbol -> Liquidation { liquidationSymbol, ..} ) <$> f liquidationSymbol
{-# INLINE liquidationSymbolL #-}
liquidationSideL :: Lens_' Liquidation (Maybe Text)
liquidationSideL f Liquidation{..} = (\liquidationSide -> Liquidation { liquidationSide, ..} ) <$> f liquidationSide
{-# INLINE liquidationSideL #-}
liquidationPriceL :: Lens_' Liquidation (Maybe Double)
liquidationPriceL f Liquidation{..} = (\liquidationPrice -> Liquidation { liquidationPrice, ..} ) <$> f liquidationPrice
{-# INLINE liquidationPriceL #-}
liquidationLeavesQtyL :: Lens_' Liquidation (Maybe Double)
liquidationLeavesQtyL f Liquidation{..} = (\liquidationLeavesQty -> Liquidation { liquidationLeavesQty, ..} ) <$> f liquidationLeavesQty
{-# INLINE liquidationLeavesQtyL #-}
marginAccountL :: Lens_' Margin (Double)
marginAccountL f Margin{..} = (\marginAccount -> Margin { marginAccount, ..} ) <$> f marginAccount
{-# INLINE marginAccountL #-}
marginCurrencyL :: Lens_' Margin (Text)
marginCurrencyL f Margin{..} = (\marginCurrency -> Margin { marginCurrency, ..} ) <$> f marginCurrency
{-# INLINE marginCurrencyL #-}
marginRiskLimitL :: Lens_' Margin (Maybe Double)
marginRiskLimitL f Margin{..} = (\marginRiskLimit -> Margin { marginRiskLimit, ..} ) <$> f marginRiskLimit
{-# INLINE marginRiskLimitL #-}
marginPrevStateL :: Lens_' Margin (Maybe Text)
marginPrevStateL f Margin{..} = (\marginPrevState -> Margin { marginPrevState, ..} ) <$> f marginPrevState
{-# INLINE marginPrevStateL #-}
marginStateL :: Lens_' Margin (Maybe Text)
marginStateL f Margin{..} = (\marginState -> Margin { marginState, ..} ) <$> f marginState
{-# INLINE marginStateL #-}
marginActionL :: Lens_' Margin (Maybe Text)
marginActionL f Margin{..} = (\marginAction -> Margin { marginAction, ..} ) <$> f marginAction
{-# INLINE marginActionL #-}
marginAmountL :: Lens_' Margin (Maybe Double)
marginAmountL f Margin{..} = (\marginAmount -> Margin { marginAmount, ..} ) <$> f marginAmount
{-# INLINE marginAmountL #-}
marginPendingCreditL :: Lens_' Margin (Maybe Double)
marginPendingCreditL f Margin{..} = (\marginPendingCredit -> Margin { marginPendingCredit, ..} ) <$> f marginPendingCredit
{-# INLINE marginPendingCreditL #-}
marginPendingDebitL :: Lens_' Margin (Maybe Double)
marginPendingDebitL f Margin{..} = (\marginPendingDebit -> Margin { marginPendingDebit, ..} ) <$> f marginPendingDebit
{-# INLINE marginPendingDebitL #-}
marginConfirmedDebitL :: Lens_' Margin (Maybe Double)
marginConfirmedDebitL f Margin{..} = (\marginConfirmedDebit -> Margin { marginConfirmedDebit, ..} ) <$> f marginConfirmedDebit
{-# INLINE marginConfirmedDebitL #-}
marginPrevRealisedPnlL :: Lens_' Margin (Maybe Double)
marginPrevRealisedPnlL f Margin{..} = (\marginPrevRealisedPnl -> Margin { marginPrevRealisedPnl, ..} ) <$> f marginPrevRealisedPnl
{-# INLINE marginPrevRealisedPnlL #-}
marginPrevUnrealisedPnlL :: Lens_' Margin (Maybe Double)
marginPrevUnrealisedPnlL f Margin{..} = (\marginPrevUnrealisedPnl -> Margin { marginPrevUnrealisedPnl, ..} ) <$> f marginPrevUnrealisedPnl
{-# INLINE marginPrevUnrealisedPnlL #-}
marginGrossCommL :: Lens_' Margin (Maybe Double)
marginGrossCommL f Margin{..} = (\marginGrossComm -> Margin { marginGrossComm, ..} ) <$> f marginGrossComm
{-# INLINE marginGrossCommL #-}
marginGrossOpenCostL :: Lens_' Margin (Maybe Double)
marginGrossOpenCostL f Margin{..} = (\marginGrossOpenCost -> Margin { marginGrossOpenCost, ..} ) <$> f marginGrossOpenCost
{-# INLINE marginGrossOpenCostL #-}
marginGrossOpenPremiumL :: Lens_' Margin (Maybe Double)
marginGrossOpenPremiumL f Margin{..} = (\marginGrossOpenPremium -> Margin { marginGrossOpenPremium, ..} ) <$> f marginGrossOpenPremium
{-# INLINE marginGrossOpenPremiumL #-}
marginGrossExecCostL :: Lens_' Margin (Maybe Double)
marginGrossExecCostL f Margin{..} = (\marginGrossExecCost -> Margin { marginGrossExecCost, ..} ) <$> f marginGrossExecCost
{-# INLINE marginGrossExecCostL #-}
marginGrossMarkValueL :: Lens_' Margin (Maybe Double)
marginGrossMarkValueL f Margin{..} = (\marginGrossMarkValue -> Margin { marginGrossMarkValue, ..} ) <$> f marginGrossMarkValue
{-# INLINE marginGrossMarkValueL #-}
marginRiskValueL :: Lens_' Margin (Maybe Double)
marginRiskValueL f Margin{..} = (\marginRiskValue -> Margin { marginRiskValue, ..} ) <$> f marginRiskValue
{-# INLINE marginRiskValueL #-}
marginTaxableMarginL :: Lens_' Margin (Maybe Double)
marginTaxableMarginL f Margin{..} = (\marginTaxableMargin -> Margin { marginTaxableMargin, ..} ) <$> f marginTaxableMargin
{-# INLINE marginTaxableMarginL #-}
marginInitMarginL :: Lens_' Margin (Maybe Double)
marginInitMarginL f Margin{..} = (\marginInitMargin -> Margin { marginInitMargin, ..} ) <$> f marginInitMargin
{-# INLINE marginInitMarginL #-}
marginMaintMarginL :: Lens_' Margin (Maybe Double)
marginMaintMarginL f Margin{..} = (\marginMaintMargin -> Margin { marginMaintMargin, ..} ) <$> f marginMaintMargin
{-# INLINE marginMaintMarginL #-}
marginSessionMarginL :: Lens_' Margin (Maybe Double)
marginSessionMarginL f Margin{..} = (\marginSessionMargin -> Margin { marginSessionMargin, ..} ) <$> f marginSessionMargin
{-# INLINE marginSessionMarginL #-}
marginTargetExcessMarginL :: Lens_' Margin (Maybe Double)
marginTargetExcessMarginL f Margin{..} = (\marginTargetExcessMargin -> Margin { marginTargetExcessMargin, ..} ) <$> f marginTargetExcessMargin
{-# INLINE marginTargetExcessMarginL #-}
marginVarMarginL :: Lens_' Margin (Maybe Double)
marginVarMarginL f Margin{..} = (\marginVarMargin -> Margin { marginVarMargin, ..} ) <$> f marginVarMargin
{-# INLINE marginVarMarginL #-}
marginRealisedPnlL :: Lens_' Margin (Maybe Double)
marginRealisedPnlL f Margin{..} = (\marginRealisedPnl -> Margin { marginRealisedPnl, ..} ) <$> f marginRealisedPnl
{-# INLINE marginRealisedPnlL #-}
marginUnrealisedPnlL :: Lens_' Margin (Maybe Double)
marginUnrealisedPnlL f Margin{..} = (\marginUnrealisedPnl -> Margin { marginUnrealisedPnl, ..} ) <$> f marginUnrealisedPnl
{-# INLINE marginUnrealisedPnlL #-}
marginIndicativeTaxL :: Lens_' Margin (Maybe Double)
marginIndicativeTaxL f Margin{..} = (\marginIndicativeTax -> Margin { marginIndicativeTax, ..} ) <$> f marginIndicativeTax
{-# INLINE marginIndicativeTaxL #-}
marginUnrealisedProfitL :: Lens_' Margin (Maybe Double)
marginUnrealisedProfitL f Margin{..} = (\marginUnrealisedProfit -> Margin { marginUnrealisedProfit, ..} ) <$> f marginUnrealisedProfit
{-# INLINE marginUnrealisedProfitL #-}
marginSyntheticMarginL :: Lens_' Margin (Maybe Double)
marginSyntheticMarginL f Margin{..} = (\marginSyntheticMargin -> Margin { marginSyntheticMargin, ..} ) <$> f marginSyntheticMargin
{-# INLINE marginSyntheticMarginL #-}
marginWalletBalanceL :: Lens_' Margin (Maybe Double)
marginWalletBalanceL f Margin{..} = (\marginWalletBalance -> Margin { marginWalletBalance, ..} ) <$> f marginWalletBalance
{-# INLINE marginWalletBalanceL #-}
marginMarginBalanceL :: Lens_' Margin (Maybe Double)
marginMarginBalanceL f Margin{..} = (\marginMarginBalance -> Margin { marginMarginBalance, ..} ) <$> f marginMarginBalance
{-# INLINE marginMarginBalanceL #-}
marginMarginBalancePcntL :: Lens_' Margin (Maybe Double)
marginMarginBalancePcntL f Margin{..} = (\marginMarginBalancePcnt -> Margin { marginMarginBalancePcnt, ..} ) <$> f marginMarginBalancePcnt
{-# INLINE marginMarginBalancePcntL #-}
marginMarginLeverageL :: Lens_' Margin (Maybe Double)
marginMarginLeverageL f Margin{..} = (\marginMarginLeverage -> Margin { marginMarginLeverage, ..} ) <$> f marginMarginLeverage
{-# INLINE marginMarginLeverageL #-}
marginMarginUsedPcntL :: Lens_' Margin (Maybe Double)
marginMarginUsedPcntL f Margin{..} = (\marginMarginUsedPcnt -> Margin { marginMarginUsedPcnt, ..} ) <$> f marginMarginUsedPcnt
{-# INLINE marginMarginUsedPcntL #-}
marginExcessMarginL :: Lens_' Margin (Maybe Double)
marginExcessMarginL f Margin{..} = (\marginExcessMargin -> Margin { marginExcessMargin, ..} ) <$> f marginExcessMargin
{-# INLINE marginExcessMarginL #-}
marginExcessMarginPcntL :: Lens_' Margin (Maybe Double)
marginExcessMarginPcntL f Margin{..} = (\marginExcessMarginPcnt -> Margin { marginExcessMarginPcnt, ..} ) <$> f marginExcessMarginPcnt
{-# INLINE marginExcessMarginPcntL #-}
marginAvailableMarginL :: Lens_' Margin (Maybe Double)
marginAvailableMarginL f Margin{..} = (\marginAvailableMargin -> Margin { marginAvailableMargin, ..} ) <$> f marginAvailableMargin
{-# INLINE marginAvailableMarginL #-}
marginWithdrawableMarginL :: Lens_' Margin (Maybe Double)
marginWithdrawableMarginL f Margin{..} = (\marginWithdrawableMargin -> Margin { marginWithdrawableMargin, ..} ) <$> f marginWithdrawableMargin
{-# INLINE marginWithdrawableMarginL #-}
marginTimestampL :: Lens_' Margin (Maybe DateTime)
marginTimestampL f Margin{..} = (\marginTimestamp -> Margin { marginTimestamp, ..} ) <$> f marginTimestamp
{-# INLINE marginTimestampL #-}
marginGrossLastValueL :: Lens_' Margin (Maybe Double)
marginGrossLastValueL f Margin{..} = (\marginGrossLastValue -> Margin { marginGrossLastValue, ..} ) <$> f marginGrossLastValue
{-# INLINE marginGrossLastValueL #-}
marginCommissionL :: Lens_' Margin (Maybe Double)
marginCommissionL f Margin{..} = (\marginCommission -> Margin { marginCommission, ..} ) <$> f marginCommission
{-# INLINE marginCommissionL #-}
notificationIdL :: Lens_' Notification (Maybe Double)
notificationIdL f Notification{..} = (\notificationId -> Notification { notificationId, ..} ) <$> f notificationId
{-# INLINE notificationIdL #-}
notificationDateL :: Lens_' Notification (DateTime)
notificationDateL f Notification{..} = (\notificationDate -> Notification { notificationDate, ..} ) <$> f notificationDate
{-# INLINE notificationDateL #-}
notificationTitleL :: Lens_' Notification (Text)
notificationTitleL f Notification{..} = (\notificationTitle -> Notification { notificationTitle, ..} ) <$> f notificationTitle
{-# INLINE notificationTitleL #-}
notificationBodyL :: Lens_' Notification (Text)
notificationBodyL f Notification{..} = (\notificationBody -> Notification { notificationBody, ..} ) <$> f notificationBody
{-# INLINE notificationBodyL #-}
notificationTtlL :: Lens_' Notification (Double)
notificationTtlL f Notification{..} = (\notificationTtl -> Notification { notificationTtl, ..} ) <$> f notificationTtl
{-# INLINE notificationTtlL #-}
notificationTypeL :: Lens_' Notification (Maybe E'Type)
notificationTypeL f Notification{..} = (\notificationType -> Notification { notificationType, ..} ) <$> f notificationType
{-# INLINE notificationTypeL #-}
notificationClosableL :: Lens_' Notification (Maybe Bool)
notificationClosableL f Notification{..} = (\notificationClosable -> Notification { notificationClosable, ..} ) <$> f notificationClosable
{-# INLINE notificationClosableL #-}
notificationPersistL :: Lens_' Notification (Maybe Bool)
notificationPersistL f Notification{..} = (\notificationPersist -> Notification { notificationPersist, ..} ) <$> f notificationPersist
{-# INLINE notificationPersistL #-}
notificationWaitForVisibilityL :: Lens_' Notification (Maybe Bool)
notificationWaitForVisibilityL f Notification{..} = (\notificationWaitForVisibility -> Notification { notificationWaitForVisibility, ..} ) <$> f notificationWaitForVisibility
{-# INLINE notificationWaitForVisibilityL #-}
notificationSoundL :: Lens_' Notification (Maybe Text)
notificationSoundL f Notification{..} = (\notificationSound -> Notification { notificationSound, ..} ) <$> f notificationSound
{-# INLINE notificationSoundL #-}
orderOrderIdL :: Lens_' Order (Text)
orderOrderIdL f Order{..} = (\orderOrderId -> Order { orderOrderId, ..} ) <$> f orderOrderId
{-# INLINE orderOrderIdL #-}
orderClOrdIdL :: Lens_' Order (Maybe Text)
orderClOrdIdL f Order{..} = (\orderClOrdId -> Order { orderClOrdId, ..} ) <$> f orderClOrdId
{-# INLINE orderClOrdIdL #-}
orderClOrdLinkIdL :: Lens_' Order (Maybe Text)
orderClOrdLinkIdL f Order{..} = (\orderClOrdLinkId -> Order { orderClOrdLinkId, ..} ) <$> f orderClOrdLinkId
{-# INLINE orderClOrdLinkIdL #-}
orderAccountL :: Lens_' Order (Maybe Double)
orderAccountL f Order{..} = (\orderAccount -> Order { orderAccount, ..} ) <$> f orderAccount
{-# INLINE orderAccountL #-}
orderSymbolL :: Lens_' Order (Maybe Text)
orderSymbolL f Order{..} = (\orderSymbol -> Order { orderSymbol, ..} ) <$> f orderSymbol
{-# INLINE orderSymbolL #-}
orderSideL :: Lens_' Order (Maybe Text)
orderSideL f Order{..} = (\orderSide -> Order { orderSide, ..} ) <$> f orderSide
{-# INLINE orderSideL #-}
orderSimpleOrderQtyL :: Lens_' Order (Maybe Double)
orderSimpleOrderQtyL f Order{..} = (\orderSimpleOrderQty -> Order { orderSimpleOrderQty, ..} ) <$> f orderSimpleOrderQty
{-# INLINE orderSimpleOrderQtyL #-}
orderOrderQtyL :: Lens_' Order (Maybe Double)
orderOrderQtyL f Order{..} = (\orderOrderQty -> Order { orderOrderQty, ..} ) <$> f orderOrderQty
{-# INLINE orderOrderQtyL #-}
orderPriceL :: Lens_' Order (Maybe Double)
orderPriceL f Order{..} = (\orderPrice -> Order { orderPrice, ..} ) <$> f orderPrice
{-# INLINE orderPriceL #-}
orderDisplayQtyL :: Lens_' Order (Maybe Double)
orderDisplayQtyL f Order{..} = (\orderDisplayQty -> Order { orderDisplayQty, ..} ) <$> f orderDisplayQty
{-# INLINE orderDisplayQtyL #-}
orderStopPxL :: Lens_' Order (Maybe Double)
orderStopPxL f Order{..} = (\orderStopPx -> Order { orderStopPx, ..} ) <$> f orderStopPx
{-# INLINE orderStopPxL #-}
orderPegOffsetValueL :: Lens_' Order (Maybe Double)
orderPegOffsetValueL f Order{..} = (\orderPegOffsetValue -> Order { orderPegOffsetValue, ..} ) <$> f orderPegOffsetValue
{-# INLINE orderPegOffsetValueL #-}
orderPegPriceTypeL :: Lens_' Order (Maybe Text)
orderPegPriceTypeL f Order{..} = (\orderPegPriceType -> Order { orderPegPriceType, ..} ) <$> f orderPegPriceType
{-# INLINE orderPegPriceTypeL #-}
orderCurrencyL :: Lens_' Order (Maybe Text)
orderCurrencyL f Order{..} = (\orderCurrency -> Order { orderCurrency, ..} ) <$> f orderCurrency
{-# INLINE orderCurrencyL #-}
orderSettlCurrencyL :: Lens_' Order (Maybe Text)
orderSettlCurrencyL f Order{..} = (\orderSettlCurrency -> Order { orderSettlCurrency, ..} ) <$> f orderSettlCurrency
{-# INLINE orderSettlCurrencyL #-}
orderOrdTypeL :: Lens_' Order (Maybe Text)
orderOrdTypeL f Order{..} = (\orderOrdType -> Order { orderOrdType, ..} ) <$> f orderOrdType
{-# INLINE orderOrdTypeL #-}
orderTimeInForceL :: Lens_' Order (Maybe Text)
orderTimeInForceL f Order{..} = (\orderTimeInForce -> Order { orderTimeInForce, ..} ) <$> f orderTimeInForce
{-# INLINE orderTimeInForceL #-}
orderExecInstL :: Lens_' Order (Maybe Text)
orderExecInstL f Order{..} = (\orderExecInst -> Order { orderExecInst, ..} ) <$> f orderExecInst
{-# INLINE orderExecInstL #-}
orderContingencyTypeL :: Lens_' Order (Maybe Text)
orderContingencyTypeL f Order{..} = (\orderContingencyType -> Order { orderContingencyType, ..} ) <$> f orderContingencyType
{-# INLINE orderContingencyTypeL #-}
orderExDestinationL :: Lens_' Order (Maybe Text)
orderExDestinationL f Order{..} = (\orderExDestination -> Order { orderExDestination, ..} ) <$> f orderExDestination
{-# INLINE orderExDestinationL #-}
orderOrdStatusL :: Lens_' Order (Maybe Text)
orderOrdStatusL f Order{..} = (\orderOrdStatus -> Order { orderOrdStatus, ..} ) <$> f orderOrdStatus
{-# INLINE orderOrdStatusL #-}
orderTriggeredL :: Lens_' Order (Maybe Text)
orderTriggeredL f Order{..} = (\orderTriggered -> Order { orderTriggered, ..} ) <$> f orderTriggered
{-# INLINE orderTriggeredL #-}
orderWorkingIndicatorL :: Lens_' Order (Maybe Bool)
orderWorkingIndicatorL f Order{..} = (\orderWorkingIndicator -> Order { orderWorkingIndicator, ..} ) <$> f orderWorkingIndicator
{-# INLINE orderWorkingIndicatorL #-}
orderOrdRejReasonL :: Lens_' Order (Maybe Text)
orderOrdRejReasonL f Order{..} = (\orderOrdRejReason -> Order { orderOrdRejReason, ..} ) <$> f orderOrdRejReason
{-# INLINE orderOrdRejReasonL #-}
orderSimpleLeavesQtyL :: Lens_' Order (Maybe Double)
orderSimpleLeavesQtyL f Order{..} = (\orderSimpleLeavesQty -> Order { orderSimpleLeavesQty, ..} ) <$> f orderSimpleLeavesQty
{-# INLINE orderSimpleLeavesQtyL #-}
orderLeavesQtyL :: Lens_' Order (Maybe Double)
orderLeavesQtyL f Order{..} = (\orderLeavesQty -> Order { orderLeavesQty, ..} ) <$> f orderLeavesQty
{-# INLINE orderLeavesQtyL #-}
orderSimpleCumQtyL :: Lens_' Order (Maybe Double)
orderSimpleCumQtyL f Order{..} = (\orderSimpleCumQty -> Order { orderSimpleCumQty, ..} ) <$> f orderSimpleCumQty
{-# INLINE orderSimpleCumQtyL #-}
orderCumQtyL :: Lens_' Order (Maybe Double)
orderCumQtyL f Order{..} = (\orderCumQty -> Order { orderCumQty, ..} ) <$> f orderCumQty
{-# INLINE orderCumQtyL #-}
orderAvgPxL :: Lens_' Order (Maybe Double)
orderAvgPxL f Order{..} = (\orderAvgPx -> Order { orderAvgPx, ..} ) <$> f orderAvgPx
{-# INLINE orderAvgPxL #-}
orderMultiLegReportingTypeL :: Lens_' Order (Maybe Text)
orderMultiLegReportingTypeL f Order{..} = (\orderMultiLegReportingType -> Order { orderMultiLegReportingType, ..} ) <$> f orderMultiLegReportingType
{-# INLINE orderMultiLegReportingTypeL #-}
orderTextL :: Lens_' Order (Maybe Text)
orderTextL f Order{..} = (\orderText -> Order { orderText, ..} ) <$> f orderText
{-# INLINE orderTextL #-}
orderTransactTimeL :: Lens_' Order (Maybe DateTime)
orderTransactTimeL f Order{..} = (\orderTransactTime -> Order { orderTransactTime, ..} ) <$> f orderTransactTime
{-# INLINE orderTransactTimeL #-}
orderTimestampL :: Lens_' Order (Maybe DateTime)
orderTimestampL f Order{..} = (\orderTimestamp -> Order { orderTimestamp, ..} ) <$> f orderTimestamp
{-# INLINE orderTimestampL #-}
orderBookSymbolL :: Lens_' OrderBook (Text)
orderBookSymbolL f OrderBook{..} = (\orderBookSymbol -> OrderBook { orderBookSymbol, ..} ) <$> f orderBookSymbol
{-# INLINE orderBookSymbolL #-}
orderBookLevelL :: Lens_' OrderBook (Double)
orderBookLevelL f OrderBook{..} = (\orderBookLevel -> OrderBook { orderBookLevel, ..} ) <$> f orderBookLevel
{-# INLINE orderBookLevelL #-}
orderBookBidSizeL :: Lens_' OrderBook (Maybe Double)
orderBookBidSizeL f OrderBook{..} = (\orderBookBidSize -> OrderBook { orderBookBidSize, ..} ) <$> f orderBookBidSize
{-# INLINE orderBookBidSizeL #-}
orderBookBidPriceL :: Lens_' OrderBook (Maybe Double)
orderBookBidPriceL f OrderBook{..} = (\orderBookBidPrice -> OrderBook { orderBookBidPrice, ..} ) <$> f orderBookBidPrice
{-# INLINE orderBookBidPriceL #-}
orderBookAskPriceL :: Lens_' OrderBook (Maybe Double)
orderBookAskPriceL f OrderBook{..} = (\orderBookAskPrice -> OrderBook { orderBookAskPrice, ..} ) <$> f orderBookAskPrice
{-# INLINE orderBookAskPriceL #-}
orderBookAskSizeL :: Lens_' OrderBook (Maybe Double)
orderBookAskSizeL f OrderBook{..} = (\orderBookAskSize -> OrderBook { orderBookAskSize, ..} ) <$> f orderBookAskSize
{-# INLINE orderBookAskSizeL #-}
orderBookTimestampL :: Lens_' OrderBook (Maybe DateTime)
orderBookTimestampL f OrderBook{..} = (\orderBookTimestamp -> OrderBook { orderBookTimestamp, ..} ) <$> f orderBookTimestamp
{-# INLINE orderBookTimestampL #-}
orderBookL2SymbolL :: Lens_' OrderBookL2 (Text)
orderBookL2SymbolL f OrderBookL2{..} = (\orderBookL2Symbol -> OrderBookL2 { orderBookL2Symbol, ..} ) <$> f orderBookL2Symbol
{-# INLINE orderBookL2SymbolL #-}
orderBookL2IdL :: Lens_' OrderBookL2 (Double)
orderBookL2IdL f OrderBookL2{..} = (\orderBookL2Id -> OrderBookL2 { orderBookL2Id, ..} ) <$> f orderBookL2Id
{-# INLINE orderBookL2IdL #-}
orderBookL2SideL :: Lens_' OrderBookL2 (Text)
orderBookL2SideL f OrderBookL2{..} = (\orderBookL2Side -> OrderBookL2 { orderBookL2Side, ..} ) <$> f orderBookL2Side
{-# INLINE orderBookL2SideL #-}
orderBookL2SizeL :: Lens_' OrderBookL2 (Maybe Double)
orderBookL2SizeL f OrderBookL2{..} = (\orderBookL2Size -> OrderBookL2 { orderBookL2Size, ..} ) <$> f orderBookL2Size
{-# INLINE orderBookL2SizeL #-}
orderBookL2PriceL :: Lens_' OrderBookL2 (Maybe Double)
orderBookL2PriceL f OrderBookL2{..} = (\orderBookL2Price -> OrderBookL2 { orderBookL2Price, ..} ) <$> f orderBookL2Price
{-# INLINE orderBookL2PriceL #-}
positionAccountL :: Lens_' Position (Double)
positionAccountL f Position{..} = (\positionAccount -> Position { positionAccount, ..} ) <$> f positionAccount
{-# INLINE positionAccountL #-}
positionSymbolL :: Lens_' Position (Text)
positionSymbolL f Position{..} = (\positionSymbol -> Position { positionSymbol, ..} ) <$> f positionSymbol
{-# INLINE positionSymbolL #-}
positionCurrencyL :: Lens_' Position (Text)
positionCurrencyL f Position{..} = (\positionCurrency -> Position { positionCurrency, ..} ) <$> f positionCurrency
{-# INLINE positionCurrencyL #-}
positionUnderlyingL :: Lens_' Position (Maybe Text)
positionUnderlyingL f Position{..} = (\positionUnderlying -> Position { positionUnderlying, ..} ) <$> f positionUnderlying
{-# INLINE positionUnderlyingL #-}
positionQuoteCurrencyL :: Lens_' Position (Maybe Text)
positionQuoteCurrencyL f Position{..} = (\positionQuoteCurrency -> Position { positionQuoteCurrency, ..} ) <$> f positionQuoteCurrency
{-# INLINE positionQuoteCurrencyL #-}
positionCommissionL :: Lens_' Position (Maybe Double)
positionCommissionL f Position{..} = (\positionCommission -> Position { positionCommission, ..} ) <$> f positionCommission
{-# INLINE positionCommissionL #-}
positionInitMarginReqL :: Lens_' Position (Maybe Double)
positionInitMarginReqL f Position{..} = (\positionInitMarginReq -> Position { positionInitMarginReq, ..} ) <$> f positionInitMarginReq
{-# INLINE positionInitMarginReqL #-}
positionMaintMarginReqL :: Lens_' Position (Maybe Double)
positionMaintMarginReqL f Position{..} = (\positionMaintMarginReq -> Position { positionMaintMarginReq, ..} ) <$> f positionMaintMarginReq
{-# INLINE positionMaintMarginReqL #-}
positionRiskLimitL :: Lens_' Position (Maybe Double)
positionRiskLimitL f Position{..} = (\positionRiskLimit -> Position { positionRiskLimit, ..} ) <$> f positionRiskLimit
{-# INLINE positionRiskLimitL #-}
positionLeverageL :: Lens_' Position (Maybe Double)
positionLeverageL f Position{..} = (\positionLeverage -> Position { positionLeverage, ..} ) <$> f positionLeverage
{-# INLINE positionLeverageL #-}
positionCrossMarginL :: Lens_' Position (Maybe Bool)
positionCrossMarginL f Position{..} = (\positionCrossMargin -> Position { positionCrossMargin, ..} ) <$> f positionCrossMargin
{-# INLINE positionCrossMarginL #-}
positionDeleveragePercentileL :: Lens_' Position (Maybe Double)
positionDeleveragePercentileL f Position{..} = (\positionDeleveragePercentile -> Position { positionDeleveragePercentile, ..} ) <$> f positionDeleveragePercentile
{-# INLINE positionDeleveragePercentileL #-}
positionRebalancedPnlL :: Lens_' Position (Maybe Double)
positionRebalancedPnlL f Position{..} = (\positionRebalancedPnl -> Position { positionRebalancedPnl, ..} ) <$> f positionRebalancedPnl
{-# INLINE positionRebalancedPnlL #-}
positionPrevRealisedPnlL :: Lens_' Position (Maybe Double)
positionPrevRealisedPnlL f Position{..} = (\positionPrevRealisedPnl -> Position { positionPrevRealisedPnl, ..} ) <$> f positionPrevRealisedPnl
{-# INLINE positionPrevRealisedPnlL #-}
positionPrevUnrealisedPnlL :: Lens_' Position (Maybe Double)
positionPrevUnrealisedPnlL f Position{..} = (\positionPrevUnrealisedPnl -> Position { positionPrevUnrealisedPnl, ..} ) <$> f positionPrevUnrealisedPnl
{-# INLINE positionPrevUnrealisedPnlL #-}
positionPrevClosePriceL :: Lens_' Position (Maybe Double)
positionPrevClosePriceL f Position{..} = (\positionPrevClosePrice -> Position { positionPrevClosePrice, ..} ) <$> f positionPrevClosePrice
{-# INLINE positionPrevClosePriceL #-}
positionOpeningTimestampL :: Lens_' Position (Maybe DateTime)
positionOpeningTimestampL f Position{..} = (\positionOpeningTimestamp -> Position { positionOpeningTimestamp, ..} ) <$> f positionOpeningTimestamp
{-# INLINE positionOpeningTimestampL #-}
positionOpeningQtyL :: Lens_' Position (Maybe Double)
positionOpeningQtyL f Position{..} = (\positionOpeningQty -> Position { positionOpeningQty, ..} ) <$> f positionOpeningQty
{-# INLINE positionOpeningQtyL #-}
positionOpeningCostL :: Lens_' Position (Maybe Double)
positionOpeningCostL f Position{..} = (\positionOpeningCost -> Position { positionOpeningCost, ..} ) <$> f positionOpeningCost
{-# INLINE positionOpeningCostL #-}
positionOpeningCommL :: Lens_' Position (Maybe Double)
positionOpeningCommL f Position{..} = (\positionOpeningComm -> Position { positionOpeningComm, ..} ) <$> f positionOpeningComm
{-# INLINE positionOpeningCommL #-}
positionOpenOrderBuyQtyL :: Lens_' Position (Maybe Double)
positionOpenOrderBuyQtyL f Position{..} = (\positionOpenOrderBuyQty -> Position { positionOpenOrderBuyQty, ..} ) <$> f positionOpenOrderBuyQty
{-# INLINE positionOpenOrderBuyQtyL #-}
positionOpenOrderBuyCostL :: Lens_' Position (Maybe Double)
positionOpenOrderBuyCostL f Position{..} = (\positionOpenOrderBuyCost -> Position { positionOpenOrderBuyCost, ..} ) <$> f positionOpenOrderBuyCost
{-# INLINE positionOpenOrderBuyCostL #-}
positionOpenOrderBuyPremiumL :: Lens_' Position (Maybe Double)
positionOpenOrderBuyPremiumL f Position{..} = (\positionOpenOrderBuyPremium -> Position { positionOpenOrderBuyPremium, ..} ) <$> f positionOpenOrderBuyPremium
{-# INLINE positionOpenOrderBuyPremiumL #-}
positionOpenOrderSellQtyL :: Lens_' Position (Maybe Double)
positionOpenOrderSellQtyL f Position{..} = (\positionOpenOrderSellQty -> Position { positionOpenOrderSellQty, ..} ) <$> f positionOpenOrderSellQty
{-# INLINE positionOpenOrderSellQtyL #-}
positionOpenOrderSellCostL :: Lens_' Position (Maybe Double)
positionOpenOrderSellCostL f Position{..} = (\positionOpenOrderSellCost -> Position { positionOpenOrderSellCost, ..} ) <$> f positionOpenOrderSellCost
{-# INLINE positionOpenOrderSellCostL #-}
positionOpenOrderSellPremiumL :: Lens_' Position (Maybe Double)
positionOpenOrderSellPremiumL f Position{..} = (\positionOpenOrderSellPremium -> Position { positionOpenOrderSellPremium, ..} ) <$> f positionOpenOrderSellPremium
{-# INLINE positionOpenOrderSellPremiumL #-}
positionExecBuyQtyL :: Lens_' Position (Maybe Double)
positionExecBuyQtyL f Position{..} = (\positionExecBuyQty -> Position { positionExecBuyQty, ..} ) <$> f positionExecBuyQty
{-# INLINE positionExecBuyQtyL #-}
positionExecBuyCostL :: Lens_' Position (Maybe Double)
positionExecBuyCostL f Position{..} = (\positionExecBuyCost -> Position { positionExecBuyCost, ..} ) <$> f positionExecBuyCost
{-# INLINE positionExecBuyCostL #-}
positionExecSellQtyL :: Lens_' Position (Maybe Double)
positionExecSellQtyL f Position{..} = (\positionExecSellQty -> Position { positionExecSellQty, ..} ) <$> f positionExecSellQty
{-# INLINE positionExecSellQtyL #-}
positionExecSellCostL :: Lens_' Position (Maybe Double)
positionExecSellCostL f Position{..} = (\positionExecSellCost -> Position { positionExecSellCost, ..} ) <$> f positionExecSellCost
{-# INLINE positionExecSellCostL #-}
positionExecQtyL :: Lens_' Position (Maybe Double)
positionExecQtyL f Position{..} = (\positionExecQty -> Position { positionExecQty, ..} ) <$> f positionExecQty
{-# INLINE positionExecQtyL #-}
positionExecCostL :: Lens_' Position (Maybe Double)
positionExecCostL f Position{..} = (\positionExecCost -> Position { positionExecCost, ..} ) <$> f positionExecCost
{-# INLINE positionExecCostL #-}
positionExecCommL :: Lens_' Position (Maybe Double)
positionExecCommL f Position{..} = (\positionExecComm -> Position { positionExecComm, ..} ) <$> f positionExecComm
{-# INLINE positionExecCommL #-}
positionCurrentTimestampL :: Lens_' Position (Maybe DateTime)
positionCurrentTimestampL f Position{..} = (\positionCurrentTimestamp -> Position { positionCurrentTimestamp, ..} ) <$> f positionCurrentTimestamp
{-# INLINE positionCurrentTimestampL #-}
positionCurrentQtyL :: Lens_' Position (Maybe Double)
positionCurrentQtyL f Position{..} = (\positionCurrentQty -> Position { positionCurrentQty, ..} ) <$> f positionCurrentQty
{-# INLINE positionCurrentQtyL #-}
positionCurrentCostL :: Lens_' Position (Maybe Double)
positionCurrentCostL f Position{..} = (\positionCurrentCost -> Position { positionCurrentCost, ..} ) <$> f positionCurrentCost
{-# INLINE positionCurrentCostL #-}
positionCurrentCommL :: Lens_' Position (Maybe Double)
positionCurrentCommL f Position{..} = (\positionCurrentComm -> Position { positionCurrentComm, ..} ) <$> f positionCurrentComm
{-# INLINE positionCurrentCommL #-}
positionRealisedCostL :: Lens_' Position (Maybe Double)
positionRealisedCostL f Position{..} = (\positionRealisedCost -> Position { positionRealisedCost, ..} ) <$> f positionRealisedCost
{-# INLINE positionRealisedCostL #-}
positionUnrealisedCostL :: Lens_' Position (Maybe Double)
positionUnrealisedCostL f Position{..} = (\positionUnrealisedCost -> Position { positionUnrealisedCost, ..} ) <$> f positionUnrealisedCost
{-# INLINE positionUnrealisedCostL #-}
positionGrossOpenCostL :: Lens_' Position (Maybe Double)
positionGrossOpenCostL f Position{..} = (\positionGrossOpenCost -> Position { positionGrossOpenCost, ..} ) <$> f positionGrossOpenCost
{-# INLINE positionGrossOpenCostL #-}
positionGrossOpenPremiumL :: Lens_' Position (Maybe Double)
positionGrossOpenPremiumL f Position{..} = (\positionGrossOpenPremium -> Position { positionGrossOpenPremium, ..} ) <$> f positionGrossOpenPremium
{-# INLINE positionGrossOpenPremiumL #-}
positionGrossExecCostL :: Lens_' Position (Maybe Double)
positionGrossExecCostL f Position{..} = (\positionGrossExecCost -> Position { positionGrossExecCost, ..} ) <$> f positionGrossExecCost
{-# INLINE positionGrossExecCostL #-}
positionIsOpenL :: Lens_' Position (Maybe Bool)
positionIsOpenL f Position{..} = (\positionIsOpen -> Position { positionIsOpen, ..} ) <$> f positionIsOpen
{-# INLINE positionIsOpenL #-}
positionMarkPriceL :: Lens_' Position (Maybe Double)
positionMarkPriceL f Position{..} = (\positionMarkPrice -> Position { positionMarkPrice, ..} ) <$> f positionMarkPrice
{-# INLINE positionMarkPriceL #-}
positionMarkValueL :: Lens_' Position (Maybe Double)
positionMarkValueL f Position{..} = (\positionMarkValue -> Position { positionMarkValue, ..} ) <$> f positionMarkValue
{-# INLINE positionMarkValueL #-}
positionRiskValueL :: Lens_' Position (Maybe Double)
positionRiskValueL f Position{..} = (\positionRiskValue -> Position { positionRiskValue, ..} ) <$> f positionRiskValue
{-# INLINE positionRiskValueL #-}
positionHomeNotionalL :: Lens_' Position (Maybe Double)
positionHomeNotionalL f Position{..} = (\positionHomeNotional -> Position { positionHomeNotional, ..} ) <$> f positionHomeNotional
{-# INLINE positionHomeNotionalL #-}
positionForeignNotionalL :: Lens_' Position (Maybe Double)
positionForeignNotionalL f Position{..} = (\positionForeignNotional -> Position { positionForeignNotional, ..} ) <$> f positionForeignNotional
{-# INLINE positionForeignNotionalL #-}
positionPosStateL :: Lens_' Position (Maybe Text)
positionPosStateL f Position{..} = (\positionPosState -> Position { positionPosState, ..} ) <$> f positionPosState
{-# INLINE positionPosStateL #-}
positionPosCostL :: Lens_' Position (Maybe Double)
positionPosCostL f Position{..} = (\positionPosCost -> Position { positionPosCost, ..} ) <$> f positionPosCost
{-# INLINE positionPosCostL #-}
positionPosCost2L :: Lens_' Position (Maybe Double)
positionPosCost2L f Position{..} = (\positionPosCost2 -> Position { positionPosCost2, ..} ) <$> f positionPosCost2
{-# INLINE positionPosCost2L #-}
positionPosCrossL :: Lens_' Position (Maybe Double)
positionPosCrossL f Position{..} = (\positionPosCross -> Position { positionPosCross, ..} ) <$> f positionPosCross
{-# INLINE positionPosCrossL #-}
positionPosInitL :: Lens_' Position (Maybe Double)
positionPosInitL f Position{..} = (\positionPosInit -> Position { positionPosInit, ..} ) <$> f positionPosInit
{-# INLINE positionPosInitL #-}
positionPosCommL :: Lens_' Position (Maybe Double)
positionPosCommL f Position{..} = (\positionPosComm -> Position { positionPosComm, ..} ) <$> f positionPosComm
{-# INLINE positionPosCommL #-}
positionPosLossL :: Lens_' Position (Maybe Double)
positionPosLossL f Position{..} = (\positionPosLoss -> Position { positionPosLoss, ..} ) <$> f positionPosLoss
{-# INLINE positionPosLossL #-}
positionPosMarginL :: Lens_' Position (Maybe Double)
positionPosMarginL f Position{..} = (\positionPosMargin -> Position { positionPosMargin, ..} ) <$> f positionPosMargin
{-# INLINE positionPosMarginL #-}
positionPosMaintL :: Lens_' Position (Maybe Double)
positionPosMaintL f Position{..} = (\positionPosMaint -> Position { positionPosMaint, ..} ) <$> f positionPosMaint
{-# INLINE positionPosMaintL #-}
positionPosAllowanceL :: Lens_' Position (Maybe Double)
positionPosAllowanceL f Position{..} = (\positionPosAllowance -> Position { positionPosAllowance, ..} ) <$> f positionPosAllowance
{-# INLINE positionPosAllowanceL #-}
positionTaxableMarginL :: Lens_' Position (Maybe Double)
positionTaxableMarginL f Position{..} = (\positionTaxableMargin -> Position { positionTaxableMargin, ..} ) <$> f positionTaxableMargin
{-# INLINE positionTaxableMarginL #-}
positionInitMarginL :: Lens_' Position (Maybe Double)
positionInitMarginL f Position{..} = (\positionInitMargin -> Position { positionInitMargin, ..} ) <$> f positionInitMargin
{-# INLINE positionInitMarginL #-}
positionMaintMarginL :: Lens_' Position (Maybe Double)
positionMaintMarginL f Position{..} = (\positionMaintMargin -> Position { positionMaintMargin, ..} ) <$> f positionMaintMargin
{-# INLINE positionMaintMarginL #-}
positionSessionMarginL :: Lens_' Position (Maybe Double)
positionSessionMarginL f Position{..} = (\positionSessionMargin -> Position { positionSessionMargin, ..} ) <$> f positionSessionMargin
{-# INLINE positionSessionMarginL #-}
positionTargetExcessMarginL :: Lens_' Position (Maybe Double)
positionTargetExcessMarginL f Position{..} = (\positionTargetExcessMargin -> Position { positionTargetExcessMargin, ..} ) <$> f positionTargetExcessMargin
{-# INLINE positionTargetExcessMarginL #-}
positionVarMarginL :: Lens_' Position (Maybe Double)
positionVarMarginL f Position{..} = (\positionVarMargin -> Position { positionVarMargin, ..} ) <$> f positionVarMargin
{-# INLINE positionVarMarginL #-}
positionRealisedGrossPnlL :: Lens_' Position (Maybe Double)
positionRealisedGrossPnlL f Position{..} = (\positionRealisedGrossPnl -> Position { positionRealisedGrossPnl, ..} ) <$> f positionRealisedGrossPnl
{-# INLINE positionRealisedGrossPnlL #-}
positionRealisedTaxL :: Lens_' Position (Maybe Double)
positionRealisedTaxL f Position{..} = (\positionRealisedTax -> Position { positionRealisedTax, ..} ) <$> f positionRealisedTax
{-# INLINE positionRealisedTaxL #-}
positionRealisedPnlL :: Lens_' Position (Maybe Double)
positionRealisedPnlL f Position{..} = (\positionRealisedPnl -> Position { positionRealisedPnl, ..} ) <$> f positionRealisedPnl
{-# INLINE positionRealisedPnlL #-}
positionUnrealisedGrossPnlL :: Lens_' Position (Maybe Double)
positionUnrealisedGrossPnlL f Position{..} = (\positionUnrealisedGrossPnl -> Position { positionUnrealisedGrossPnl, ..} ) <$> f positionUnrealisedGrossPnl
{-# INLINE positionUnrealisedGrossPnlL #-}
positionLongBankruptL :: Lens_' Position (Maybe Double)
positionLongBankruptL f Position{..} = (\positionLongBankrupt -> Position { positionLongBankrupt, ..} ) <$> f positionLongBankrupt
{-# INLINE positionLongBankruptL #-}
positionShortBankruptL :: Lens_' Position (Maybe Double)
positionShortBankruptL f Position{..} = (\positionShortBankrupt -> Position { positionShortBankrupt, ..} ) <$> f positionShortBankrupt
{-# INLINE positionShortBankruptL #-}
positionTaxBaseL :: Lens_' Position (Maybe Double)
positionTaxBaseL f Position{..} = (\positionTaxBase -> Position { positionTaxBase, ..} ) <$> f positionTaxBase
{-# INLINE positionTaxBaseL #-}
positionIndicativeTaxRateL :: Lens_' Position (Maybe Double)
positionIndicativeTaxRateL f Position{..} = (\positionIndicativeTaxRate -> Position { positionIndicativeTaxRate, ..} ) <$> f positionIndicativeTaxRate
{-# INLINE positionIndicativeTaxRateL #-}
positionIndicativeTaxL :: Lens_' Position (Maybe Double)
positionIndicativeTaxL f Position{..} = (\positionIndicativeTax -> Position { positionIndicativeTax, ..} ) <$> f positionIndicativeTax
{-# INLINE positionIndicativeTaxL #-}
positionUnrealisedTaxL :: Lens_' Position (Maybe Double)
positionUnrealisedTaxL f Position{..} = (\positionUnrealisedTax -> Position { positionUnrealisedTax, ..} ) <$> f positionUnrealisedTax
{-# INLINE positionUnrealisedTaxL #-}
positionUnrealisedPnlL :: Lens_' Position (Maybe Double)
positionUnrealisedPnlL f Position{..} = (\positionUnrealisedPnl -> Position { positionUnrealisedPnl, ..} ) <$> f positionUnrealisedPnl
{-# INLINE positionUnrealisedPnlL #-}
positionUnrealisedPnlPcntL :: Lens_' Position (Maybe Double)
positionUnrealisedPnlPcntL f Position{..} = (\positionUnrealisedPnlPcnt -> Position { positionUnrealisedPnlPcnt, ..} ) <$> f positionUnrealisedPnlPcnt
{-# INLINE positionUnrealisedPnlPcntL #-}
positionUnrealisedRoePcntL :: Lens_' Position (Maybe Double)
positionUnrealisedRoePcntL f Position{..} = (\positionUnrealisedRoePcnt -> Position { positionUnrealisedRoePcnt, ..} ) <$> f positionUnrealisedRoePcnt
{-# INLINE positionUnrealisedRoePcntL #-}
positionSimpleQtyL :: Lens_' Position (Maybe Double)
positionSimpleQtyL f Position{..} = (\positionSimpleQty -> Position { positionSimpleQty, ..} ) <$> f positionSimpleQty
{-# INLINE positionSimpleQtyL #-}
positionSimpleCostL :: Lens_' Position (Maybe Double)
positionSimpleCostL f Position{..} = (\positionSimpleCost -> Position { positionSimpleCost, ..} ) <$> f positionSimpleCost
{-# INLINE positionSimpleCostL #-}
positionSimpleValueL :: Lens_' Position (Maybe Double)
positionSimpleValueL f Position{..} = (\positionSimpleValue -> Position { positionSimpleValue, ..} ) <$> f positionSimpleValue
{-# INLINE positionSimpleValueL #-}
positionSimplePnlL :: Lens_' Position (Maybe Double)
positionSimplePnlL f Position{..} = (\positionSimplePnl -> Position { positionSimplePnl, ..} ) <$> f positionSimplePnl
{-# INLINE positionSimplePnlL #-}
positionSimplePnlPcntL :: Lens_' Position (Maybe Double)
positionSimplePnlPcntL f Position{..} = (\positionSimplePnlPcnt -> Position { positionSimplePnlPcnt, ..} ) <$> f positionSimplePnlPcnt
{-# INLINE positionSimplePnlPcntL #-}
positionAvgCostPriceL :: Lens_' Position (Maybe Double)
positionAvgCostPriceL f Position{..} = (\positionAvgCostPrice -> Position { positionAvgCostPrice, ..} ) <$> f positionAvgCostPrice
{-# INLINE positionAvgCostPriceL #-}
positionAvgEntryPriceL :: Lens_' Position (Maybe Double)
positionAvgEntryPriceL f Position{..} = (\positionAvgEntryPrice -> Position { positionAvgEntryPrice, ..} ) <$> f positionAvgEntryPrice
{-# INLINE positionAvgEntryPriceL #-}
positionBreakEvenPriceL :: Lens_' Position (Maybe Double)
positionBreakEvenPriceL f Position{..} = (\positionBreakEvenPrice -> Position { positionBreakEvenPrice, ..} ) <$> f positionBreakEvenPrice
{-# INLINE positionBreakEvenPriceL #-}
positionMarginCallPriceL :: Lens_' Position (Maybe Double)
positionMarginCallPriceL f Position{..} = (\positionMarginCallPrice -> Position { positionMarginCallPrice, ..} ) <$> f positionMarginCallPrice
{-# INLINE positionMarginCallPriceL #-}
positionLiquidationPriceL :: Lens_' Position (Maybe Double)
positionLiquidationPriceL f Position{..} = (\positionLiquidationPrice -> Position { positionLiquidationPrice, ..} ) <$> f positionLiquidationPrice
{-# INLINE positionLiquidationPriceL #-}
positionBankruptPriceL :: Lens_' Position (Maybe Double)
positionBankruptPriceL f Position{..} = (\positionBankruptPrice -> Position { positionBankruptPrice, ..} ) <$> f positionBankruptPrice
{-# INLINE positionBankruptPriceL #-}
positionTimestampL :: Lens_' Position (Maybe DateTime)
positionTimestampL f Position{..} = (\positionTimestamp -> Position { positionTimestamp, ..} ) <$> f positionTimestamp
{-# INLINE positionTimestampL #-}
positionLastPriceL :: Lens_' Position (Maybe Double)
positionLastPriceL f Position{..} = (\positionLastPrice -> Position { positionLastPrice, ..} ) <$> f positionLastPrice
{-# INLINE positionLastPriceL #-}
positionLastValueL :: Lens_' Position (Maybe Double)
positionLastValueL f Position{..} = (\positionLastValue -> Position { positionLastValue, ..} ) <$> f positionLastValue
{-# INLINE positionLastValueL #-}
quoteTimestampL :: Lens_' Quote (DateTime)
quoteTimestampL f Quote{..} = (\quoteTimestamp -> Quote { quoteTimestamp, ..} ) <$> f quoteTimestamp
{-# INLINE quoteTimestampL #-}
quoteSymbolL :: Lens_' Quote (Text)
quoteSymbolL f Quote{..} = (\quoteSymbol -> Quote { quoteSymbol, ..} ) <$> f quoteSymbol
{-# INLINE quoteSymbolL #-}
quoteBidSizeL :: Lens_' Quote (Maybe Double)
quoteBidSizeL f Quote{..} = (\quoteBidSize -> Quote { quoteBidSize, ..} ) <$> f quoteBidSize
{-# INLINE quoteBidSizeL #-}
quoteBidPriceL :: Lens_' Quote (Maybe Double)
quoteBidPriceL f Quote{..} = (\quoteBidPrice -> Quote { quoteBidPrice, ..} ) <$> f quoteBidPrice
{-# INLINE quoteBidPriceL #-}
quoteAskPriceL :: Lens_' Quote (Maybe Double)
quoteAskPriceL f Quote{..} = (\quoteAskPrice -> Quote { quoteAskPrice, ..} ) <$> f quoteAskPrice
{-# INLINE quoteAskPriceL #-}
quoteAskSizeL :: Lens_' Quote (Maybe Double)
quoteAskSizeL f Quote{..} = (\quoteAskSize -> Quote { quoteAskSize, ..} ) <$> f quoteAskSize
{-# INLINE quoteAskSizeL #-}
settlementTimestampL :: Lens_' Settlement (DateTime)
settlementTimestampL f Settlement{..} = (\settlementTimestamp -> Settlement { settlementTimestamp, ..} ) <$> f settlementTimestamp
{-# INLINE settlementTimestampL #-}
settlementSymbolL :: Lens_' Settlement (Text)
settlementSymbolL f Settlement{..} = (\settlementSymbol -> Settlement { settlementSymbol, ..} ) <$> f settlementSymbol
{-# INLINE settlementSymbolL #-}
settlementSettlementTypeL :: Lens_' Settlement (Maybe Text)
settlementSettlementTypeL f Settlement{..} = (\settlementSettlementType -> Settlement { settlementSettlementType, ..} ) <$> f settlementSettlementType
{-# INLINE settlementSettlementTypeL #-}
settlementSettledPriceL :: Lens_' Settlement (Maybe Double)
settlementSettledPriceL f Settlement{..} = (\settlementSettledPrice -> Settlement { settlementSettledPrice, ..} ) <$> f settlementSettledPrice
{-# INLINE settlementSettledPriceL #-}
settlementBankruptL :: Lens_' Settlement (Maybe Double)
settlementBankruptL f Settlement{..} = (\settlementBankrupt -> Settlement { settlementBankrupt, ..} ) <$> f settlementBankrupt
{-# INLINE settlementBankruptL #-}
settlementTaxBaseL :: Lens_' Settlement (Maybe Double)
settlementTaxBaseL f Settlement{..} = (\settlementTaxBase -> Settlement { settlementTaxBase, ..} ) <$> f settlementTaxBase
{-# INLINE settlementTaxBaseL #-}
settlementTaxRateL :: Lens_' Settlement (Maybe Double)
settlementTaxRateL f Settlement{..} = (\settlementTaxRate -> Settlement { settlementTaxRate, ..} ) <$> f settlementTaxRate
{-# INLINE settlementTaxRateL #-}
statsRootSymbolL :: Lens_' Stats (Text)
statsRootSymbolL f Stats{..} = (\statsRootSymbol -> Stats { statsRootSymbol, ..} ) <$> f statsRootSymbol
{-# INLINE statsRootSymbolL #-}
statsCurrencyL :: Lens_' Stats (Maybe Text)
statsCurrencyL f Stats{..} = (\statsCurrency -> Stats { statsCurrency, ..} ) <$> f statsCurrency
{-# INLINE statsCurrencyL #-}
statsVolume24hL :: Lens_' Stats (Maybe Double)
statsVolume24hL f Stats{..} = (\statsVolume24h -> Stats { statsVolume24h, ..} ) <$> f statsVolume24h
{-# INLINE statsVolume24hL #-}
statsTurnover24hL :: Lens_' Stats (Maybe Double)
statsTurnover24hL f Stats{..} = (\statsTurnover24h -> Stats { statsTurnover24h, ..} ) <$> f statsTurnover24h
{-# INLINE statsTurnover24hL #-}
statsOpenInterestL :: Lens_' Stats (Maybe Double)
statsOpenInterestL f Stats{..} = (\statsOpenInterest -> Stats { statsOpenInterest, ..} ) <$> f statsOpenInterest
{-# INLINE statsOpenInterestL #-}
statsOpenValueL :: Lens_' Stats (Maybe Double)
statsOpenValueL f Stats{..} = (\statsOpenValue -> Stats { statsOpenValue, ..} ) <$> f statsOpenValue
{-# INLINE statsOpenValueL #-}
statsHistoryDateL :: Lens_' StatsHistory (DateTime)
statsHistoryDateL f StatsHistory{..} = (\statsHistoryDate -> StatsHistory { statsHistoryDate, ..} ) <$> f statsHistoryDate
{-# INLINE statsHistoryDateL #-}
statsHistoryRootSymbolL :: Lens_' StatsHistory (Text)
statsHistoryRootSymbolL f StatsHistory{..} = (\statsHistoryRootSymbol -> StatsHistory { statsHistoryRootSymbol, ..} ) <$> f statsHistoryRootSymbol
{-# INLINE statsHistoryRootSymbolL #-}
statsHistoryCurrencyL :: Lens_' StatsHistory (Maybe Text)
statsHistoryCurrencyL f StatsHistory{..} = (\statsHistoryCurrency -> StatsHistory { statsHistoryCurrency, ..} ) <$> f statsHistoryCurrency
{-# INLINE statsHistoryCurrencyL #-}
statsHistoryVolumeL :: Lens_' StatsHistory (Maybe Double)
statsHistoryVolumeL f StatsHistory{..} = (\statsHistoryVolume -> StatsHistory { statsHistoryVolume, ..} ) <$> f statsHistoryVolume
{-# INLINE statsHistoryVolumeL #-}
statsHistoryTurnoverL :: Lens_' StatsHistory (Maybe Double)
statsHistoryTurnoverL f StatsHistory{..} = (\statsHistoryTurnover -> StatsHistory { statsHistoryTurnover, ..} ) <$> f statsHistoryTurnover
{-# INLINE statsHistoryTurnoverL #-}
statsUSDRootSymbolL :: Lens_' StatsUSD (Text)
statsUSDRootSymbolL f StatsUSD{..} = (\statsUSDRootSymbol -> StatsUSD { statsUSDRootSymbol, ..} ) <$> f statsUSDRootSymbol
{-# INLINE statsUSDRootSymbolL #-}
statsUSDCurrencyL :: Lens_' StatsUSD (Maybe Text)
statsUSDCurrencyL f StatsUSD{..} = (\statsUSDCurrency -> StatsUSD { statsUSDCurrency, ..} ) <$> f statsUSDCurrency
{-# INLINE statsUSDCurrencyL #-}
statsUSDTurnover24hL :: Lens_' StatsUSD (Maybe Double)
statsUSDTurnover24hL f StatsUSD{..} = (\statsUSDTurnover24h -> StatsUSD { statsUSDTurnover24h, ..} ) <$> f statsUSDTurnover24h
{-# INLINE statsUSDTurnover24hL #-}
statsUSDTurnover30dL :: Lens_' StatsUSD (Maybe Double)
statsUSDTurnover30dL f StatsUSD{..} = (\statsUSDTurnover30d -> StatsUSD { statsUSDTurnover30d, ..} ) <$> f statsUSDTurnover30d
{-# INLINE statsUSDTurnover30dL #-}
statsUSDTurnover365dL :: Lens_' StatsUSD (Maybe Double)
statsUSDTurnover365dL f StatsUSD{..} = (\statsUSDTurnover365d -> StatsUSD { statsUSDTurnover365d, ..} ) <$> f statsUSDTurnover365d
{-# INLINE statsUSDTurnover365dL #-}
statsUSDTurnoverL :: Lens_' StatsUSD (Maybe Double)
statsUSDTurnoverL f StatsUSD{..} = (\statsUSDTurnover -> StatsUSD { statsUSDTurnover, ..} ) <$> f statsUSDTurnover
{-# INLINE statsUSDTurnoverL #-}
tradeTimestampL :: Lens_' Trade (DateTime)
tradeTimestampL f Trade{..} = (\tradeTimestamp -> Trade { tradeTimestamp, ..} ) <$> f tradeTimestamp
{-# INLINE tradeTimestampL #-}
tradeSymbolL :: Lens_' Trade (Text)
tradeSymbolL f Trade{..} = (\tradeSymbol -> Trade { tradeSymbol, ..} ) <$> f tradeSymbol
{-# INLINE tradeSymbolL #-}
tradeSideL :: Lens_' Trade (Maybe Text)
tradeSideL f Trade{..} = (\tradeSide -> Trade { tradeSide, ..} ) <$> f tradeSide
{-# INLINE tradeSideL #-}
tradeSizeL :: Lens_' Trade (Maybe Double)
tradeSizeL f Trade{..} = (\tradeSize -> Trade { tradeSize, ..} ) <$> f tradeSize
{-# INLINE tradeSizeL #-}
tradePriceL :: Lens_' Trade (Maybe Double)
tradePriceL f Trade{..} = (\tradePrice -> Trade { tradePrice, ..} ) <$> f tradePrice
{-# INLINE tradePriceL #-}
tradeTickDirectionL :: Lens_' Trade (Maybe Text)
tradeTickDirectionL f Trade{..} = (\tradeTickDirection -> Trade { tradeTickDirection, ..} ) <$> f tradeTickDirection
{-# INLINE tradeTickDirectionL #-}
tradeTrdMatchIdL :: Lens_' Trade (Maybe Text)
tradeTrdMatchIdL f Trade{..} = (\tradeTrdMatchId -> Trade { tradeTrdMatchId, ..} ) <$> f tradeTrdMatchId
{-# INLINE tradeTrdMatchIdL #-}
tradeGrossValueL :: Lens_' Trade (Maybe Double)
tradeGrossValueL f Trade{..} = (\tradeGrossValue -> Trade { tradeGrossValue, ..} ) <$> f tradeGrossValue
{-# INLINE tradeGrossValueL #-}
tradeHomeNotionalL :: Lens_' Trade (Maybe Double)
tradeHomeNotionalL f Trade{..} = (\tradeHomeNotional -> Trade { tradeHomeNotional, ..} ) <$> f tradeHomeNotional
{-# INLINE tradeHomeNotionalL #-}
tradeForeignNotionalL :: Lens_' Trade (Maybe Double)
tradeForeignNotionalL f Trade{..} = (\tradeForeignNotional -> Trade { tradeForeignNotional, ..} ) <$> f tradeForeignNotional
{-# INLINE tradeForeignNotionalL #-}
tradeBinTimestampL :: Lens_' TradeBin (DateTime)
tradeBinTimestampL f TradeBin{..} = (\tradeBinTimestamp -> TradeBin { tradeBinTimestamp, ..} ) <$> f tradeBinTimestamp
{-# INLINE tradeBinTimestampL #-}
tradeBinSymbolL :: Lens_' TradeBin (Text)
tradeBinSymbolL f TradeBin{..} = (\tradeBinSymbol -> TradeBin { tradeBinSymbol, ..} ) <$> f tradeBinSymbol
{-# INLINE tradeBinSymbolL #-}
tradeBinOpenL :: Lens_' TradeBin (Maybe Double)
tradeBinOpenL f TradeBin{..} = (\tradeBinOpen -> TradeBin { tradeBinOpen, ..} ) <$> f tradeBinOpen
{-# INLINE tradeBinOpenL #-}
tradeBinHighL :: Lens_' TradeBin (Maybe Double)
tradeBinHighL f TradeBin{..} = (\tradeBinHigh -> TradeBin { tradeBinHigh, ..} ) <$> f tradeBinHigh
{-# INLINE tradeBinHighL #-}
tradeBinLowL :: Lens_' TradeBin (Maybe Double)
tradeBinLowL f TradeBin{..} = (\tradeBinLow -> TradeBin { tradeBinLow, ..} ) <$> f tradeBinLow
{-# INLINE tradeBinLowL #-}
tradeBinCloseL :: Lens_' TradeBin (Maybe Double)
tradeBinCloseL f TradeBin{..} = (\tradeBinClose -> TradeBin { tradeBinClose, ..} ) <$> f tradeBinClose
{-# INLINE tradeBinCloseL #-}
tradeBinTradesL :: Lens_' TradeBin (Maybe Double)
tradeBinTradesL f TradeBin{..} = (\tradeBinTrades -> TradeBin { tradeBinTrades, ..} ) <$> f tradeBinTrades
{-# INLINE tradeBinTradesL #-}
tradeBinVolumeL :: Lens_' TradeBin (Maybe Double)
tradeBinVolumeL f TradeBin{..} = (\tradeBinVolume -> TradeBin { tradeBinVolume, ..} ) <$> f tradeBinVolume
{-# INLINE tradeBinVolumeL #-}
tradeBinVwapL :: Lens_' TradeBin (Maybe Double)
tradeBinVwapL f TradeBin{..} = (\tradeBinVwap -> TradeBin { tradeBinVwap, ..} ) <$> f tradeBinVwap
{-# INLINE tradeBinVwapL #-}
tradeBinLastSizeL :: Lens_' TradeBin (Maybe Double)
tradeBinLastSizeL f TradeBin{..} = (\tradeBinLastSize -> TradeBin { tradeBinLastSize, ..} ) <$> f tradeBinLastSize
{-# INLINE tradeBinLastSizeL #-}
tradeBinTurnoverL :: Lens_' TradeBin (Maybe Double)
tradeBinTurnoverL f TradeBin{..} = (\tradeBinTurnover -> TradeBin { tradeBinTurnover, ..} ) <$> f tradeBinTurnover
{-# INLINE tradeBinTurnoverL #-}
tradeBinHomeNotionalL :: Lens_' TradeBin (Maybe Double)
tradeBinHomeNotionalL f TradeBin{..} = (\tradeBinHomeNotional -> TradeBin { tradeBinHomeNotional, ..} ) <$> f tradeBinHomeNotional
{-# INLINE tradeBinHomeNotionalL #-}
tradeBinForeignNotionalL :: Lens_' TradeBin (Maybe Double)
tradeBinForeignNotionalL f TradeBin{..} = (\tradeBinForeignNotional -> TradeBin { tradeBinForeignNotional, ..} ) <$> f tradeBinForeignNotional
{-# INLINE tradeBinForeignNotionalL #-}
transactionTransactIdL :: Lens_' Transaction (Text)
transactionTransactIdL f Transaction{..} = (\transactionTransactId -> Transaction { transactionTransactId, ..} ) <$> f transactionTransactId
{-# INLINE transactionTransactIdL #-}
transactionAccountL :: Lens_' Transaction (Maybe Double)
transactionAccountL f Transaction{..} = (\transactionAccount -> Transaction { transactionAccount, ..} ) <$> f transactionAccount
{-# INLINE transactionAccountL #-}
transactionCurrencyL :: Lens_' Transaction (Maybe Text)
transactionCurrencyL f Transaction{..} = (\transactionCurrency -> Transaction { transactionCurrency, ..} ) <$> f transactionCurrency
{-# INLINE transactionCurrencyL #-}
transactionTransactTypeL :: Lens_' Transaction (Maybe Text)
transactionTransactTypeL f Transaction{..} = (\transactionTransactType -> Transaction { transactionTransactType, ..} ) <$> f transactionTransactType
{-# INLINE transactionTransactTypeL #-}
transactionAmountL :: Lens_' Transaction (Maybe Double)
transactionAmountL f Transaction{..} = (\transactionAmount -> Transaction { transactionAmount, ..} ) <$> f transactionAmount
{-# INLINE transactionAmountL #-}
transactionFeeL :: Lens_' Transaction (Maybe Double)
transactionFeeL f Transaction{..} = (\transactionFee -> Transaction { transactionFee, ..} ) <$> f transactionFee
{-# INLINE transactionFeeL #-}
transactionTransactStatusL :: Lens_' Transaction (Maybe Text)
transactionTransactStatusL f Transaction{..} = (\transactionTransactStatus -> Transaction { transactionTransactStatus, ..} ) <$> f transactionTransactStatus
{-# INLINE transactionTransactStatusL #-}
transactionAddressL :: Lens_' Transaction (Maybe Text)
transactionAddressL f Transaction{..} = (\transactionAddress -> Transaction { transactionAddress, ..} ) <$> f transactionAddress
{-# INLINE transactionAddressL #-}
transactionTxL :: Lens_' Transaction (Maybe Text)
transactionTxL f Transaction{..} = (\transactionTx -> Transaction { transactionTx, ..} ) <$> f transactionTx
{-# INLINE transactionTxL #-}
transactionTextL :: Lens_' Transaction (Maybe Text)
transactionTextL f Transaction{..} = (\transactionText -> Transaction { transactionText, ..} ) <$> f transactionText
{-# INLINE transactionTextL #-}
transactionTransactTimeL :: Lens_' Transaction (Maybe DateTime)
transactionTransactTimeL f Transaction{..} = (\transactionTransactTime -> Transaction { transactionTransactTime, ..} ) <$> f transactionTransactTime
{-# INLINE transactionTransactTimeL #-}
transactionTimestampL :: Lens_' Transaction (Maybe DateTime)
transactionTimestampL f Transaction{..} = (\transactionTimestamp -> Transaction { transactionTimestamp, ..} ) <$> f transactionTimestamp
{-# INLINE transactionTimestampL #-}
userIdL :: Lens_' User (Maybe Double)
userIdL f User{..} = (\userId -> User { userId, ..} ) <$> f userId
{-# INLINE userIdL #-}
userOwnerIdL :: Lens_' User (Maybe Double)
userOwnerIdL f User{..} = (\userOwnerId -> User { userOwnerId, ..} ) <$> f userOwnerId
{-# INLINE userOwnerIdL #-}
userFirstnameL :: Lens_' User (Maybe Text)
userFirstnameL f User{..} = (\userFirstname -> User { userFirstname, ..} ) <$> f userFirstname
{-# INLINE userFirstnameL #-}
userLastnameL :: Lens_' User (Maybe Text)
userLastnameL f User{..} = (\userLastname -> User { userLastname, ..} ) <$> f userLastname
{-# INLINE userLastnameL #-}
userUsernameL :: Lens_' User (Text)
userUsernameL f User{..} = (\userUsername -> User { userUsername, ..} ) <$> f userUsername
{-# INLINE userUsernameL #-}
userEmailL :: Lens_' User (Text)
userEmailL f User{..} = (\userEmail -> User { userEmail, ..} ) <$> f userEmail
{-# INLINE userEmailL #-}
userPhoneL :: Lens_' User (Maybe Text)
userPhoneL f User{..} = (\userPhone -> User { userPhone, ..} ) <$> f userPhone
{-# INLINE userPhoneL #-}
userCreatedL :: Lens_' User (Maybe DateTime)
userCreatedL f User{..} = (\userCreated -> User { userCreated, ..} ) <$> f userCreated
{-# INLINE userCreatedL #-}
userLastUpdatedL :: Lens_' User (Maybe DateTime)
userLastUpdatedL f User{..} = (\userLastUpdated -> User { userLastUpdated, ..} ) <$> f userLastUpdated
{-# INLINE userLastUpdatedL #-}
userPreferencesL :: Lens_' User (Maybe UserPreferences)
userPreferencesL f User{..} = (\userPreferences -> User { userPreferences, ..} ) <$> f userPreferences
{-# INLINE userPreferencesL #-}
userTfaEnabledL :: Lens_' User (Maybe Text)
userTfaEnabledL f User{..} = (\userTfaEnabled -> User { userTfaEnabled, ..} ) <$> f userTfaEnabled
{-# INLINE userTfaEnabledL #-}
userAffiliateIdL :: Lens_' User (Maybe Text)
userAffiliateIdL f User{..} = (\userAffiliateId -> User { userAffiliateId, ..} ) <$> f userAffiliateId
{-# INLINE userAffiliateIdL #-}
userPgpPubKeyL :: Lens_' User (Maybe Text)
userPgpPubKeyL f User{..} = (\userPgpPubKey -> User { userPgpPubKey, ..} ) <$> f userPgpPubKey
{-# INLINE userPgpPubKeyL #-}
userCountryL :: Lens_' User (Maybe Text)
userCountryL f User{..} = (\userCountry -> User { userCountry, ..} ) <$> f userCountry
{-# INLINE userCountryL #-}
userCommissionMakerFeeL :: Lens_' UserCommission (Maybe Double)
userCommissionMakerFeeL f UserCommission{..} = (\userCommissionMakerFee -> UserCommission { userCommissionMakerFee, ..} ) <$> f userCommissionMakerFee
{-# INLINE userCommissionMakerFeeL #-}
userCommissionTakerFeeL :: Lens_' UserCommission (Maybe Double)
userCommissionTakerFeeL f UserCommission{..} = (\userCommissionTakerFee -> UserCommission { userCommissionTakerFee, ..} ) <$> f userCommissionTakerFee
{-# INLINE userCommissionTakerFeeL #-}
userCommissionSettlementFeeL :: Lens_' UserCommission (Maybe Double)
userCommissionSettlementFeeL f UserCommission{..} = (\userCommissionSettlementFee -> UserCommission { userCommissionSettlementFee, ..} ) <$> f userCommissionSettlementFee
{-# INLINE userCommissionSettlementFeeL #-}
userCommissionMaxFeeL :: Lens_' UserCommission (Maybe Double)
userCommissionMaxFeeL f UserCommission{..} = (\userCommissionMaxFee -> UserCommission { userCommissionMaxFee, ..} ) <$> f userCommissionMaxFee
{-# INLINE userCommissionMaxFeeL #-}
userPreferencesAlertOnLiquidationsL :: Lens_' UserPreferences (Maybe Bool)
userPreferencesAlertOnLiquidationsL f UserPreferences{..} = (\userPreferencesAlertOnLiquidations -> UserPreferences { userPreferencesAlertOnLiquidations, ..} ) <$> f userPreferencesAlertOnLiquidations
{-# INLINE userPreferencesAlertOnLiquidationsL #-}
userPreferencesAnimationsEnabledL :: Lens_' UserPreferences (Maybe Bool)
userPreferencesAnimationsEnabledL f UserPreferences{..} = (\userPreferencesAnimationsEnabled -> UserPreferences { userPreferencesAnimationsEnabled, ..} ) <$> f userPreferencesAnimationsEnabled
{-# INLINE userPreferencesAnimationsEnabledL #-}
userPreferencesAnnouncementsLastSeenL :: Lens_' UserPreferences (Maybe DateTime)
userPreferencesAnnouncementsLastSeenL f UserPreferences{..} = (\userPreferencesAnnouncementsLastSeen -> UserPreferences { userPreferencesAnnouncementsLastSeen, ..} ) <$> f userPreferencesAnnouncementsLastSeen
{-# INLINE userPreferencesAnnouncementsLastSeenL #-}
userPreferencesChatChannelIdL :: Lens_' UserPreferences (Maybe Double)
userPreferencesChatChannelIdL f UserPreferences{..} = (\userPreferencesChatChannelId -> UserPreferences { userPreferencesChatChannelId, ..} ) <$> f userPreferencesChatChannelId
{-# INLINE userPreferencesChatChannelIdL #-}
userPreferencesColorThemeL :: Lens_' UserPreferences (Maybe Text)
userPreferencesColorThemeL f UserPreferences{..} = (\userPreferencesColorTheme -> UserPreferences { userPreferencesColorTheme, ..} ) <$> f userPreferencesColorTheme
{-# INLINE userPreferencesColorThemeL #-}
userPreferencesCurrencyL :: Lens_' UserPreferences (Maybe Text)
userPreferencesCurrencyL f UserPreferences{..} = (\userPreferencesCurrency -> UserPreferences { userPreferencesCurrency, ..} ) <$> f userPreferencesCurrency
{-# INLINE userPreferencesCurrencyL #-}
userPreferencesDebugL :: Lens_' UserPreferences (Maybe Bool)
userPreferencesDebugL f UserPreferences{..} = (\userPreferencesDebug -> UserPreferences { userPreferencesDebug, ..} ) <$> f userPreferencesDebug
{-# INLINE userPreferencesDebugL #-}
userPreferencesDisableEmailsL :: Lens_' UserPreferences (Maybe [Text])
userPreferencesDisableEmailsL f UserPreferences{..} = (\userPreferencesDisableEmails -> UserPreferences { userPreferencesDisableEmails, ..} ) <$> f userPreferencesDisableEmails
{-# INLINE userPreferencesDisableEmailsL #-}
userPreferencesHideConfirmDialogsL :: Lens_' UserPreferences (Maybe [Text])
userPreferencesHideConfirmDialogsL f UserPreferences{..} = (\userPreferencesHideConfirmDialogs -> UserPreferences { userPreferencesHideConfirmDialogs, ..} ) <$> f userPreferencesHideConfirmDialogs
{-# INLINE userPreferencesHideConfirmDialogsL #-}
userPreferencesHideConnectionModalL :: Lens_' UserPreferences (Maybe Bool)
userPreferencesHideConnectionModalL f UserPreferences{..} = (\userPreferencesHideConnectionModal -> UserPreferences { userPreferencesHideConnectionModal, ..} ) <$> f userPreferencesHideConnectionModal
{-# INLINE userPreferencesHideConnectionModalL #-}
userPreferencesHideFromLeaderboardL :: Lens_' UserPreferences (Maybe Bool)
userPreferencesHideFromLeaderboardL f UserPreferences{..} = (\userPreferencesHideFromLeaderboard -> UserPreferences { userPreferencesHideFromLeaderboard, ..} ) <$> f userPreferencesHideFromLeaderboard
{-# INLINE userPreferencesHideFromLeaderboardL #-}
userPreferencesHideNameFromLeaderboardL :: Lens_' UserPreferences (Maybe Bool)
userPreferencesHideNameFromLeaderboardL f UserPreferences{..} = (\userPreferencesHideNameFromLeaderboard -> UserPreferences { userPreferencesHideNameFromLeaderboard, ..} ) <$> f userPreferencesHideNameFromLeaderboard
{-# INLINE userPreferencesHideNameFromLeaderboardL #-}
userPreferencesHideNotificationsL :: Lens_' UserPreferences (Maybe [Text])
userPreferencesHideNotificationsL f UserPreferences{..} = (\userPreferencesHideNotifications -> UserPreferences { userPreferencesHideNotifications, ..} ) <$> f userPreferencesHideNotifications
{-# INLINE userPreferencesHideNotificationsL #-}
userPreferencesLocaleL :: Lens_' UserPreferences (Maybe Text)
userPreferencesLocaleL f UserPreferences{..} = (\userPreferencesLocale -> UserPreferences { userPreferencesLocale, ..} ) <$> f userPreferencesLocale
{-# INLINE userPreferencesLocaleL #-}
userPreferencesMsgsSeenL :: Lens_' UserPreferences (Maybe [Text])
userPreferencesMsgsSeenL f UserPreferences{..} = (\userPreferencesMsgsSeen -> UserPreferences { userPreferencesMsgsSeen, ..} ) <$> f userPreferencesMsgsSeen
{-# INLINE userPreferencesMsgsSeenL #-}
userPreferencesOrderBookBinningL :: Lens_' UserPreferences (Maybe A.Value)
userPreferencesOrderBookBinningL f UserPreferences{..} = (\userPreferencesOrderBookBinning -> UserPreferences { userPreferencesOrderBookBinning, ..} ) <$> f userPreferencesOrderBookBinning
{-# INLINE userPreferencesOrderBookBinningL #-}
userPreferencesOrderBookTypeL :: Lens_' UserPreferences (Maybe Text)
userPreferencesOrderBookTypeL f UserPreferences{..} = (\userPreferencesOrderBookType -> UserPreferences { userPreferencesOrderBookType, ..} ) <$> f userPreferencesOrderBookType
{-# INLINE userPreferencesOrderBookTypeL #-}
userPreferencesOrderClearImmediateL :: Lens_' UserPreferences (Maybe Bool)
userPreferencesOrderClearImmediateL f UserPreferences{..} = (\userPreferencesOrderClearImmediate -> UserPreferences { userPreferencesOrderClearImmediate, ..} ) <$> f userPreferencesOrderClearImmediate
{-# INLINE userPreferencesOrderClearImmediateL #-}
userPreferencesOrderControlsPlusMinusL :: Lens_' UserPreferences (Maybe Bool)
userPreferencesOrderControlsPlusMinusL f UserPreferences{..} = (\userPreferencesOrderControlsPlusMinus -> UserPreferences { userPreferencesOrderControlsPlusMinus, ..} ) <$> f userPreferencesOrderControlsPlusMinus
{-# INLINE userPreferencesOrderControlsPlusMinusL #-}
userPreferencesSoundsL :: Lens_' UserPreferences (Maybe [Text])
userPreferencesSoundsL f UserPreferences{..} = (\userPreferencesSounds -> UserPreferences { userPreferencesSounds, ..} ) <$> f userPreferencesSounds
{-# INLINE userPreferencesSoundsL #-}
userPreferencesStrictIpCheckL :: Lens_' UserPreferences (Maybe Bool)
userPreferencesStrictIpCheckL f UserPreferences{..} = (\userPreferencesStrictIpCheck -> UserPreferences { userPreferencesStrictIpCheck, ..} ) <$> f userPreferencesStrictIpCheck
{-# INLINE userPreferencesStrictIpCheckL #-}
userPreferencesStrictTimeoutL :: Lens_' UserPreferences (Maybe Bool)
userPreferencesStrictTimeoutL f UserPreferences{..} = (\userPreferencesStrictTimeout -> UserPreferences { userPreferencesStrictTimeout, ..} ) <$> f userPreferencesStrictTimeout
{-# INLINE userPreferencesStrictTimeoutL #-}
userPreferencesTickerGroupL :: Lens_' UserPreferences (Maybe Text)
userPreferencesTickerGroupL f UserPreferences{..} = (\userPreferencesTickerGroup -> UserPreferences { userPreferencesTickerGroup, ..} ) <$> f userPreferencesTickerGroup
{-# INLINE userPreferencesTickerGroupL #-}
userPreferencesTickerPinnedL :: Lens_' UserPreferences (Maybe Bool)
userPreferencesTickerPinnedL f UserPreferences{..} = (\userPreferencesTickerPinned -> UserPreferences { userPreferencesTickerPinned, ..} ) <$> f userPreferencesTickerPinned
{-# INLINE userPreferencesTickerPinnedL #-}
userPreferencesTradeLayoutL :: Lens_' UserPreferences (Maybe Text)
userPreferencesTradeLayoutL f UserPreferences{..} = (\userPreferencesTradeLayout -> UserPreferences { userPreferencesTradeLayout, ..} ) <$> f userPreferencesTradeLayout
{-# INLINE userPreferencesTradeLayoutL #-}
walletAccountL :: Lens_' Wallet (Double)
walletAccountL f Wallet{..} = (\walletAccount -> Wallet { walletAccount, ..} ) <$> f walletAccount
{-# INLINE walletAccountL #-}
walletCurrencyL :: Lens_' Wallet (Text)
walletCurrencyL f Wallet{..} = (\walletCurrency -> Wallet { walletCurrency, ..} ) <$> f walletCurrency
{-# INLINE walletCurrencyL #-}
walletPrevDepositedL :: Lens_' Wallet (Maybe Double)
walletPrevDepositedL f Wallet{..} = (\walletPrevDeposited -> Wallet { walletPrevDeposited, ..} ) <$> f walletPrevDeposited
{-# INLINE walletPrevDepositedL #-}
walletPrevWithdrawnL :: Lens_' Wallet (Maybe Double)
walletPrevWithdrawnL f Wallet{..} = (\walletPrevWithdrawn -> Wallet { walletPrevWithdrawn, ..} ) <$> f walletPrevWithdrawn
{-# INLINE walletPrevWithdrawnL #-}
walletPrevTransferInL :: Lens_' Wallet (Maybe Double)
walletPrevTransferInL f Wallet{..} = (\walletPrevTransferIn -> Wallet { walletPrevTransferIn, ..} ) <$> f walletPrevTransferIn
{-# INLINE walletPrevTransferInL #-}
walletPrevTransferOutL :: Lens_' Wallet (Maybe Double)
walletPrevTransferOutL f Wallet{..} = (\walletPrevTransferOut -> Wallet { walletPrevTransferOut, ..} ) <$> f walletPrevTransferOut
{-# INLINE walletPrevTransferOutL #-}
walletPrevAmountL :: Lens_' Wallet (Maybe Double)
walletPrevAmountL f Wallet{..} = (\walletPrevAmount -> Wallet { walletPrevAmount, ..} ) <$> f walletPrevAmount
{-# INLINE walletPrevAmountL #-}
walletPrevTimestampL :: Lens_' Wallet (Maybe DateTime)
walletPrevTimestampL f Wallet{..} = (\walletPrevTimestamp -> Wallet { walletPrevTimestamp, ..} ) <$> f walletPrevTimestamp
{-# INLINE walletPrevTimestampL #-}
walletDeltaDepositedL :: Lens_' Wallet (Maybe Double)
walletDeltaDepositedL f Wallet{..} = (\walletDeltaDeposited -> Wallet { walletDeltaDeposited, ..} ) <$> f walletDeltaDeposited
{-# INLINE walletDeltaDepositedL #-}
walletDeltaWithdrawnL :: Lens_' Wallet (Maybe Double)
walletDeltaWithdrawnL f Wallet{..} = (\walletDeltaWithdrawn -> Wallet { walletDeltaWithdrawn, ..} ) <$> f walletDeltaWithdrawn
{-# INLINE walletDeltaWithdrawnL #-}
walletDeltaTransferInL :: Lens_' Wallet (Maybe Double)
walletDeltaTransferInL f Wallet{..} = (\walletDeltaTransferIn -> Wallet { walletDeltaTransferIn, ..} ) <$> f walletDeltaTransferIn
{-# INLINE walletDeltaTransferInL #-}
walletDeltaTransferOutL :: Lens_' Wallet (Maybe Double)
walletDeltaTransferOutL f Wallet{..} = (\walletDeltaTransferOut -> Wallet { walletDeltaTransferOut, ..} ) <$> f walletDeltaTransferOut
{-# INLINE walletDeltaTransferOutL #-}
walletDeltaAmountL :: Lens_' Wallet (Maybe Double)
walletDeltaAmountL f Wallet{..} = (\walletDeltaAmount -> Wallet { walletDeltaAmount, ..} ) <$> f walletDeltaAmount
{-# INLINE walletDeltaAmountL #-}
walletDepositedL :: Lens_' Wallet (Maybe Double)
walletDepositedL f Wallet{..} = (\walletDeposited -> Wallet { walletDeposited, ..} ) <$> f walletDeposited
{-# INLINE walletDepositedL #-}
walletWithdrawnL :: Lens_' Wallet (Maybe Double)
walletWithdrawnL f Wallet{..} = (\walletWithdrawn -> Wallet { walletWithdrawn, ..} ) <$> f walletWithdrawn
{-# INLINE walletWithdrawnL #-}
walletTransferInL :: Lens_' Wallet (Maybe Double)
walletTransferInL f Wallet{..} = (\walletTransferIn -> Wallet { walletTransferIn, ..} ) <$> f walletTransferIn
{-# INLINE walletTransferInL #-}
walletTransferOutL :: Lens_' Wallet (Maybe Double)
walletTransferOutL f Wallet{..} = (\walletTransferOut -> Wallet { walletTransferOut, ..} ) <$> f walletTransferOut
{-# INLINE walletTransferOutL #-}
walletAmountL :: Lens_' Wallet (Maybe Double)
walletAmountL f Wallet{..} = (\walletAmount -> Wallet { walletAmount, ..} ) <$> f walletAmount
{-# INLINE walletAmountL #-}
walletPendingCreditL :: Lens_' Wallet (Maybe Double)
walletPendingCreditL f Wallet{..} = (\walletPendingCredit -> Wallet { walletPendingCredit, ..} ) <$> f walletPendingCredit
{-# INLINE walletPendingCreditL #-}
walletPendingDebitL :: Lens_' Wallet (Maybe Double)
walletPendingDebitL f Wallet{..} = (\walletPendingDebit -> Wallet { walletPendingDebit, ..} ) <$> f walletPendingDebit
{-# INLINE walletPendingDebitL #-}
walletConfirmedDebitL :: Lens_' Wallet (Maybe Double)
walletConfirmedDebitL f Wallet{..} = (\walletConfirmedDebit -> Wallet { walletConfirmedDebit, ..} ) <$> f walletConfirmedDebit
{-# INLINE walletConfirmedDebitL #-}
walletTimestampL :: Lens_' Wallet (Maybe DateTime)
walletTimestampL f Wallet{..} = (\walletTimestamp -> Wallet { walletTimestamp, ..} ) <$> f walletTimestamp
{-# INLINE walletTimestampL #-}
walletAddrL :: Lens_' Wallet (Maybe Text)
walletAddrL f Wallet{..} = (\walletAddr -> Wallet { walletAddr, ..} ) <$> f walletAddr
{-# INLINE walletAddrL #-}
walletScriptL :: Lens_' Wallet (Maybe Text)
walletScriptL f Wallet{..} = (\walletScript -> Wallet { walletScript, ..} ) <$> f walletScript
{-# INLINE walletScriptL #-}
walletWithdrawalLockL :: Lens_' Wallet (Maybe [Text])
walletWithdrawalLockL f Wallet{..} = (\walletWithdrawalLock -> Wallet { walletWithdrawalLock, ..} ) <$> f walletWithdrawalLock
{-# INLINE walletWithdrawalLockL #-}