bittrex-0.1.0.0: API bindings to bittrex.com

Safe HaskellNone
LanguageHaskell2010

Bittrex.Types

Synopsis

Documentation

data APIOpts Source #

Constructors

APIOpts 

data BittrexError Source #

Instances

Eq BittrexError Source # 
Show BittrexError Source # 
Generic BittrexError Source # 

Associated Types

type Rep BittrexError :: * -> * #

FromJSON BittrexError Source # 
type Rep BittrexError Source # 
type Rep BittrexError = D1 * (MetaData "BittrexError" "Bittrex.Types" "bittrex-0.1.0.0-Imf5uyvwOtK7c1DCdkyHS1" False) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "INVALID_MARKET" PrefixI False) (U1 *)) (C1 * (MetaCons "MARKET_NOT_PROVIDED" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "APIKEY_NOT_PROVIDED" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "APIKEY_INVALID" PrefixI False) (U1 *)) (C1 * (MetaCons "INVALID_SIGNATURE" PrefixI False) (U1 *))))) ((:+:) * ((:+:) * (C1 * (MetaCons "NONCE_NOT_PROVIDED" PrefixI False) (U1 *)) (C1 * (MetaCons "INVALID_PERMISSION" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "INVALID_CURRENCY" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "WITHDRAWAL_TOO_SMALL" PrefixI False) (U1 *)) (C1 * (MetaCons "CURRENCY_DOES_NOT_EXIST" PrefixI False) (U1 *))))))

data Ticker Source #

Constructors

Ticker 

Fields

data APIKeys Source #

API Keys

Constructors

APIKeys 

Fields

data WithdrawalHistory Source #

Instances

Eq WithdrawalHistory Source # 
Show WithdrawalHistory Source # 
Generic WithdrawalHistory Source # 
FromJSON WithdrawalHistory Source # 
type Rep WithdrawalHistory Source # 
type Rep WithdrawalHistory = D1 * (MetaData "WithdrawalHistory" "Bittrex.Types" "bittrex-0.1.0.0-Imf5uyvwOtK7c1DCdkyHS1" False) (C1 * (MetaCons "WithdrawalHistory" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "whPaymentUuid") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)) (S1 * (MetaSel (Just Symbol "whCurrency") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "whAmount") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Scientific)) ((:*:) * (S1 * (MetaSel (Just Symbol "whAddress") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)) (S1 * (MetaSel (Just Symbol "whOpened") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "whAuthorized") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool)) ((:*:) * (S1 * (MetaSel (Just Symbol "whPendingPayment") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool)) (S1 * (MetaSel (Just Symbol "whTxCost") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Scientific)))) ((:*:) * (S1 * (MetaSel (Just Symbol "whTxId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)) ((:*:) * (S1 * (MetaSel (Just Symbol "whCanceled") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool)) (S1 * (MetaSel (Just Symbol "whInvalidAddress") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool)))))))

data DepositHistory Source #

Instances

Eq DepositHistory Source # 
Show DepositHistory Source # 
Generic DepositHistory Source # 

Associated Types

type Rep DepositHistory :: * -> * #

FromJSON DepositHistory Source # 
type Rep DepositHistory Source # 

newtype UUID Source #

Constructors

UUID Text 

Instances

data Balance Source #

data OrderType Source #

Constructors

SELL 
BUY 
LIMIT_SELL 
LIMIT_BUY 

Instances

Eq OrderType Source # 
Show OrderType Source # 
Generic OrderType Source # 

Associated Types

type Rep OrderType :: * -> * #

FromJSON OrderType Source # 
type Rep OrderType Source # 
type Rep OrderType = D1 * (MetaData "OrderType" "Bittrex.Types" "bittrex-0.1.0.0-Imf5uyvwOtK7c1DCdkyHS1" False) ((:+:) * ((:+:) * (C1 * (MetaCons "SELL" PrefixI False) (U1 *)) (C1 * (MetaCons "BUY" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "LIMIT_SELL" PrefixI False) (U1 *)) (C1 * (MetaCons "LIMIT_BUY" PrefixI False) (U1 *))))

data OpenOrder Source #

Instances

Eq OpenOrder Source # 
Show OpenOrder Source # 
Generic OpenOrder Source # 

Associated Types

type Rep OpenOrder :: * -> * #

FromJSON OpenOrder Source # 
type Rep OpenOrder Source # 
type Rep OpenOrder = D1 * (MetaData "OpenOrder" "Bittrex.Types" "bittrex-0.1.0.0-Imf5uyvwOtK7c1DCdkyHS1" False) (C1 * (MetaCons "OpenOrder" PrefixI True) ((:*:) * ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "ooUuid") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "ooOrderUuid") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "ooExchange") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)) (S1 * (MetaSel (Just Symbol "ooOrderType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * OrderType)))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "ooQuantity") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Scientific)) (S1 * (MetaSel (Just Symbol "ooQuantityRemaining") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Scientific))) ((:*:) * (S1 * (MetaSel (Just Symbol "ooLimit") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Scientific)) (S1 * (MetaSel (Just Symbol "ooCommissionPaid") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Scientific))))) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "ooPrice") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Scientific)) (S1 * (MetaSel (Just Symbol "ooPricePerUnit") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Scientific)))) ((:*:) * (S1 * (MetaSel (Just Symbol "ooOpened") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)) (S1 * (MetaSel (Just Symbol "ooClosed") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Text))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "ooCancelInitiated") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool)) (S1 * (MetaSel (Just Symbol "ooImmediateOrCancel") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool))) ((:*:) * (S1 * (MetaSel (Just Symbol "ooIsConditional") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool)) ((:*:) * (S1 * (MetaSel (Just Symbol "ooCondition") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "ooConditionTarget") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Text)))))))))

data OrderHistory Source #

Instances

Eq OrderHistory Source # 
Show OrderHistory Source # 
Generic OrderHistory Source # 

Associated Types

type Rep OrderHistory :: * -> * #

FromJSON OrderHistory Source # 
type Rep OrderHistory Source # 
type Rep OrderHistory = D1 * (MetaData "OrderHistory" "Bittrex.Types" "bittrex-0.1.0.0-Imf5uyvwOtK7c1DCdkyHS1" False) (C1 * (MetaCons "OrderHistory" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "ohOrderUuid") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)) ((:*:) * (S1 * (MetaSel (Just Symbol "ohExchange") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)) (S1 * (MetaSel (Just Symbol "ohTimeStamp") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)))) ((:*:) * (S1 * (MetaSel (Just Symbol "ohOrderType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * OrderType)) ((:*:) * (S1 * (MetaSel (Just Symbol "ohLimit") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Scientific)) (S1 * (MetaSel (Just Symbol "ohQuantity") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Scientific))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "ohQuantityRemaining") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Scientific)) ((:*:) * (S1 * (MetaSel (Just Symbol "ohCommission") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Scientific)) (S1 * (MetaSel (Just Symbol "ohPrice") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Scientific)))) ((:*:) * (S1 * (MetaSel (Just Symbol "ohPricePerUnit") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Scientific))) ((:*:) * (S1 * (MetaSel (Just Symbol "ohIsConditional") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool)) (S1 * (MetaSel (Just Symbol "ohImmediateOrCancel") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool)))))))

data Order Source #

Instances

Eq Order Source # 

Methods

(==) :: Order -> Order -> Bool #

(/=) :: Order -> Order -> Bool #

Show Order Source # 

Methods

showsPrec :: Int -> Order -> ShowS #

show :: Order -> String #

showList :: [Order] -> ShowS #

Generic Order Source # 

Associated Types

type Rep Order :: * -> * #

Methods

from :: Order -> Rep Order x #

to :: Rep Order x -> Order #

FromJSON Order Source # 
type Rep Order Source # 
type Rep Order = D1 * (MetaData "Order" "Bittrex.Types" "bittrex-0.1.0.0-Imf5uyvwOtK7c1DCdkyHS1" False) (C1 * (MetaCons "Order" PrefixI True) ((:*:) * ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "oAccountId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "oOrderUuid") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "oExchange") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)) ((:*:) * (S1 * (MetaSel (Just Symbol "oOrderType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * OrderType)) (S1 * (MetaSel (Just Symbol "oQuantity") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Scientific))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "oQuantityRemaining") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Scientific)) ((:*:) * (S1 * (MetaSel (Just Symbol "oLimit") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Scientific)) (S1 * (MetaSel (Just Symbol "oReserved") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Scientific)))) ((:*:) * (S1 * (MetaSel (Just Symbol "oReservedRemaining") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Scientific)) ((:*:) * (S1 * (MetaSel (Just Symbol "oCommissionReserved") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Scientific)) (S1 * (MetaSel (Just Symbol "oCommissionReserveRemaining") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Scientific)))))) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "oCommissionPaid") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Scientific)) ((:*:) * (S1 * (MetaSel (Just Symbol "oPrice") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Scientific)) (S1 * (MetaSel (Just Symbol "oPricePerUnit") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Scientific))))) ((:*:) * (S1 * (MetaSel (Just Symbol "oOpen") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)) ((:*:) * (S1 * (MetaSel (Just Symbol "oIsOpen") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool)) (S1 * (MetaSel (Just Symbol "oSentinal") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "oTimeStamp") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)) ((:*:) * (S1 * (MetaSel (Just Symbol "oCommission") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Scientific)) (S1 * (MetaSel (Just Symbol "oIsConditional") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool)))) ((:*:) * (S1 * (MetaSel (Just Symbol "oImmediateOrCancel") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool)) ((:*:) * (S1 * (MetaSel (Just Symbol "oCancelInitiated") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool)) (S1 * (MetaSel (Just Symbol "oCondition") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text))))))))