bitx-bitcoin-0.11.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.

Instances

Eq Ticker Source # 

Methods

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

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

Data Ticker Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Ticker -> c Ticker #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Ticker #

toConstr :: Ticker -> Constr #

dataTypeOf :: Ticker -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Ticker) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Ticker) #

gmapT :: (forall b. Data b => b -> b) -> Ticker -> Ticker #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Ticker -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Ticker -> r #

gmapQ :: (forall d. Data d => d -> u) -> Ticker -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Ticker -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Ticker -> m Ticker #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Ticker -> m Ticker #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Ticker -> m Ticker #

Ord Ticker Source # 
Show Ticker Source # 
Generic Ticker Source # 

Associated Types

type Rep Ticker :: * -> * #

Methods

from :: Ticker -> Rep Ticker x #

to :: Rep Ticker x -> Ticker #

NFData Ticker Source # 

Methods

rnf :: Ticker -> () #

BitXAesRecordConvert Ticker Source # 

Associated Types

type Aes Ticker :: * Source #

HasTimestamp Ticker UTCTime Source # 
HasRolling24HourVolume Ticker Scientific Source # 
HasPair Ticker CcyPair Source # 
HasLastTrade Ticker (Maybe Int) Source # 
HasBid Ticker (Maybe Int) Source # 
HasAsk Ticker (Maybe Int) Source # 
BitXAesRecordConvert [Ticker] Source # 

Associated Types

type Aes [Ticker] :: * Source #

Methods

aesToRec :: Aes [Ticker] -> [Ticker] Source #

type Rep Ticker Source # 
type Aes Ticker Source # 
type Aes Ticker
type Aes [Ticker] Source # 
type Aes [Ticker]

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 #

Data CcyPair Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CcyPair -> c CcyPair #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CcyPair #

toConstr :: CcyPair -> Constr #

dataTypeOf :: CcyPair -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c CcyPair) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CcyPair) #

gmapT :: (forall b. Data b => b -> b) -> CcyPair -> CcyPair #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CcyPair -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CcyPair -> r #

gmapQ :: (forall d. Data d => d -> u) -> CcyPair -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CcyPair -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CcyPair -> m CcyPair #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CcyPair -> m CcyPair #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CcyPair -> m CcyPair #

Ord CcyPair Source # 
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 # 
NFData CcyPair Source # 

Methods

rnf :: CcyPair -> () #

HasPair Ticker CcyPair Source # 
HasPair PrivateOrder CcyPair Source # 
HasPair OrderRequest CcyPair Source # 
HasPair MarketOrderRequest CcyPair Source # 
HasPair QuoteRequest CcyPair Source # 
HasPair OrderQuote CcyPair Source # 
HasPair PrivateTrade CcyPair Source # 
type Rep CcyPair Source # 
type Rep CcyPair = D1 (MetaData "CcyPair" "Network.Bitcoin.BitX.Types" "bitx-bitcoin-0.11.0.0-C2gby9XIQPy6jaD7bGSiE8" 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.

Instances

Eq Orderbook Source # 
Data Orderbook Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Orderbook -> c Orderbook #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Orderbook #

toConstr :: Orderbook -> Constr #

dataTypeOf :: Orderbook -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Orderbook) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Orderbook) #

gmapT :: (forall b. Data b => b -> b) -> Orderbook -> Orderbook #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Orderbook -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Orderbook -> r #

gmapQ :: (forall d. Data d => d -> u) -> Orderbook -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Orderbook -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Orderbook -> m Orderbook #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Orderbook -> m Orderbook #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Orderbook -> m Orderbook #

Ord Orderbook Source # 
Show Orderbook Source # 
Generic Orderbook Source # 

Associated Types

type Rep Orderbook :: * -> * #

NFData Orderbook Source # 

Methods

rnf :: Orderbook -> () #

BitXAesRecordConvert Orderbook Source # 

Associated Types

type Aes Orderbook :: * Source #

HasTimestamp Orderbook UTCTime Source # 
HasBids Orderbook [Bid] Source # 
HasAsks Orderbook [Ask] Source # 
type Rep Orderbook Source # 
type Rep Orderbook = D1 (MetaData "Orderbook" "Network.Bitcoin.BitX.Types" "bitx-bitcoin-0.11.0.0-C2gby9XIQPy6jaD7bGSiE8" False) (C1 (MetaCons "Orderbook" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "orderbookTimestamp") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 UTCTime)) ((:*:) (S1 (MetaSel (Just Symbol "orderbookBids") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Bid])) (S1 (MetaSel (Just Symbol "orderbookAsks") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Ask])))))
type Aes Orderbook Source # 

data Order Source #

A single placed order in the orderbook

Constructors

Order 

Instances

Eq Order Source # 

Methods

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

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

Data Order Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Order -> c Order #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Order #

toConstr :: Order -> Constr #

dataTypeOf :: Order -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Order) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Order) #

gmapT :: (forall b. Data b => b -> b) -> Order -> Order #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Order -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Order -> r #

gmapQ :: (forall d. Data d => d -> u) -> Order -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Order -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Order -> m Order #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Order -> m Order #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Order -> m Order #

Ord Order Source # 

Methods

compare :: Order -> Order -> Ordering #

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

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

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

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

max :: Order -> Order -> Order #

min :: Order -> Order -> Order #

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 #

NFData Order Source # 

Methods

rnf :: Order -> () #

BitXAesRecordConvert Order Source # 

Associated Types

type Aes Order :: * Source #

HasVolume Order Scientific Source # 
HasPrice Order Int Source # 
HasBids Orderbook [Bid] Source # 
HasAsks Orderbook [Ask] Source # 
type Rep Order Source # 
type Rep Order = D1 (MetaData "Order" "Network.Bitcoin.BitX.Types" "bitx-bitcoin-0.11.0.0-C2gby9XIQPy6jaD7bGSiE8" False) (C1 (MetaCons "Order" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "orderVolume") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Scientific)) (S1 (MetaSel (Just Symbol "orderPrice") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int))))
type Aes Order Source # 
type Aes Order

type Bid = Order Source #

Convenient type alias for a bid order

type Ask = Order Source #

Convenient type alias for an ask order

data Trade Source #

Instances

Eq Trade Source # 

Methods

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

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

Data Trade Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Trade -> c Trade #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Trade #

toConstr :: Trade -> Constr #

dataTypeOf :: Trade -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Trade) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Trade) #

gmapT :: (forall b. Data b => b -> b) -> Trade -> Trade #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Trade -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Trade -> r #

gmapQ :: (forall d. Data d => d -> u) -> Trade -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Trade -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Trade -> m Trade #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Trade -> m Trade #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Trade -> m Trade #

Ord Trade Source # 

Methods

compare :: Trade -> Trade -> Ordering #

(<) :: Trade -> Trade -> Bool #

(<=) :: Trade -> Trade -> Bool #

(>) :: Trade -> Trade -> Bool #

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

max :: Trade -> Trade -> Trade #

min :: Trade -> Trade -> Trade #

Show Trade Source # 

Methods

showsPrec :: Int -> Trade -> ShowS #

show :: Trade -> String #

showList :: [Trade] -> ShowS #

Generic Trade Source # 

Associated Types

type Rep Trade :: * -> * #

Methods

from :: Trade -> Rep Trade x #

to :: Rep Trade x -> Trade #

NFData Trade Source # 

Methods

rnf :: Trade -> () #

BitXAesRecordConvert Trade Source # 

Associated Types

type Aes Trade :: * Source #

HasTimestamp Trade UTCTime Source # 
HasVolume Trade Scientific Source # 
HasPrice Trade Int Source # 
HasIsBuy Trade Bool Source # 
BitXAesRecordConvert [Trade] Source # 

Associated Types

type Aes [Trade] :: * Source #

Methods

aesToRec :: Aes [Trade] -> [Trade] Source #

type Rep Trade Source # 
type Aes Trade Source # 
type Aes Trade
type Aes [Trade] Source # 
type Aes [Trade]

data BitXAuth Source #

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

Constructors

BitXAuth 

Instances

Eq BitXAuth Source # 
Data BitXAuth Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BitXAuth -> c BitXAuth #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BitXAuth #

toConstr :: BitXAuth -> Constr #

dataTypeOf :: BitXAuth -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c BitXAuth) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BitXAuth) #

gmapT :: (forall b. Data b => b -> b) -> BitXAuth -> BitXAuth #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BitXAuth -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BitXAuth -> r #

gmapQ :: (forall d. Data d => d -> u) -> BitXAuth -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> BitXAuth -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> BitXAuth -> m BitXAuth #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BitXAuth -> m BitXAuth #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BitXAuth -> m BitXAuth #

Ord BitXAuth Source # 
Show BitXAuth Source # 
IsString BitXAuth Source # 
Generic BitXAuth Source # 

Associated Types

type Rep BitXAuth :: * -> * #

Methods

from :: BitXAuth -> Rep BitXAuth x #

to :: Rep BitXAuth x -> BitXAuth #

NFData BitXAuth Source # 

Methods

rnf :: BitXAuth -> () #

BitXAesRecordConvert BitXAuth Source # 

Associated Types

type Aes BitXAuth :: * Source #

HasSecret BitXAuth Text Source # 
HasId BitXAuth Text Source # 
type Rep BitXAuth Source # 
type Rep BitXAuth = D1 (MetaData "BitXAuth" "Network.Bitcoin.BitX.Types" "bitx-bitcoin-0.11.0.0-C2gby9XIQPy6jaD7bGSiE8" False) (C1 (MetaCons "BitXAuth" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "bitXAuthId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)) (S1 (MetaSel (Just Symbol "bitXAuthSecret") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text))))
type Aes BitXAuth Source # 

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 # 
Data PrivateOrder Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PrivateOrder -> c PrivateOrder #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PrivateOrder #

toConstr :: PrivateOrder -> Constr #

dataTypeOf :: PrivateOrder -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c PrivateOrder) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PrivateOrder) #

gmapT :: (forall b. Data b => b -> b) -> PrivateOrder -> PrivateOrder #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PrivateOrder -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PrivateOrder -> r #

gmapQ :: (forall d. Data d => d -> u) -> PrivateOrder -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PrivateOrder -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PrivateOrder -> m PrivateOrder #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PrivateOrder -> m PrivateOrder #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PrivateOrder -> m PrivateOrder #

Show PrivateOrder Source # 
Generic PrivateOrder Source # 

Associated Types

type Rep PrivateOrder :: * -> * #

NFData PrivateOrder Source # 

Methods

rnf :: PrivateOrder -> () #

BitXAesRecordConvert PrivateOrder Source # 

Associated Types

type Aes PrivateOrder :: * Source #

HasPair PrivateOrder CcyPair Source # 
HasId 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 Rep PrivateOrder Source # 
type Rep PrivateOrder = D1 (MetaData "PrivateOrder" "Network.Bitcoin.BitX.Types" "bitx-bitcoin-0.11.0.0-C2gby9XIQPy6jaD7bGSiE8" False) (C1 (MetaCons "PrivateOrder" PrefixI True) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "privateOrderBase") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Scientific)) ((:*:) (S1 (MetaSel (Just Symbol "privateOrderCounter") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Scientific)) (S1 (MetaSel (Just Symbol "privateOrderCreationTimestamp") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 UTCTime)))) ((:*:) (S1 (MetaSel (Just Symbol "privateOrderExpirationTimestamp") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 UTCTime)) ((:*:) (S1 (MetaSel (Just Symbol "privateOrderCompletedTimestamp") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 UTCTime)) (S1 (MetaSel (Just Symbol "privateOrderFeeBase") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Scientific))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "privateOrderFeeCounter") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Scientific)) ((:*:) (S1 (MetaSel (Just Symbol "privateOrderLimitPrice") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)) (S1 (MetaSel (Just Symbol "privateOrderLimitVolume") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Scientific)))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "privateOrderId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 OrderID)) (S1 (MetaSel (Just Symbol "privateOrderPair") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 CcyPair))) ((:*:) (S1 (MetaSel (Just Symbol "privateOrderState") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 RequestStatus)) (S1 (MetaSel (Just Symbol "privateOrderOrderType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 OrderType)))))))
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

Instances

Eq OrderType Source # 
Data OrderType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> OrderType -> c OrderType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c OrderType #

toConstr :: OrderType -> Constr #

dataTypeOf :: OrderType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c OrderType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c OrderType) #

gmapT :: (forall b. Data b => b -> b) -> OrderType -> OrderType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> OrderType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> OrderType -> r #

gmapQ :: (forall d. Data d => d -> u) -> OrderType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> OrderType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> OrderType -> m OrderType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> OrderType -> m OrderType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> OrderType -> m OrderType #

Ord OrderType Source # 
Show OrderType Source # 
Generic OrderType Source # 

Associated Types

type Rep OrderType :: * -> * #

FromJSON OrderType Source # 
NFData OrderType Source # 

Methods

rnf :: OrderType -> () #

HasOrderType PrivateOrder OrderType Source # 
HasOrderType OrderRequest OrderType Source # 
HasOrderType MarketOrderRequest OrderType Source # 
HasOrderType PrivateTrade OrderType Source # 
type Rep OrderType Source # 
type Rep OrderType = D1 (MetaData "OrderType" "Network.Bitcoin.BitX.Types" "bitx-bitcoin-0.11.0.0-C2gby9XIQPy6jaD7bGSiE8" False) ((:+:) (C1 (MetaCons "ASK" PrefixI False) U1) (C1 (MetaCons "BID" PrefixI False) U1))

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.

Instances

Eq RequestStatus Source # 
Data RequestStatus Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RequestStatus -> c RequestStatus #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RequestStatus #

toConstr :: RequestStatus -> Constr #

dataTypeOf :: RequestStatus -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c RequestStatus) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RequestStatus) #

gmapT :: (forall b. Data b => b -> b) -> RequestStatus -> RequestStatus #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RequestStatus -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RequestStatus -> r #

gmapQ :: (forall d. Data d => d -> u) -> RequestStatus -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RequestStatus -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RequestStatus -> m RequestStatus #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RequestStatus -> m RequestStatus #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RequestStatus -> m RequestStatus #

Ord RequestStatus Source # 
Show RequestStatus Source # 
Generic RequestStatus Source # 

Associated Types

type Rep RequestStatus :: * -> * #

NFData RequestStatus Source # 

Methods

rnf :: RequestStatus -> () #

HasState PrivateOrder RequestStatus Source # 
HasStatus WithdrawalRequest RequestStatus Source # 
type Rep RequestStatus Source # 
type Rep RequestStatus = D1 (MetaData "RequestStatus" "Network.Bitcoin.BitX.Types" "bitx-bitcoin-0.11.0.0-C2gby9XIQPy6jaD7bGSiE8" False) ((:+:) (C1 (MetaCons "PENDING" PrefixI False) U1) ((:+:) (C1 (MetaCons "COMPLETE" PrefixI False) U1) (C1 (MetaCons "CANCELLED" PrefixI False) U1)))

data OrderRequest Source #

A request to place an order.

Instances

Eq OrderRequest Source # 
Data OrderRequest Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> OrderRequest -> c OrderRequest #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c OrderRequest #

toConstr :: OrderRequest -> Constr #

dataTypeOf :: OrderRequest -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c OrderRequest) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c OrderRequest) #

gmapT :: (forall b. Data b => b -> b) -> OrderRequest -> OrderRequest #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> OrderRequest -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> OrderRequest -> r #

gmapQ :: (forall d. Data d => d -> u) -> OrderRequest -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> OrderRequest -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> OrderRequest -> m OrderRequest #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> OrderRequest -> m OrderRequest #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> OrderRequest -> m OrderRequest #

Ord OrderRequest Source # 
Show OrderRequest Source # 
Generic OrderRequest Source # 

Associated Types

type Rep OrderRequest :: * -> * #

NFData OrderRequest Source # 

Methods

rnf :: OrderRequest -> () #

POSTEncodeable OrderRequest Source # 
HasPair OrderRequest CcyPair Source # 
HasVolume OrderRequest Scientific Source # 
HasPrice OrderRequest Int Source # 
HasOrderType OrderRequest OrderType Source # 
type Rep OrderRequest Source # 
type Rep OrderRequest = D1 (MetaData "OrderRequest" "Network.Bitcoin.BitX.Types" "bitx-bitcoin-0.11.0.0-C2gby9XIQPy6jaD7bGSiE8" False) (C1 (MetaCons "OrderRequest" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "orderRequestPair") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 CcyPair)) (S1 (MetaSel (Just Symbol "orderRequestOrderType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 OrderType))) ((:*:) (S1 (MetaSel (Just Symbol "orderRequestVolume") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Scientific)) (S1 (MetaSel (Just Symbol "orderRequestPrice") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)))))

data MarketOrderRequest Source #

Instances

Eq MarketOrderRequest Source # 
Data MarketOrderRequest Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MarketOrderRequest -> c MarketOrderRequest #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MarketOrderRequest #

toConstr :: MarketOrderRequest -> Constr #

dataTypeOf :: MarketOrderRequest -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c MarketOrderRequest) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MarketOrderRequest) #

gmapT :: (forall b. Data b => b -> b) -> MarketOrderRequest -> MarketOrderRequest #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MarketOrderRequest -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MarketOrderRequest -> r #

gmapQ :: (forall d. Data d => d -> u) -> MarketOrderRequest -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MarketOrderRequest -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MarketOrderRequest -> m MarketOrderRequest #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MarketOrderRequest -> m MarketOrderRequest #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MarketOrderRequest -> m MarketOrderRequest #

Ord MarketOrderRequest Source # 
Show MarketOrderRequest Source # 
Generic MarketOrderRequest Source # 
NFData MarketOrderRequest Source # 

Methods

rnf :: MarketOrderRequest -> () #

POSTEncodeable MarketOrderRequest Source # 
HasPair MarketOrderRequest CcyPair Source # 
HasVolume MarketOrderRequest Scientific Source # 
HasOrderType MarketOrderRequest OrderType Source # 
type Rep MarketOrderRequest Source # 
type Rep MarketOrderRequest = D1 (MetaData "MarketOrderRequest" "Network.Bitcoin.BitX.Types" "bitx-bitcoin-0.11.0.0-C2gby9XIQPy6jaD7bGSiE8" False) (C1 (MetaCons "MarketOrderRequest" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "marketOrderRequestPair") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 CcyPair)) ((:*:) (S1 (MetaSel (Just Symbol "marketOrderRequestOrderType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 OrderType)) (S1 (MetaSel (Just Symbol "marketOrderRequestVolume") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Scientific)))))

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...

Instances

Eq BitXError Source # 
Data BitXError Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BitXError -> c BitXError #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BitXError #

toConstr :: BitXError -> Constr #

dataTypeOf :: BitXError -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c BitXError) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BitXError) #

gmapT :: (forall b. Data b => b -> b) -> BitXError -> BitXError #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BitXError -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BitXError -> r #

gmapQ :: (forall d. Data d => d -> u) -> BitXError -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> BitXError -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> BitXError -> m BitXError #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BitXError -> m BitXError #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BitXError -> m BitXError #

Ord BitXError Source # 
Show BitXError Source # 
Generic BitXError Source # 

Associated Types

type Rep BitXError :: * -> * #

NFData BitXError Source # 

Methods

rnf :: BitXError -> () #

BitXAesRecordConvert BitXError Source # 

Associated Types

type Aes BitXError :: * Source #

HasErrorCode BitXError Text Source # 
HasError BitXError Text Source # 
type Rep BitXError Source # 
type Rep BitXError = D1 (MetaData "BitXError" "Network.Bitcoin.BitX.Types" "bitx-bitcoin-0.11.0.0-C2gby9XIQPy6jaD7bGSiE8" False) (C1 (MetaCons "BitXError" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "bitXErrorError") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)) (S1 (MetaSel (Just Symbol "bitXErrorErrorCode") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text))))
type Aes BitXError 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

Eq Asset Source # 

Methods

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

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

Data Asset Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Asset -> c Asset #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Asset #

toConstr :: Asset -> Constr #

dataTypeOf :: Asset -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Asset) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Asset) #

gmapT :: (forall b. Data b => b -> b) -> Asset -> Asset #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Asset -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Asset -> r #

gmapQ :: (forall d. Data d => d -> u) -> Asset -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Asset -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Asset -> m Asset #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Asset -> m Asset #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Asset -> m Asset #

Ord Asset Source # 

Methods

compare :: Asset -> Asset -> Ordering #

(<) :: Asset -> Asset -> Bool #

(<=) :: Asset -> Asset -> Bool #

(>) :: Asset -> Asset -> Bool #

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

max :: Asset -> Asset -> Asset #

min :: Asset -> Asset -> Asset #

Show Asset Source # 

Methods

showsPrec :: Int -> Asset -> ShowS #

show :: Asset -> String #

showList :: [Asset] -> ShowS #

Generic Asset Source # 

Associated Types

type Rep Asset :: * -> * #

Methods

from :: Asset -> Rep Asset x #

to :: Rep Asset x -> Asset #

FromJSON Asset Source # 
NFData Asset Source # 

Methods

rnf :: Asset -> () #

POSTEncodeable Asset Source # 
HasCurrency Transaction Asset Source # 
HasCurrency BitcoinSendRequest Asset Source # 
HasCurrency Account Asset Source # 
HasAsset Balance Asset Source # 
HasAsset FundingAddress Asset Source # 
type Rep Asset Source # 
type Rep Asset = D1 (MetaData "Asset" "Network.Bitcoin.BitX.Types" "bitx-bitcoin-0.11.0.0-C2gby9XIQPy6jaD7bGSiE8" False) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "ZAR" PrefixI False) U1) (C1 (MetaCons "NAD" PrefixI False) U1)) ((:+:) (C1 (MetaCons "XBT" PrefixI False) U1) (C1 (MetaCons "KES" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "MYR" PrefixI False) U1) (C1 (MetaCons "NGN" PrefixI False) U1)) ((:+:) (C1 (MetaCons "IDR" PrefixI False) U1) (C1 (MetaCons "SGD" PrefixI False) U1))))

data Balance Source #

The current balance of a private account.

Instances

Eq Balance Source # 

Methods

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

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

Data Balance Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Balance -> c Balance #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Balance #

toConstr :: Balance -> Constr #

dataTypeOf :: Balance -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Balance) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Balance) #

gmapT :: (forall b. Data b => b -> b) -> Balance -> Balance #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Balance -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Balance -> r #

gmapQ :: (forall d. Data d => d -> u) -> Balance -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Balance -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Balance -> m Balance #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Balance -> m Balance #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Balance -> m Balance #

Ord Balance Source # 
Show Balance Source # 
Generic Balance Source # 

Associated Types

type Rep Balance :: * -> * #

Methods

from :: Balance -> Rep Balance x #

to :: Rep Balance x -> Balance #

NFData Balance Source # 

Methods

rnf :: Balance -> () #

BitXAesRecordConvert Balance Source # 

Associated Types

type Aes Balance :: * Source #

HasId Balance AccountID Source # 
HasBalance Balance Scientific Source # 
HasUnconfirmed Balance Scientific Source # 
HasReserved Balance Scientific Source # 
HasAsset Balance Asset Source # 
BitXAesRecordConvert [Balance] Source # 

Associated Types

type Aes [Balance] :: * Source #

Methods

aesToRec :: Aes [Balance] -> [Balance] Source #

type Rep Balance Source # 
type Aes Balance Source # 
type Aes [Balance] Source # 
type Aes [Balance]

data FundingAddress Source #

A registered address for an acocunt.

Instances

Eq FundingAddress Source # 
Data FundingAddress Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FundingAddress -> c FundingAddress #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FundingAddress #

toConstr :: FundingAddress -> Constr #

dataTypeOf :: FundingAddress -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c FundingAddress) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FundingAddress) #

gmapT :: (forall b. Data b => b -> b) -> FundingAddress -> FundingAddress #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FundingAddress -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FundingAddress -> r #

gmapQ :: (forall d. Data d => d -> u) -> FundingAddress -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FundingAddress -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FundingAddress -> m FundingAddress #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FundingAddress -> m FundingAddress #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FundingAddress -> m FundingAddress #

Ord FundingAddress Source # 
Show FundingAddress Source # 
Generic FundingAddress Source # 

Associated Types

type Rep FundingAddress :: * -> * #

NFData FundingAddress Source # 

Methods

rnf :: FundingAddress -> () #

BitXAesRecordConvert FundingAddress Source # 
HasAsset FundingAddress Asset Source # 
HasTotalUnconfirmed FundingAddress Scientific Source # 
HasTotalReceived FundingAddress Scientific Source # 
HasAddress FundingAddress Text Source # 
type Rep FundingAddress Source # 
type Rep FundingAddress = D1 (MetaData "FundingAddress" "Network.Bitcoin.BitX.Types" "bitx-bitcoin-0.11.0.0-C2gby9XIQPy6jaD7bGSiE8" False) (C1 (MetaCons "FundingAddress" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "fundingAddressAsset") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Asset)) (S1 (MetaSel (Just Symbol "fundingAddressAddress") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text))) ((:*:) (S1 (MetaSel (Just Symbol "fundingAddressTotalReceived") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Scientific)) (S1 (MetaSel (Just Symbol "fundingAddressTotalUnconfirmed") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Scientific)))))
type Aes FundingAddress Source # 

data WithdrawalRequest Source #

The state of a request to withdraw from an account.

Instances

Eq WithdrawalRequest Source # 
Data WithdrawalRequest Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> WithdrawalRequest -> c WithdrawalRequest #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c WithdrawalRequest #

toConstr :: WithdrawalRequest -> Constr #

dataTypeOf :: WithdrawalRequest -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c WithdrawalRequest) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c WithdrawalRequest) #

gmapT :: (forall b. Data b => b -> b) -> WithdrawalRequest -> WithdrawalRequest #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> WithdrawalRequest -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> WithdrawalRequest -> r #

gmapQ :: (forall d. Data d => d -> u) -> WithdrawalRequest -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> WithdrawalRequest -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> WithdrawalRequest -> m WithdrawalRequest #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> WithdrawalRequest -> m WithdrawalRequest #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> WithdrawalRequest -> m WithdrawalRequest #

Ord WithdrawalRequest Source # 
Show WithdrawalRequest Source # 
Generic WithdrawalRequest Source # 
NFData WithdrawalRequest Source # 

Methods

rnf :: WithdrawalRequest -> () #

BitXAesRecordConvert WithdrawalRequest Source # 
HasId WithdrawalRequest Text Source # 
HasStatus WithdrawalRequest RequestStatus Source # 
BitXAesRecordConvert [WithdrawalRequest] Source # 
type Rep WithdrawalRequest Source # 
type Rep WithdrawalRequest = D1 (MetaData "WithdrawalRequest" "Network.Bitcoin.BitX.Types" "bitx-bitcoin-0.11.0.0-C2gby9XIQPy6jaD7bGSiE8" False) (C1 (MetaCons "WithdrawalRequest" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "withdrawalRequestStatus") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 RequestStatus)) (S1 (MetaSel (Just Symbol "withdrawalRequestId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text))))
type Aes WithdrawalRequest Source # 
type Aes [WithdrawalRequest] Source # 

data NewWithdrawal Source #

A request to withdraw from an account.

Instances

Eq NewWithdrawal Source # 
Data NewWithdrawal Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NewWithdrawal -> c NewWithdrawal #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c NewWithdrawal #

toConstr :: NewWithdrawal -> Constr #

dataTypeOf :: NewWithdrawal -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c NewWithdrawal) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c NewWithdrawal) #

gmapT :: (forall b. Data b => b -> b) -> NewWithdrawal -> NewWithdrawal #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NewWithdrawal -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NewWithdrawal -> r #

gmapQ :: (forall d. Data d => d -> u) -> NewWithdrawal -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> NewWithdrawal -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> NewWithdrawal -> m NewWithdrawal #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NewWithdrawal -> m NewWithdrawal #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NewWithdrawal -> m NewWithdrawal #

Ord NewWithdrawal Source # 
Show NewWithdrawal Source # 
Generic NewWithdrawal Source # 

Associated Types

type Rep NewWithdrawal :: * -> * #

NFData NewWithdrawal Source # 

Methods

rnf :: NewWithdrawal -> () #

POSTEncodeable NewWithdrawal Source # 
HasWithdrawalType NewWithdrawal WithdrawalType Source # 
HasAmount NewWithdrawal Scientific Source # 
HasBeneficiaryId NewWithdrawal (Maybe Text) Source # 
type Rep NewWithdrawal Source # 
type Rep NewWithdrawal = D1 (MetaData "NewWithdrawal" "Network.Bitcoin.BitX.Types" "bitx-bitcoin-0.11.0.0-C2gby9XIQPy6jaD7bGSiE8" False) (C1 (MetaCons "NewWithdrawal" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "newWithdrawalWithdrawalType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 WithdrawalType)) ((:*:) (S1 (MetaSel (Just Symbol "newWithdrawalAmount") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Scientific)) (S1 (MetaSel (Just Symbol "newWithdrawalBeneficiaryId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text))))))

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 (??)

Instances

Eq WithdrawalType Source # 
Data WithdrawalType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> WithdrawalType -> c WithdrawalType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c WithdrawalType #

toConstr :: WithdrawalType -> Constr #

dataTypeOf :: WithdrawalType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c WithdrawalType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c WithdrawalType) #

gmapT :: (forall b. Data b => b -> b) -> WithdrawalType -> WithdrawalType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> WithdrawalType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> WithdrawalType -> r #

gmapQ :: (forall d. Data d => d -> u) -> WithdrawalType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> WithdrawalType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> WithdrawalType -> m WithdrawalType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> WithdrawalType -> m WithdrawalType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> WithdrawalType -> m WithdrawalType #

Ord WithdrawalType Source # 
Show WithdrawalType Source # 
Generic WithdrawalType Source # 

Associated Types

type Rep WithdrawalType :: * -> * #

FromJSON WithdrawalType Source # 
NFData WithdrawalType Source # 

Methods

rnf :: WithdrawalType -> () #

HasWithdrawalType NewWithdrawal WithdrawalType Source # 
type Rep WithdrawalType Source # 
type Rep WithdrawalType = D1 (MetaData "WithdrawalType" "Network.Bitcoin.BitX.Types" "bitx-bitcoin-0.11.0.0-C2gby9XIQPy6jaD7bGSiE8" False) ((:+:) ((:+:) (C1 (MetaCons "ZAR_EFT" PrefixI False) U1) (C1 (MetaCons "NAD_EFT" PrefixI False) U1)) ((:+:) (C1 (MetaCons "KES_MPESA" PrefixI False) U1) ((:+:) (C1 (MetaCons "MYR_IBG" PrefixI False) U1) (C1 (MetaCons "IDR_LLG" PrefixI False) U1))))

data BitcoinSendRequest Source #

A request to send bitcoin to a bitcoin address or email address.

Instances

Eq BitcoinSendRequest Source # 
Data BitcoinSendRequest Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BitcoinSendRequest -> c BitcoinSendRequest #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BitcoinSendRequest #

toConstr :: BitcoinSendRequest -> Constr #

dataTypeOf :: BitcoinSendRequest -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c BitcoinSendRequest) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BitcoinSendRequest) #

gmapT :: (forall b. Data b => b -> b) -> BitcoinSendRequest -> BitcoinSendRequest #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BitcoinSendRequest -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BitcoinSendRequest -> r #

gmapQ :: (forall d. Data d => d -> u) -> BitcoinSendRequest -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> BitcoinSendRequest -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> BitcoinSendRequest -> m BitcoinSendRequest #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BitcoinSendRequest -> m BitcoinSendRequest #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BitcoinSendRequest -> m BitcoinSendRequest #

Ord BitcoinSendRequest Source # 
Show BitcoinSendRequest Source # 
Generic BitcoinSendRequest Source # 
NFData BitcoinSendRequest Source # 

Methods

rnf :: BitcoinSendRequest -> () #

POSTEncodeable BitcoinSendRequest Source # 
HasCurrency BitcoinSendRequest Asset Source # 
HasAddress BitcoinSendRequest Text Source # 
HasAmount BitcoinSendRequest Scientific Source # 
HasDescription BitcoinSendRequest (Maybe Text) Source # 
HasMessage BitcoinSendRequest (Maybe Text) Source # 
type Rep BitcoinSendRequest Source # 
type Rep BitcoinSendRequest = D1 (MetaData "BitcoinSendRequest" "Network.Bitcoin.BitX.Types" "bitx-bitcoin-0.11.0.0-C2gby9XIQPy6jaD7bGSiE8" False) (C1 (MetaCons "BitcoinSendRequest" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "bitcoinSendRequestAmount") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Scientific)) (S1 (MetaSel (Just Symbol "bitcoinSendRequestCurrency") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Asset))) ((:*:) (S1 (MetaSel (Just Symbol "bitcoinSendRequestAddress") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)) ((:*:) (S1 (MetaSel (Just Symbol "bitcoinSendRequestDescription") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "bitcoinSendRequestMessage") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text)))))))

data QuoteRequest Source #

A request to lock in a quote.

Instances

Eq QuoteRequest Source # 
Data QuoteRequest Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> QuoteRequest -> c QuoteRequest #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c QuoteRequest #

toConstr :: QuoteRequest -> Constr #

dataTypeOf :: QuoteRequest -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c QuoteRequest) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c QuoteRequest) #

gmapT :: (forall b. Data b => b -> b) -> QuoteRequest -> QuoteRequest #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> QuoteRequest -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> QuoteRequest -> r #

gmapQ :: (forall d. Data d => d -> u) -> QuoteRequest -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> QuoteRequest -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> QuoteRequest -> m QuoteRequest #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> QuoteRequest -> m QuoteRequest #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> QuoteRequest -> m QuoteRequest #

Ord QuoteRequest Source # 
Show QuoteRequest Source # 
Generic QuoteRequest Source # 

Associated Types

type Rep QuoteRequest :: * -> * #

NFData QuoteRequest Source # 

Methods

rnf :: QuoteRequest -> () #

POSTEncodeable QuoteRequest Source # 
HasPair QuoteRequest CcyPair Source # 
HasQuoteType QuoteRequest QuoteType Source # 
HasBaseAmount QuoteRequest Scientific Source # 
type Rep QuoteRequest Source # 
type Rep QuoteRequest = D1 (MetaData "QuoteRequest" "Network.Bitcoin.BitX.Types" "bitx-bitcoin-0.11.0.0-C2gby9XIQPy6jaD7bGSiE8" False) (C1 (MetaCons "QuoteRequest" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "quoteRequestQuoteType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 QuoteType)) ((:*:) (S1 (MetaSel (Just Symbol "quoteRequestPair") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 CcyPair)) (S1 (MetaSel (Just Symbol "quoteRequestBaseAmount") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Scientific)))))

data OrderQuote Source #

A temporarily locked-in quote.

Instances

Eq OrderQuote Source # 
Data OrderQuote Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> OrderQuote -> c OrderQuote #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c OrderQuote #

toConstr :: OrderQuote -> Constr #

dataTypeOf :: OrderQuote -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c OrderQuote) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c OrderQuote) #

gmapT :: (forall b. Data b => b -> b) -> OrderQuote -> OrderQuote #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> OrderQuote -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> OrderQuote -> r #

gmapQ :: (forall d. Data d => d -> u) -> OrderQuote -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> OrderQuote -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> OrderQuote -> m OrderQuote #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> OrderQuote -> m OrderQuote #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> OrderQuote -> m OrderQuote #

Ord OrderQuote Source # 
Show OrderQuote Source # 
Generic OrderQuote Source # 

Associated Types

type Rep OrderQuote :: * -> * #

NFData OrderQuote Source # 

Methods

rnf :: OrderQuote -> () #

BitXAesRecordConvert OrderQuote Source # 

Associated Types

type Aes OrderQuote :: * Source #

HasPair OrderQuote CcyPair Source # 
HasId OrderQuote Text Source # 
HasQuoteType OrderQuote QuoteType Source # 
HasBaseAmount OrderQuote Scientific Source # 
HasExpiresAt OrderQuote UTCTime Source # 
HasExercised OrderQuote Bool Source # 
HasDiscarded OrderQuote Bool Source # 
HasCreatedAt OrderQuote UTCTime Source # 
HasCounterAmount OrderQuote Scientific Source # 
type Rep OrderQuote Source # 
type Aes OrderQuote Source # 

data QuoteType Source #

Constructors

BUY 
SELL 

Instances

Eq QuoteType Source # 
Data QuoteType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> QuoteType -> c QuoteType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c QuoteType #

toConstr :: QuoteType -> Constr #

dataTypeOf :: QuoteType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c QuoteType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c QuoteType) #

gmapT :: (forall b. Data b => b -> b) -> QuoteType -> QuoteType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> QuoteType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> QuoteType -> r #

gmapQ :: (forall d. Data d => d -> u) -> QuoteType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> QuoteType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> QuoteType -> m QuoteType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> QuoteType -> m QuoteType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> QuoteType -> m QuoteType #

Ord QuoteType Source # 
Show QuoteType Source # 
Generic QuoteType Source # 

Associated Types

type Rep QuoteType :: * -> * #

FromJSON QuoteType Source # 
NFData QuoteType Source # 

Methods

rnf :: QuoteType -> () #

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.11.0.0-C2gby9XIQPy6jaD7bGSiE8" False) ((:+:) (C1 (MetaCons "BUY" PrefixI False) U1) (C1 (MetaCons "SELL" PrefixI False) U1))

data Transaction Source #

A transaction on a private user account.

Instances

Eq Transaction Source # 
Data Transaction Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Transaction -> c Transaction #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Transaction #

toConstr :: Transaction -> Constr #

dataTypeOf :: Transaction -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Transaction) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Transaction) #

gmapT :: (forall b. Data b => b -> b) -> Transaction -> Transaction #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Transaction -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Transaction -> r #

gmapQ :: (forall d. Data d => d -> u) -> Transaction -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Transaction -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Transaction -> m Transaction #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Transaction -> m Transaction #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Transaction -> m Transaction #

Ord Transaction Source # 
Show Transaction Source # 
Generic Transaction Source # 

Associated Types

type Rep Transaction :: * -> * #

NFData Transaction Source # 

Methods

rnf :: Transaction -> () #

BitXAesRecordConvert Transaction Source # 

Associated Types

type Aes Transaction :: * Source #

HasTimestamp Transaction UTCTime Source # 
HasRowIndex Transaction Int Source # 
HasDescription Transaction Text Source # 
HasCurrency Transaction Asset Source # 
HasBalanceDelta Transaction Scientific Source # 
HasBalance Transaction Scientific Source # 
HasAvailableDelta Transaction Scientific Source # 
HasAvailable Transaction Scientific Source # 
BitXAesRecordConvert [Transaction] Source # 

Associated Types

type Aes [Transaction] :: * Source #

type Rep Transaction Source # 
type Aes Transaction Source # 
type Aes [Transaction] Source # 

data Account Source #

A registered account.

Constructors

Account 

Instances

Eq Account Source # 

Methods

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

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

Data Account Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Account -> c Account #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Account #

toConstr :: Account -> Constr #

dataTypeOf :: Account -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Account) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Account) #

gmapT :: (forall b. Data b => b -> b) -> Account -> Account #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Account -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Account -> r #

gmapQ :: (forall d. Data d => d -> u) -> Account -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Account -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Account -> m Account #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Account -> m Account #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Account -> m Account #

Ord Account Source # 
Show Account Source # 
Generic Account Source # 

Associated Types

type Rep Account :: * -> * #

Methods

from :: Account -> Rep Account x #

to :: Rep Account x -> Account #

NFData Account Source # 

Methods

rnf :: Account -> () #

POSTEncodeable Account Source # 
BitXAesRecordConvert Account Source # 

Associated Types

type Aes Account :: * Source #

HasId Account Text Source # 
HasCurrency Account Asset Source # 
HasName Account Text Source # 
type Rep Account Source # 
type Rep Account = D1 (MetaData "Account" "Network.Bitcoin.BitX.Types" "bitx-bitcoin-0.11.0.0-C2gby9XIQPy6jaD7bGSiE8" False) (C1 (MetaCons "Account" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "accountId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)) ((:*:) (S1 (MetaSel (Just Symbol "accountName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)) (S1 (MetaSel (Just Symbol "accountCurrency") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Asset)))))
type Aes Account Source # 

data PrivateTrade Source #

A private trade, containing a lot more information than is avaiable when inspecting trades via the public API.

Instances

Eq PrivateTrade Source # 
Data PrivateTrade Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PrivateTrade -> c PrivateTrade #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PrivateTrade #

toConstr :: PrivateTrade -> Constr #

dataTypeOf :: PrivateTrade -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c PrivateTrade) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PrivateTrade) #

gmapT :: (forall b. Data b => b -> b) -> PrivateTrade -> PrivateTrade #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PrivateTrade -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PrivateTrade -> r #

gmapQ :: (forall d. Data d => d -> u) -> PrivateTrade -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PrivateTrade -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PrivateTrade -> m PrivateTrade #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PrivateTrade -> m PrivateTrade #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PrivateTrade -> m PrivateTrade #

Ord PrivateTrade Source # 
Show PrivateTrade Source # 
Generic PrivateTrade Source # 

Associated Types

type Rep PrivateTrade :: * -> * #

NFData PrivateTrade Source # 

Methods

rnf :: PrivateTrade -> () #

BitXAesRecordConvert PrivateTrade Source # 

Associated Types

type Aes PrivateTrade :: * Source #

HasTimestamp PrivateTrade UTCTime Source # 
HasPair PrivateTrade CcyPair Source # 
HasVolume PrivateTrade Scientific Source # 
HasPrice PrivateTrade Int Source # 
HasIsBuy PrivateTrade Bool Source # 
HasOrderType PrivateTrade OrderType Source # 
HasFeeCounter PrivateTrade Scientific Source # 
HasFeeBase PrivateTrade Scientific Source # 
HasCounter PrivateTrade Scientific Source # 
HasBase PrivateTrade Scientific Source # 
HasOrderId PrivateTrade Text Source # 
BitXAesRecordConvert [PrivateTrade] Source # 

Associated Types

type Aes [PrivateTrade] :: * Source #

type Rep PrivateTrade Source # 
type Rep PrivateTrade = D1 (MetaData "PrivateTrade" "Network.Bitcoin.BitX.Types" "bitx-bitcoin-0.11.0.0-C2gby9XIQPy6jaD7bGSiE8" False) (C1 (MetaCons "PrivateTrade" PrefixI True) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "privateTradeBase") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Scientific)) (S1 (MetaSel (Just Symbol "privateTradeCounter") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Scientific))) ((:*:) (S1 (MetaSel (Just Symbol "privateTradeFeeBase") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Scientific)) ((:*:) (S1 (MetaSel (Just Symbol "privateTradeFeeCounter") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Scientific)) (S1 (MetaSel (Just Symbol "privateTradeIsBuy") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "privateTradeOrderId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)) ((:*:) (S1 (MetaSel (Just Symbol "privateTradePair") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 CcyPair)) (S1 (MetaSel (Just Symbol "privateTradePrice") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)))) ((:*:) (S1 (MetaSel (Just Symbol "privateTradeTimestamp") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 UTCTime)) ((:*:) (S1 (MetaSel (Just Symbol "privateTradeOrderType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 OrderType)) (S1 (MetaSel (Just Symbol "privateTradeVolume") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Scientific)))))))
type Aes PrivateTrade Source # 
type Aes [PrivateTrade] Source # 

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 #

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 #

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

Minimal complete definition

ask

Methods

ask :: Lens' s a Source #

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

Minimal complete definition

lastTrade

Methods

lastTrade :: Lens' s a Source #

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

Minimal complete definition

bids

Methods

bids :: Lens' s a Source #

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

Minimal complete definition

asks

Methods

asks :: Lens' s a Source #

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

Minimal complete definition

secret

Methods

secret :: Lens' s a Source #

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

Minimal complete definition

base

Methods

base :: 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 HasLimitVolume s a | s -> a where Source #

Minimal complete definition

limitVolume

Methods

limitVolume :: Lens' s a Source #

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

Minimal complete definition

rowIndex

Methods

rowIndex :: 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 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 HasMessage s a | s -> a where Source #

Minimal complete definition

message

Methods

message :: 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 #

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

Minimal complete definition

isBuy

Methods

isBuy :: Lens' s a Source #

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 #

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

Minimal complete definition

orderId

Methods

orderId :: Lens' s a Source #