{-# LANGUAGE OverloadedStrings #-}
{-# OPTIONS_GHC -Wall #-}
module Network.Bitcoin.BlockChain ( Client
, TransactionID
, BTC
, getBlockCount
, getDifficulty
, setTransactionFee
, getRawMemoryPool
, BlockHash
, BlockHeight
, getBlockHash
, Block(..)
, getBlock
, OutputSetInfo(..)
, getOutputSetInfo
, OutputInfo(..)
, getOutputInfo
) where
import Control.Monad
import Data.Aeson
import Network.Bitcoin.Internal
import Network.Bitcoin.RawTransaction
getBlockCount :: Client -> IO BlockHeight
getBlockCount client = callApi client "getblockcount" []
getDifficulty :: Client -> IO Integer
getDifficulty client = callApi client "getdifficulty" []
setTransactionFee :: Client -> BTC -> IO ()
setTransactionFee client fee =
stupidAPI <$> callApi client "settxfee" [ tj fee ]
where stupidAPI :: Bool -> ()
stupidAPI = const ()
getRawMemoryPool :: Client -> IO (Vector TransactionID)
getRawMemoryPool client = callApi client "getrawmempool" []
type BlockHash = HexString
type BlockHeight = Integer
getBlockHash :: Client
-> BlockHeight
-> IO BlockHash
getBlockHash client idx = callApi client "getblockhash" [ tj idx ]
data Block = Block { blockHash :: BlockHash
, blkConfirmations :: Integer
, blkSize :: Integer
, blkHeight :: BlockHeight
, blkVersion :: Integer
, merkleRoot :: BlockHash
, subTransactions :: Vector TransactionID
, blkTime :: Integer
, blkNonce :: Integer
, blkBits :: HexString
, blkDifficulty :: Double
, nextBlock :: Maybe BlockHash
, prevBlock :: Maybe BlockHash
}
deriving ( Show, Read, Ord, Eq )
instance FromJSON Block where
parseJSON (Object o) = Block <$> o .: "hash"
<*> o .: "confirmations"
<*> o .: "size"
<*> o .: "height"
<*> o .: "version"
<*> o .: "merkleroot"
<*> o .: "tx"
<*> o .: "time"
<*> o .: "nonce"
<*> o .: "bits"
<*> o .: "difficulty"
<*> o .:? "nextblockhash"
<*> o .:? "previousblockhash"
parseJSON _ = mzero
getBlock :: Client -> BlockHash -> IO Block
getBlock client bh = callApi client "getblock" [ tj bh ]
data OutputSetInfo =
OutputSetInfo { osiBestBlock :: BlockHash
, osiHeight :: BlockHeight
, numTransactions :: Integer
, transactionOutputs :: Integer
, serializedSize :: Integer
}
deriving ( Show, Read, Ord, Eq )
instance FromJSON OutputSetInfo where
parseJSON (Object o) = OutputSetInfo <$> o .: "bestblock"
<*> o .: "height"
<*> o .: "transactions"
<*> o .: "txouts"
<*> o .: "bytes_serialized"
parseJSON _ = mzero
getOutputSetInfo :: Client -> IO OutputSetInfo
getOutputSetInfo client = callApi client "gettxoutsetinfo" []
data OutputInfo =
OutputInfo { oiBestBlock :: BlockHash
, oiConfirmations :: Integer
, oiAmount :: BTC
, oiScriptPubKey :: ScriptPubKey
, oiVersion :: Maybe Integer
, oiCoinBase :: Bool
}
deriving ( Show, Read, Ord, Eq )
instance FromJSON OutputInfo where
parseJSON (Object o) = OutputInfo <$> o .: "bestblock"
<*> o .: "confirmations"
<*> o .: "value"
<*> o .: "scriptPubKey"
<*> o .:? "version"
<*> o .: "coinbase"
parseJSON _ = mzero
getOutputInfo :: Client
-> TransactionID
-> Integer
-> IO (Maybe OutputInfo)
getOutputInfo client txid n = callApi client "gettxout" [ tj txid, tj n ]