bitx-bitcoin-0.10.0.0: A Haskell library for working with the BitX bitcoin exchange.

Copyright2016 Tebello Thejane
LicenseBSD3
MaintainerTebello Thejane <zyxoas+hackage@gmail.com>
StabilityExperimental
Portabilitynon-portable (GHC Extensions)
Safe HaskellNone
LanguageHaskell2010

Network.Bitcoin.BitX.Types

Description

The types used for the various BitX API calls.

Synopsis

Documentation

data Ticker Source #

The state of a single market, identified by the currency pair. As usual, the ask/sell price is the price of the last filled ask order, and the bid/buy price is the price of the last filled bid order. Necessarily bid <= ask.

data CcyPair Source #

A currency pair

Constructors

XBTZAR

Bitcoin vs. ZAR

XBTNAD

Bitcoin vs. Namibian Dollar

ZARXBT

ZAR vs. Namibian Dollar

NADXBT

Namibian Dollar vs. Bitcoin

XBTKES

Bitcoin vs. Kenyan Shilling

KESXBT

Kenyan Shilling vs Bitcoin

XBTMYR

Bitcoin vs. Malaysian Ringgit

MYRXBT

Malaysian Ringgit vs. Bitcoin

XBTNGN

Bitcoin vs. Nigerian Naira

NGNXBT

Nigerian Naira vs. Bitcoin

XBTIDR

Bitcoin vs. Indonesian Rupiah

IDRXBT

Indonesian Rupiah vs. Bitcoin

XBTSGD

Bitcoin vs. Singapore Dollar

SGDXBT

Singapore Dollar vs. Bitcoin

Instances

Eq CcyPair Source # 

Methods

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

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

Show CcyPair Source # 
Generic CcyPair Source # 

Associated Types

type Rep CcyPair :: * -> * #

Methods

from :: CcyPair -> Rep CcyPair x #

to :: Rep CcyPair x -> CcyPair #

FromJSON CcyPair Source # 
HasPair Ticker CcyPair Source # 

Methods

pair :: Lens' Ticker CcyPair Source #

HasPair PrivateOrder CcyPair Source # 

Methods

pair :: Lens' PrivateOrder CcyPair Source #

HasPair PrivateOrderWithTrades CcyPair Source # 
HasPair OrderRequest CcyPair Source # 

Methods

pair :: Lens' OrderRequest CcyPair Source #

HasPair MarketOrderRequest CcyPair Source # 
HasPair QuoteRequest CcyPair Source # 

Methods

pair :: Lens' QuoteRequest CcyPair Source #

HasPair OrderQuote CcyPair Source # 

Methods

pair :: Lens' OrderQuote CcyPair Source #

type Rep CcyPair Source # 
type Rep CcyPair = D1 (MetaData "CcyPair" "Network.Bitcoin.BitX.Types" "bitx-bitcoin-0.10.0.0-9BaETuWGwGzIwPqYsLZU89" False) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "XBTZAR" PrefixI False) U1) ((:+:) (C1 (MetaCons "XBTNAD" PrefixI False) U1) (C1 (MetaCons "ZARXBT" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "NADXBT" PrefixI False) U1) (C1 (MetaCons "XBTKES" PrefixI False) U1)) ((:+:) (C1 (MetaCons "KESXBT" PrefixI False) U1) (C1 (MetaCons "XBTMYR" PrefixI False) U1)))) ((:+:) ((:+:) (C1 (MetaCons "MYRXBT" PrefixI False) U1) ((:+:) (C1 (MetaCons "XBTNGN" PrefixI False) U1) (C1 (MetaCons "NGNXBT" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "XBTIDR" PrefixI False) U1) (C1 (MetaCons "IDRXBT" PrefixI False) U1)) ((:+:) (C1 (MetaCons "XBTSGD" PrefixI False) U1) (C1 (MetaCons "SGDXBT" PrefixI False) U1)))))

data Orderbook Source #

The current state of the publically accessible orderbook. Bid orders are requests to buy, ask orders are requests to sell.

data Order Source #

A single placed order in the orderbook

Constructors

Order 

type Bid = Order Source #

Convenient type alias for a bid order

type Ask = Order Source #

Convenient type alias for an ask order

data BitXAuth Source #

An auth type used by all private API calls, after authorisation.

Constructors

BitXAuth 

data PrivateOrder Source #

>>> :set -XOverloadedStrings
>>> "id:secret" :: BitXAuth
BitXAuth {bitXAuthId = "id", bitXAuthSecret = "secret"}
>>> "id:se:cret" :: BitXAuth
BitXAuth {bitXAuthId = "id", bitXAuthSecret = "se:cret"}

A recently placed (private) order, containing a lot more information than is available on the public order book.

Instances

Eq PrivateOrder Source # 
Show PrivateOrder Source # 
BitXAesRecordConvert PrivateOrder Source # 

Associated Types

type Aes PrivateOrder :: * Source #

HasPair PrivateOrder CcyPair Source # 

Methods

pair :: Lens' PrivateOrder CcyPair Source #

HasId PrivateOrder OrderID Source # 

Methods

id :: Lens' PrivateOrder OrderID Source #

HasState PrivateOrder RequestStatus Source # 
HasOrderType PrivateOrder OrderType Source # 
HasLimitVolume PrivateOrder Scientific Source # 
HasLimitPrice PrivateOrder Int Source # 
HasFeeCounter PrivateOrder Scientific Source # 
HasFeeBase PrivateOrder Scientific Source # 
HasExpirationTimestamp PrivateOrder UTCTime Source # 
HasCreationTimestamp PrivateOrder UTCTime Source # 
HasCounter PrivateOrder Scientific Source # 
HasCompletedTimestamp PrivateOrder UTCTime Source # 
HasBase PrivateOrder Scientific Source # 
BitXAesRecordConvert [PrivateOrder] Source # 

Associated Types

type Aes [PrivateOrder] :: * Source #

type Aes PrivateOrder Source # 
type Aes [PrivateOrder] Source # 

data OrderType Source #

The type of a placed order.

Constructors

ASK

A request to sell

BID

A request to buy

data RequestStatus Source #

The state of a (private) placed request -- either an order or a withdrawal request.

Constructors

PENDING

Not yet completed. An order will stay in PENDING state even as it is partially filled, and will move to COMPLETE once it has been completely filled.

COMPLETE

Completed.

CANCELLED

Cancelled. Note that an order cannot be in CANCELLED state, since cancelling an order removes it from the orderbook.

data BitXError Source #

A possible error which the BitX API might return, instead of returning the requested data. Note that as yet there is no exhaustive list of error codes available, so comparisons will have to be done via Text comparisons (as opposed to typed pattern matching). Sorry...

data PrivateOrderWithTrades Source #

A recently placed (private) order, containing a lot more information than is available on the public order book, together with details of any trades which have (partially) filled it.

Instances

Eq PrivateOrderWithTrades Source # 
Show PrivateOrderWithTrades Source # 
BitXAesRecordConvert PrivateOrderWithTrades Source # 
HasPair PrivateOrderWithTrades CcyPair Source # 
HasId PrivateOrderWithTrades OrderID Source # 
HasState PrivateOrderWithTrades RequestStatus Source # 
HasOrderType PrivateOrderWithTrades OrderType Source # 
HasLimitVolume PrivateOrderWithTrades Scientific Source # 
HasLimitPrice PrivateOrderWithTrades Int Source # 
HasFeeCounter PrivateOrderWithTrades Scientific Source # 
HasFeeBase PrivateOrderWithTrades Scientific Source # 
HasExpirationTimestamp PrivateOrderWithTrades UTCTime Source # 
HasCreationTimestamp PrivateOrderWithTrades UTCTime Source # 
HasCounter PrivateOrderWithTrades Scientific Source # 
HasCompletedTimestamp PrivateOrderWithTrades UTCTime Source # 
HasBase PrivateOrderWithTrades Scientific Source # 
HasTrades PrivateOrderWithTrades [Trade] Source # 
type Aes PrivateOrderWithTrades Source # 

data Asset Source #

A trade-able asset. Essentially, a currency.

Constructors

ZAR

South African Rand

NAD

Namibian Dollar

XBT

Bitcoin

KES

Kenyan Shilling

MYR

Malaysian Ringgit

NGN

Nigerian Naira

IDR

Indonesian Rupiah

SGD

Singapore Dollar

Instances

data WithdrawalType Source #

The type of a withdrawal request.

Constructors

ZAR_EFT

ZAR by Electronic Funds Transfer

NAD_EFT

Namibian Dollar by EFT

KES_MPESA

Kenyan Shilling by Vodafone MPESA

MYR_IBG

Malaysian Ringgit by Interbank GIRO (?)

IDR_LLG

Indonesian Rupiah by Lalu Lintas Giro (??)

data OrderQuote Source #

A temporarily locked-in quote.

data QuoteType Source #

Constructors

BUY 
SELL 

Instances

Eq QuoteType Source # 
Show QuoteType Source # 
Generic QuoteType Source # 

Associated Types

type Rep QuoteType :: * -> * #

FromJSON QuoteType Source # 
HasQuoteType QuoteRequest QuoteType Source # 
HasQuoteType OrderQuote QuoteType Source # 
type Rep QuoteType Source # 
type Rep QuoteType = D1 (MetaData "QuoteType" "Network.Bitcoin.BitX.Types" "bitx-bitcoin-0.10.0.0-9BaETuWGwGzIwPqYsLZU89" False) ((:+:) (C1 (MetaCons "BUY" PrefixI False) U1) (C1 (MetaCons "SELL" PrefixI False) U1))

data Transaction Source #

A transaction on a private user account.

Convenient constructors for records which serve as input parameters to functions. These are not completely safe (since you can forget to set a field and the Haskell compiler won't notice), but they are a bit more convenient than dealing with the raw records directly, as long as you're careful.

mkBitXAuth :: BitXAuth Source #

mkBitXAuth = BitXAuth "" ""

mkAccount :: Account Source #

mkAccount = Account "" "" ZAR

mkBitcoinSendRequest :: BitcoinSendRequest Source #

mkBitcoinSendRequest = BitcoinSendRequest 0 ZAR "" Nothing Nothing

mkOrderRequest :: OrderRequest Source #

mkOrderRequest = OrderRequest ZARXBT BID 0 0

mkQuoteRequest :: QuoteRequest Source #

mkQuoteRequest = QuoteRequest BUY ZARXBT 0

mkNewWithdrawal :: NewWithdrawal Source #

mkNewWithdrawal = NewWithdrawal ZAR_EFT 0

mkMarketOrderRequest :: MarketOrderRequest Source #

mkMarketOrderRequest = MarketOrderRequest ZARXBT BID 0

Lens Has* instances for convenient record accessors and mutators.

For a broader view of how these function (and why you can generally ignore them) see the documentation for lens's makeFields.

Essentially, an instance declaration of the form

instance HasFoo MyRecord Int

implies that we can pretend that the data type MyRecord has a field called Foo of type Int (although in reality the field would be called myRecordFoo or such), and that there exists a lens called foo which can be used -- among other things -- as a setter and getter on MyRecord.

class HasError s a | s -> a where Source #

Minimal complete definition

error

Methods

error :: Lens' s a Source #

Instances

class HasErrorCode s a | s -> a where Source #

Minimal complete definition

errorCode

Methods

errorCode :: Lens' s a Source #

class HasBid s a | s -> a where Source #

Minimal complete definition

bid

Methods

bid :: Lens' s a Source #

Instances

class HasAsk s a | s -> a where Source #

Minimal complete definition

ask

Methods

ask :: Lens' s a Source #

Instances

class HasLastTrade s a | s -> a where Source #

Minimal complete definition

lastTrade

Methods

lastTrade :: Lens' s a Source #

Instances

class HasRolling24HourVolume s a | s -> a where Source #

Minimal complete definition

rolling24HourVolume

Methods

rolling24HourVolume :: Lens' s a Source #

class HasPrice s a | s -> a where Source #

Minimal complete definition

price

Methods

price :: Lens' s a Source #

class HasBids s a | s -> a where Source #

Minimal complete definition

bids

Methods

bids :: Lens' s a Source #

Instances

class HasAsks s a | s -> a where Source #

Minimal complete definition

asks

Methods

asks :: Lens' s a Source #

Instances

class HasSecret s a | s -> a where Source #

Minimal complete definition

secret

Methods

secret :: Lens' s a Source #

Instances

class HasBase s a | s -> a where Source #

Minimal complete definition

base

Methods

base :: Lens' s a Source #

class HasCounter s a | s -> a where Source #

Minimal complete definition

counter

Methods

counter :: Lens' s a Source #

class HasFeeBase s a | s -> a where Source #

Minimal complete definition

feeBase

Methods

feeBase :: Lens' s a Source #

class HasLimitPrice s a | s -> a where Source #

Minimal complete definition

limitPrice

Methods

limitPrice :: Lens' s a Source #

class HasState s a | s -> a where Source #

Minimal complete definition

state

Methods

state :: Lens' s a Source #

class HasTrades s a | s -> a where Source #

Minimal complete definition

trades

Methods

trades :: Lens' s a Source #

class HasRowIndex s a | s -> a where Source #

Minimal complete definition

rowIndex

Methods

rowIndex :: Lens' s a Source #

class HasBalance s a | s -> a where Source #

Minimal complete definition

balance

Methods

balance :: Lens' s a Source #

class HasAvailable s a | s -> a where Source #

Minimal complete definition

available

Methods

available :: Lens' s a Source #

class HasBalanceDelta s a | s -> a where Source #

Minimal complete definition

balanceDelta

Methods

balanceDelta :: Lens' s a Source #

class HasAvailableDelta s a | s -> a where Source #

Minimal complete definition

availableDelta

Methods

availableDelta :: Lens' s a Source #

class HasCurrency s a | s -> a where Source #

Minimal complete definition

currency

Methods

currency :: Lens' s a Source #

class HasDescription s a | s -> a where Source #

Minimal complete definition

description

Methods

description :: Lens' s a Source #

class HasAsset s a | s -> a where Source #

Minimal complete definition

asset

Methods

asset :: Lens' s a Source #

class HasReserved s a | s -> a where Source #

Minimal complete definition

reserved

Methods

reserved :: Lens' s a Source #

class HasUnconfirmed s a | s -> a where Source #

Minimal complete definition

unconfirmed

Methods

unconfirmed :: Lens' s a Source #

class HasAddress s a | s -> a where Source #

Minimal complete definition

address

Methods

address :: Lens' s a Source #

class HasTotalReceived s a | s -> a where Source #

Minimal complete definition

totalReceived

Methods

totalReceived :: Lens' s a Source #

class HasTotalUnconfirmed s a | s -> a where Source #

Minimal complete definition

totalUnconfirmed

Methods

totalUnconfirmed :: Lens' s a Source #

class HasAmount s a | s -> a where Source #

Minimal complete definition

amount

Methods

amount :: Lens' s a Source #

class HasWithdrawalType s a | s -> a where Source #

Minimal complete definition

withdrawalType

Methods

withdrawalType :: Lens' s a Source #

class HasMessage s a | s -> a where Source #

Minimal complete definition

message

Methods

message :: Lens' s a Source #

class HasQuoteType s a | s -> a where Source #

Minimal complete definition

quoteType

Methods

quoteType :: Lens' s a Source #

class HasBaseAmount s a | s -> a where Source #

Minimal complete definition

baseAmount

Methods

baseAmount :: Lens' s a Source #

class HasCounterAmount s a | s -> a where Source #

Minimal complete definition

counterAmount

Methods

counterAmount :: Lens' s a Source #

class HasCreatedAt s a | s -> a where Source #

Minimal complete definition

createdAt

Methods

createdAt :: Lens' s a Source #

class HasExpiresAt s a | s -> a where Source #

Minimal complete definition

expiresAt

Methods

expiresAt :: Lens' s a Source #

class HasDiscarded s a | s -> a where Source #

Minimal complete definition

discarded

Methods

discarded :: Lens' s a Source #

class HasExercised s a | s -> a where Source #

Minimal complete definition

exercised

Methods

exercised :: Lens' s a Source #

class HasName s a | s -> a where Source #

Minimal complete definition

name

Methods

name :: Lens' s a Source #

Instances

class HasIsBuy s a | s -> a where Source #

Minimal complete definition

isBuy

Methods

isBuy :: Lens' s a Source #

Instances

class HasStatus s a | s -> a where Source #

Minimal complete definition

status

Methods

status :: Lens' s a Source #

class HasBeneficiaryId s a | s -> a where Source #

Minimal complete definition

beneficiaryId

Methods

beneficiaryId :: Lens' s a Source #