bitcoin-hs-0.0.1: Partial implementation of the Bitcoin protocol (as of 2013)

Safe HaskellNone
LanguageHaskell98

Bitcoin.Protocol.Signature

Contents

Description

Signing, verifying, and encoding/decoding of signatures.

Synopsis

types

data Signature Source #

An ECDSA signature

Constructors

Signature 

data SignatureExt Source #

"Extended signature": an ECDSA signature together with the sighash type

newtype SignBits Source #

Two extra bits of information, used to recover the public key from the signatures.

Constructors

SignBits Word8 

data SigHash Source #

SigHash specifies how to the OP_CHECKSIG opcode should work (?)

Constructors

SigHash 

data SigHashType Source #

Constructors

SigHashAll 
SigHashNone 
SigHashSingle 
SigHashAllZero

0 appears in the blockchain, should be handled as SigHashAll, but we must also properly serialize it back to 0 :(

SigHash encoding

DER signature encoding

encodeSignatureDER :: OctetStream a => SignatureExt -> a Source #

Signatures use DER encoding to pack the r and s components into a single byte stream (this is also what OpenSSL produces by default). (it seem that this is true only in the blockchain, not for signatures of messages, which use CompactSig?)

Howeever, there is an extra last byte appended, which is "SIGHASH"

decodeSignatureDER' :: OctetStream a => Bool -> a -> Maybe SignatureExt Source #

DER encoding looks like this:

0x30 len [ 0x02 lenR [ R ] 0x02 lenS [ S ] ] SIGHASH

so that's 7 extra bytes on top of R and S.

Except when it doesn't look it that... (mostly in MULTISIG transactions). Of course nothing is documented anywhere.

So the Bool argument controls if we are playing strict (True) or loose (False)

"compact" signature encoding

decodeCompactSigBase64 :: Base64 -> Maybe (PubKeyFormat, SignBits, Signature) Source #

Decodes a base64-encoded "compact" signature

decodeCompactSig :: OctetStream a => a -> Maybe (PubKeyFormat, SignBits, Signature) Source #

Decodes a 65 bytes long "compact" signature.

First byte is either one of 0x1b, 0x1c, 0x1d, 0x1e (uncompressed public key) or 0x1f, 0x20, 0x21, 0x22 (compressed public key). This information is necessary to recover the public key from the message hash and the signature. In the output only the relevant two bits of information is retained.

After that comes 32 bytes R and 32 bytes S.

encodeCompactSig :: OctetStream a => (PubKeyFormat, SignBits, Signature) -> a Source #

About the Word8: Bit 0 encodes whether the curve point R (which has x coordinate r from the signature) has even or odd y coordinate; and bit 1 encodes how to reconstruct the x coordinate from r. The rest of the bits must be zero

signing messages (user specified random generator)

signTextMessage :: (OctetStream msg, RandomGen gen) => PrivKey -> msg -> gen -> ((SignBits, Signature), gen) Source #

Signing a bitcoin-QT compatible text message

signRawMessage :: (OctetStream msg, RandomGen gen) => PrivKey -> msg -> gen -> ((SignBits, Signature), gen) Source #

signTextMessageAddr_ :: (OctetStream msg, RandomGen gen) => PubKeyFormat -> PrivKey -> msg -> gen -> (Base64, gen) Source #

signTextMessageAddr :: (OctetStream msg, RandomGen gen) => PubKeyFormat -> PrivKey -> msg -> gen -> ((Address, Base64), gen) Source #

Bitcoin-QT compatible message signing (can be checked with the address instead of the public key)

signing messages (default random generator in IO - primarily for testing)

signTextMessageIO :: OctetStream msg => PrivKey -> msg -> IO (SignBits, Signature) Source #

Signing a bitcoin-QT compatible text message (using the default random number generator in IO).

signTextMessageAddrIO :: OctetStream msg => PubKeyFormat -> PrivKey -> msg -> IO (Address, Base64) Source #

Bitcoin-QT compatible message signing with the default random generator (can be checked with the address instead of the public key)

signing messages (RFC6979 deterministic signatures)

signTextMessageRFC6979 :: OctetStream msg => PrivKey -> msg -> (SignBits, Signature) Source #

Signing a bitcoin-QT compatible text message using the deterministic RFC6979 signatures.

signRawMessageRFC6979 :: OctetStream msg => PrivKey -> msg -> (SignBits, Signature) Source #

Signing a raw (octet stream) message using the deterministic RFC6979 signatures.

signTextMessageAddrRFC6979 :: OctetStream msg => PubKeyFormat -> PrivKey -> msg -> (Address, Base64) Source #

Bitcoin-QT compatible message signing (can be checked with the address instead of the public key), using the deterministic RFC6979 signatures.

verifying signatures

verifyTextSignatureAddr :: OctetStream msg => Address -> Base64 -> msg -> Bool Source #

First argument is the address, second is the base64-encoded "compact signature", third is the message.

TODO: UTF8 encoding!

verifyTextSignaturePK :: OctetStream msg => PubKey -> Signature -> msg -> Bool Source #

Verifying a bitcoin-QT compatible text signature using the public key

verifyRawSignaturePK :: OctetStream msg => PubKey -> Signature -> msg -> Bool Source #

Verifying a signature for raw data (no bitcoin-QT magic wrapper around the message)

public key recovery

recoverTextPubKey :: OctetStream msg => (PubKeyFormat, SignBits, Signature) -> msg -> Maybe PubKey Source #

Recovers the public key from the compact signature and the text message (Bitcoin-QT compatible)

recoverRawPubKey :: OctetStream msg => (PubKeyFormat, SignBits, Signature) -> msg -> Maybe PubKey Source #

Recovers the public key from the compact signature and the raw message (no Bitcoin-QT magic)

text message signing (bitcoin-qt compatible)

messageMagic :: ByteString Source #

This is prepended to the message. Only it is not simply prepended...

prepareMessageForSigning :: OctetStream a => a -> ByteString Source #

Now, this is a seriously braindead and completely undocumented protocol

messageHash :: OctetStream msg => Bool -> msg -> Hash256 Source #

The message hash function we use for signing message.

The bool parameter specifies whether to sign the raw message or the really stupidly serialized and magic prefixed text version...