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

CopyrightNo Rights Reserved
LicensePublic Domain
MaintainerTebello Thejane <zyxoas+hackage@gmail.com>
StabilityExperimental
Portabilitynon-portable (GHC Extensions)
Safe HaskellNone
LanguageHaskell2010

Network.Bitcoin.BitX.Public

Description

Usage example

As a small example, to get the current selling price of bitcoin on the BitX exchange, do the following:

{-# LANGUAGE QuasiQuotes #-}

import Record.Lens
import Record
import Network.Bitcoin.BitX

main = do
  bitXResponse <- getTicker XBTZAR
  case bitXResponse of
    ValidResponse tic -> print (view [lens| ask |] tic)
    _                 -> error "Ah well..."
 

Synopsis

Documentation

getTicker :: CcyPair -> IO (BitXAPIResponse Ticker) Source

Returns the latest ticker indicators.

getTickers :: IO (BitXAPIResponse [Ticker]) Source

Returns the latest ticker indicators from all active BitX exchanges.

getOrderBook :: CcyPair -> IO (BitXAPIResponse Orderbook) Source

Returns a list of bids and asks in the order book.

Ask orders are sorted by price ascending. Bid orders are sorted by price descending. Note that multiple orders at the same price are not necessarily conflated.

getTrades :: CcyPair -> IO (BitXAPIResponse [Trade]) Source

Returns a list of the most recent trades