Copyright | (c) Alejandro Durán Pallarés, 2015 |
---|---|
License | BSD3 |
Maintainer | vwwv@correo.ugr.es |
Stability | experimental |
Safe Haskell | None |
Language | Haskell2010 |
EasyBitcoin is a simple haskell library providing types and class-instances for bitcoin related code; it also include an small set of functions to handle addresses, transactions and escrows.
Some small examples can be found here .
- data Address net
- class Addressable add where
- address :: BlockNetwork net => add net -> Address net
- isPay2SH :: Address net -> Bool
- isPay2PKH :: Address net -> Bool
- addressFromUncompressed :: Key v net -> Address net
- data Key visibility net
- data Visibility
- derive :: Int -> Key v net -> Key v net
- derivePublic :: Key v net -> Key Public net
- deriveHardened :: Int -> Key Private net -> Key Private net
- deriveRoot :: Key v net -> Key v net
- showAsCompressedSingletonKey :: BlockNetwork net => Key v net -> String
- showAsUncompressedSingletonKey :: BlockNetwork net => Key v net -> String
- serializeCompressedSingleton :: BlockNetwork net => Key v net -> ByteString
- serializeUncompressedSingleton :: BlockNetwork net => Key v net -> ByteString
- (===) :: Key v net -> Key v net -> Bool
- data Outpoint = Outpoint Txid Int
- data Txid
- txid :: Tx net -> Txid
- data Tx net
- transaction :: BlockNetwork net => [(Outpoint, Key Private net)] -> (Address net, BTC net) -> [(Address net, BTC net)] -> Tx net
- unsignedTransaction :: [Outpoint] -> [(Address net, BTC net)] -> Tx net
- txOutputs :: BlockNetwork net => Tx net -> [(Maybe (Address net), BTC net)]
- txInputs :: Tx net -> [Outpoint]
- data RedeemScript net = RedeemScript {
- numRequired :: Int
- redeemSignatures :: [Key Public net]
- data ScriptSig
- data SigHash
- = SigAll {
- anyoneCanPay :: !Bool
- | SigNone {
- anyoneCanPay :: !Bool
- | SigSingle {
- anyoneCanPay :: !Bool
- | SigUnknown {
- anyoneCanPay :: !Bool
- getSigCode :: !Word8
- = SigAll {
- data TxSignature
- sigHashType :: TxSignature -> SigHash
- signTxAt :: BlockNetwork net => Tx net -> Outpoint -> Maybe (RedeemScript net) -> Key Private net -> Tx net
- scriptSig :: Outpoint -> Traversal' (Tx net) ScriptSig
- escrowSignatures :: BlockNetwork net => Prism' ScriptSig ([TxSignature], Maybe (RedeemScript net))
- escrowSignaturesFor :: BlockNetwork net => RedeemScript net -> Prism' ScriptSig [TxSignature]
- simpleSignature :: Prism' ScriptSig (TxSignature, Key Public net)
- checkInput :: BlockNetwork net => Tx net -> Outpoint -> Address net -> Bool
- checkSignatureAt :: BlockNetwork net => Tx net -> Outpoint -> Maybe (RedeemScript net) -> TxSignature -> Key v net -> Bool
- createSignature :: BlockNetwork net => Tx net -> Outpoint -> Maybe (RedeemScript net) -> Key Private net -> TxSignature
- createSignatureAs :: BlockNetwork net => SigHash -> Tx net -> Outpoint -> Maybe (RedeemScript net) -> Key Private net -> TxSignature
- data BTC a
- btc :: Double -> BTC net
- mBTC :: Double -> BTC net
- satoshis :: Int -> BTC net
- asBtc :: BTC net -> Double
- asMbtc :: BTC net -> Double
- asSatoshis :: BTC net -> Int
- showAsBtc :: BTC net -> String
- showAsMbtc :: BTC net -> String
- showAsSatoshis :: BTC net -> String
- data ProdNet
- data TestNet
- class BlockNetwork net where
- data Params net = Params {}
Usage Example:
As a toy example, let's imagine the following scenario:
- On a blog, there's a donation address
mm8LjcoUYdPNKgWshGs7dueFu33aK56ckb
(private key91vaDsoxZACAZeGM89Y7dBnbTB7wrvtBeEkMTpL2sCgEtHf4RBn
). - The blog is written by blogger A, who wrote 70% of the posts, and blogger B, who wrote the remaining 30%.
- They want split the donation proportionally to the number of posts they have written.
- Blogger A has as personal address
miHWju2dzq9RcUPESzYBgVWa3W3swTXtLo
. - Blogger B has as personal address
mvsXpubWQSw2dK2L85iYFppnNjGm439aWK
.
As this is an example, we won't use real bitcoin, but testnet bitcoin, also, we'll use Coinbase's public bitcoin client, Toshi, so we don't have to install anything in our computer:
import Network.EasyBitcoin import Control.Monad(forever) import Network.HTTP.Client(HttpException(StatusCodeException)) import Network.Wreq(get,post,statusCode,responseBody) import Control.Exception(handleJust) import Control.Lens import Data.Aeson.Lens import Data.Aeson import Safe import Control.Applicative import Control.Monad import Control.Concurrent ---------------------------------------------------------------------------------------------- incoming = read "91vaDsoxZACAZeGM89Y7dBnbTB7wrvtBeEkMTpL2sCgEtHf4RBn" :: Key Private TestNet outgoingA = read "miHWju2dzq9RcUPESzYBgVWa3W3swTXtLo" :: Address TestNet outgoingB = read "mvsXpubWQSw2dK2L85iYFppnNjGm439aWK" :: Address TestNet ---------------------------------------------------------------------------------------------- fee = btc 0.0001 -- the miner fee to use. threshold = btc 0.2 -- won't send any transaction till reach this amount. This is important -- to avoid creating "dust" transactions. server = "https://testnet3.toshi.io/" -- The Coinbase Toshi client testnet url. secondsToPool = 20 ---------------------------------------------------------------------------------------------- -- General workflow: -- each 20 seconds: -- - read from Toshi all unspent outpoints. -- - if not enough funds holds on the unspent outpoints: -- continue next iteration. -- - else: -- combining all available outpoints into a transaction to miHWju2dzq9RcUPESzYBgVWa3W3swTXtLo and mvsXpubWQSw2dK2L85iYFppnNjGm439aWK -- send this transaction to Toshi to be broad-casted into the network. main::IO () main = do putStrLn $ "Rebrodcasting from " ++ show (address incoming) ++ " to "++ show outgoingA ++ " and " ++ show outgoingB forever $ do readToshi >>= maybe (return ()) sendToshi . createTransaction threadDelay (secondsToPool*1000000) -- If not enough funds, returns Nothing, otherwise, returns the transaction to be sent. createTransaction :: [(Outpoint, BTC TestNet)] -> Maybe (Tx TestNet) createTransaction inputs = if amount > threshold then Just txToSend else Nothing where amount = sum (fmap snd inputs) - fee amountToA = btc (asBtc amount * 0.7) amountToB = amount - amountToA txToSend = transaction (outpoint,incoming) | (outpoint, _ ) <- inputs [(outgoingB,amountToB)] sendToshi :: Tx TestNet -> IO () sendToshi tx = do putStrLn $ "Sending tx: " ++ show (txid tx) post (server ++ "apiv0/transactions") (toJSON$show tx) return () -- Querying and parsing the Toshi client about the unspent_outputs holds on the address defined by the private key -- 91vaDsoxZACAZeGM89Y7dBnbTB7wrvtBeEkMTpL2sCgEtHf4RBn (that is mm8LjcoUYdPNKgWshGs7dueFu33aK56ckb). readToshi :: IO [(Outpoint, BTC TestNet)] readToshi = handleJust isNotFound (const$ return []) $ do body <- get $ server ++ "apiv0addresses"++ show (address incoming) ++ "unspent_outputs" return $ body ^.. responseBody . values . to parseOutpoint . _Just where -- Toshi returns 404 if the address has never received any tx isNotFound ex = case ex of StatusCodeException s _ _ | s ^. statusCode == 404 -> Just () _ -> Nothing parseOutpoint val = do vout <- (val ^? key "output_index" ._JSON) txid <- (val ^? key "transaction_hash" ._JSON. to readMay._Just) amount <- (val ^? key "amount" ._JSON. to satoshis) Just (Outpoint txid vout, amount)
Addresses:
Bitcoin address, either Pay2PKH or Pay2SH
class Addressable add where Source
Values from where an address can be derived. Keys, are interpreted as compressed by default, if need to derive an address from
an uncompressed key, use addressFromUncompressed
instead.
address :: BlockNetwork net => add net -> Address net Source
Addressable RedeemScript Source | |
Addressable (Key v) Source | As addresses are obtained from public keys hashes, when deriving from a private key, it will first get derived to public address key = address (derivePublic key) Addresses derived from Keys will always be Pay2PKH addresses: isPay2PKH (address key) = True |
isPay2SH :: Address net -> Bool Source
Address was derived from an script hash. Though these addresses can represent the hash of any script, only redeem scripts for multi-signature are currently supported.
addressFromUncompressed :: Key v net -> Address net Source
Derive an address from a key as uncompressed.
Keys:
data Key visibility net Source
Key
s represents public and private bitcoin keys.
Key
s can be used either as singleton keys or as hierarchical deterministic keys
as defined on BIP0032. It supports compressed and uncompressed keys.
It has an additional phantom type to describe on which network this key is supposed to be used .
Its Read
instance understands the WIF format for singleton private keys, the BIP0032 format for private and public hierarchical
deterministic keys, and for singleton public keys it also understands hexadecimal representation of binary serialized OpenSSL public keys.
When parsing a key, if no information about its hierarchal position is available, for example when reading from a WIF format, it is consider to be root.
Its Show
instance works always as defined on BIP0032 In case you need to show it as singleton, you can use
the functions showAsSingletonKey
and showAsSingletonKeyUncompressed
.
Addressable (Key v) Source | As addresses are obtained from public keys hashes, when deriving from a private key, it will first get derived to public address key = address (derivePublic key) Addresses derived from Keys will always be Pay2PKH addresses: isPay2PKH (address key) = True |
Eq (Key v net) Source | |
BlockNetwork net => Read (Key Private net) Source | |
BlockNetwork net => Read (Key Public net) Source | |
BlockNetwork net => Show (Key Private net) Source | |
BlockNetwork net => Show (Key Public net) Source | |
BlockNetwork net => Binary (Key Private net) Source | |
BlockNetwork net => Binary (Key Public net) Source |
data Visibility Source
derive :: Int -> Key v net -> Key v net Source
Derives the n-th child of a key, keeping it public if the parent was public, otherwise private.
derivePublic :: Key v net -> Key Public net Source
Transform a private key into a public key, or does nothing if it was already a public key.
derive n . derivePublic = derivePublic . derive n
deriveHardened :: Int -> Key Private net -> Key Private net Source
Like derive
but derives a hardened child. Hardened child can only be derived from private keys.
deriveRoot :: Key v net -> Key v net Source
Takes a hierarchical key keeping its ECSDA point or exponent, but setting it as root.
It is equivalent to:
deriveRoot = read . showAsSingletonKey
showAsCompressedSingletonKey :: BlockNetwork net => Key v net -> String Source
Show the key as a singleton compressed key as defined by the WIF format for private keys and as hexadecimal representation of the OpenSSL binary serialization for public keys.
showAsUncompressedSingletonKey :: BlockNetwork net => Key v net -> String Source
Like showAsCompressedSingletonKey
but interpreting the keys as uncompressed. Notice this function is
for legacy keys, as currently most software only use compressed keys.
serializeCompressedSingleton :: BlockNetwork net => Key v net -> ByteString Source
serializeUncompressedSingleton :: BlockNetwork net => Key v net -> ByteString Source
(===) :: Key v net -> Key v net -> Bool Source
Compares 2 keys not taking into account their hierarchical position.
k1 === k2 = deriveRoot k1 == deriveRoot k2
Transactions:
Represents a reference to a transaction output, that is, a transaction hash (Txid
) plus the output position
within the output vector of the referenced transaction.
A transaction identification as a hash of the transaction. 2 transaction are consider different if they have different
Txid
s. In some cases, it might be possible for a peer to modify a transaction into an equivalent one having a different
Txid
, for futher info read about the "transaction-malleability-issue".
A transaction hash used to indentify a transaction. Notice that due to the "transaction-malleability-issue", it is possible for an adversary, to derivated a new equivalent transaction with a different Txid.
Bitcoin transaction. When parsed, only syntax validation is performanced, particulary, signature validation is not.
:: BlockNetwork net | |
=> [(Outpoint, Key Private net)] | Transaction's inputs |
-> (Address net, BTC net) | Transaction's output |
-> [(Address net, BTC net)] | Additional optional outputs |
-> Tx net |
Creates a transaction ready to be broadcasted.
unsignedTransaction :: [Outpoint] -> [(Address net, BTC net)] -> Tx net Source
Return a transaction without signatures so it can be signed later on or by other participants (in case of multisignature escrows).
txOutputs :: BlockNetwork net => Tx net -> [(Maybe (Address net), BTC net)] Source
Return's the amount spent for each transaction's output and its address in case it can be parsed (Pay2PKH or Pay2SH).
Escrows and Signatures:
data RedeemScript net Source
Contains:
* number of requiered signatures.
* public keys allowed to use for signing.
The signature order does matter, it should sign using the keys from the tail of the list
till the button, so for eaxample, given RedeemScript 2 [k_a,k_b,key_c]
,
signA.signB
, signA.signC
and signB.signC
would valid combination, but
signB.signA
would not.
RedeemScript | |
|
Addressable RedeemScript Source | |
Eq (RedeemScript net) Source | |
BlockNetwork net => Read (RedeemScript net) Source | |
BlockNetwork net => Show (RedeemScript net) Source | |
BlockNetwork net => Binary (RedeemScript net) Source |
A SigHash stands for Signature Hash Type, and it describes what parts of the transaction shall be signed. Check the docs for more info
SigAll | |
| |
SigNone | |
| |
SigSingle | |
| |
SigUnknown | |
|
data TxSignature Source
A TxSignature
is a combination of a ecdsa signature and the SigHash
used while signing.
sigHashType :: TxSignature -> SigHash Source
:: BlockNetwork net | |
=> Tx net | Transaction to sign |
-> Outpoint | Reference the input within the transaction to be signed. |
-> Maybe (RedeemScript net) | If using to see multisig-escrow, this should contain the redeemScript defining that escrow. |
-> Key Private net | Key to sign |
-> Tx net |
Sign an specific input of a transaction.
escrowSignatures :: BlockNetwork net => Prism' ScriptSig ([TxSignature], Maybe (RedeemScript net)) Source
The prism successes when the scriptSig is either empty, partially or full signed escrow-multisig.
escrowSignaturesFor :: BlockNetwork net => RedeemScript net -> Prism' ScriptSig [TxSignature] Source
The prism successes when the scriptSig is either empty, partially or full signed escrow-multisig; unless it is empty, it will also require than the redeem used by the scriptSig is an specific one.
simpleSignature :: Prism' ScriptSig (TxSignature, Key Public net) Source
The prism successes when the scriptSig is from an already signed Pay2PKH, it does not check whether this signature is valid or not.
checkInput :: BlockNetwork net => Tx net -> Outpoint -> Address net -> Bool Source
Check an specific input of a transaction is fully signed, it understand both, Pay2PKH and Pay2SH for multisig-escrow. for other kinds of
transaction it will return always False
.
In case of multisig-escrow, it also check signatures use the right order defined on the RedeemScript.
:: BlockNetwork net | |
=> Tx net | Transaction to verify. |
-> Outpoint | Reference the input within the transaction to be verified. |
-> Maybe (RedeemScript net) | In case of multisig-escrow this should contain the RedeemScript. |
-> TxSignature | The signature to verify. |
-> Key v net | The signature's key. |
-> Bool |
Verify a signature for a transaction input was done using an specific key.
createSignature :: BlockNetwork net => Tx net -> Outpoint -> Maybe (RedeemScript net) -> Key Private net -> TxSignature Source
Creates a "sig-all" signature of a transaction input.
createSignatureAs :: BlockNetwork net => SigHash -> Tx net -> Outpoint -> Maybe (RedeemScript net) -> Key Private net -> TxSignature Source
Creates an specif type of signature for a transaction's input.
Bitcoins are represented internally as an integer value, but showed and read as a decimal values. When importing them, extra significative digits will be silently dropped.
asSatoshis :: BTC net -> Int Source
showAsMbtc :: BTC net -> String Source
showAsSatoshis :: BTC net -> String Source
Network Parameters:
Original bitcoin network, where "real" bitcoin used on production system.
Bitcoin network for test, where "fake" bitcoins can be used to test systems.
class BlockNetwork net where Source
Network parameters to adapt the library to work with different networks, such when using it for different alt-coins.
Params | |
|