haskoin-crypto-0.0.1.1: Implementation of Bitcoin cryptographic primitives.

Safe HaskellNone

Network.Haskoin.Crypto

Contents

Description

This package provides the elliptic curve cryptography required for creating and validating bitcoin transactions. It also provides SHA-256 and RIPEMD-160 hashing functions.

Synopsis

Elliptic Curve Keys

Public Keys

data PubKey Source

Elliptic curve public key type. Two constructors are provided for creating compressed and uncompressed public keys from a Point. The use of compressed keys is preferred as it produces shorter keys without compromising security. Uncompressed keys are supported for backwards compatibility.

Constructors

PubKey

Compressed public key

Fields

pubKeyPoint :: !Point
 
PubKeyU

Uncompressed public key

Fields

pubKeyPoint :: !Point
 

isValidPubKey :: PubKey -> BoolSource

Returns True if the public key is valid. This will check if the public key point lies on the curve.

isPubKeyU :: PubKey -> BoolSource

Returns True if the public key is uncompressed

derivePubKey :: PrvKey -> PubKeySource

Derives a public key from a private key. This function will preserve information on key compression (PrvKey becomes PubKey and PrvKeyU becomes PubKeyU)

pubKeyAddr :: PubKey -> AddressSource

Computes an Address value from a public key

addPubKeys :: PubKey -> Hash256 -> Maybe PubKeySource

Add a public key to a private key defined by its Hash256 value. This will transform the private key into a public key and add the respective public key points together. This is provided as a helper for BIP32 wallet implementations. This function fails for uncompressed keys and returns Nothing if the private key value is >= than the order of the curve N.

Private Keys

data PrvKey Source

Elliptic curve private key type. Two constructors are provided for creating compressed or uncompressed private keys. Compression information is stored in private key WIF formats and needs to be preserved to generate the correct addresses from the corresponding public key.

Constructors

PrvKey

Compressed private key

Fields

prvKeyFieldN :: !FieldN
 
PrvKeyU

Uncompressed private key

Fields

prvKeyFieldN :: !FieldN
 

isValidPrvKey :: Integer -> BoolSource

Returns True if the private key is valid. This will check if the integer value representing the private key is greater than 0 and smaller than the curve order N.

makePrvKey :: Integer -> Maybe PrvKeySource

Builds a compressed private key from an Integer value. Returns Nothing if the Integer would not produce a valid private key. For security, the Integer needs to be generated from a random source with sufficient entropy.

makePrvKeyU :: Integer -> Maybe PrvKeySource

Builds an uncompressed private key from an Integer value. Returns Nothing if the Integer would not produce a valid private key. For security, the Integer needs to be generated from a random source with sufficient entropy.

fromPrvKey :: PrvKey -> IntegerSource

Returns the Integer value of a private key

isPrvKeyU :: PrvKey -> BoolSource

Returns True of the private key is uncompressed

addPrvKeys :: PrvKey -> Hash256 -> Maybe PrvKeySource

Add two private keys together. One of the keys is defined by a Hash256. The functions fails on uncompressed private keys and return Nothing if the Hash256 is smaller than the order of the curve N. This is provided as a helper for implementing BIP32 wallets.

putPrvKey :: PrvKey -> PutSource

Serialize a private key into the Data.Binary.Put monad as a 32 byte big endian ByteString. This is useful when a constant length serialization format for private keys is required

getPrvKey :: Get PrvKeySource

Deserializes a compressed private key from the Data.Binary.Get monad as a 32 byte big endian ByteString.

getPrvKeyU :: Get PrvKeySource

Deserializes an uncompressed private key from the Data.Binary.Get monad as a 32 byte big endian ByteString

fromWIF :: String -> Maybe PrvKeySource

Decodes a private key from a WIF encoded String. This function can fail if the input string does not decode correctly as a base 58 string or if the checksum fails. http://en.bitcoin.it/wiki/Wallet_import_format

toWIF :: PrvKey -> StringSource

Encodes a private key into WIF format

ECDSA

SecretT Monad

The SecretT monad is a monadic wrapper around HMAC DRBG (deterministic random byte generator) using SHA-256. The implementation is provided in Hash and the specification is defined in http://csrc.nist.gov/publications/nistpubs/800-90A/SP800-90A.pdf. The SecretT monad is used to generate random private keys and random nonces for ECDSA signatures.

type SecretT m a = StateT (SecretState m) m aSource

StateT monad stack tracking the internal state of HMAC DRBG pseudo random number generator using SHA-256. The SecretT monad is run with the withSource function by providing it a source of entropy.

withSource :: Monad m => (Int -> m ByteString) -> SecretT m a -> m aSource

Run a SecretT monad by providing it a source of entropy. You can use devURandom, devRandom or provide your own entropy source function.

devURandom :: Int -> IO ByteStringSource

/dev/urandom entropy source. This is only available on machines supporting it. This function is meant to be used together with withSource.

devRandom :: Int -> IO ByteStringSource

/dev/random entropy source. This is only available on machines supporting it. This function is meant to be used together with withSource.

genPrvKey :: Monad m => SecretT m PrvKeySource

Produce a new PrvKey randomly from the SecretT monad.

Signatures

Elliptic curve cryptography standards are defined in http://www.secg.org/download/aid-780/sec1-v2.pdf

data Signature Source

Data type representing an ECDSA signature.

signMsg :: Monad m => Hash256 -> PrvKey -> SecretT m SignatureSource

Safely sign a message inside the SecretT monad. The SecretT monad will generate a new nonce for each signature.

detSignMsg :: Hash256 -> PrvKey -> SignatureSource

Sign a message using ECDSA deterministic signatures as defined by RFC 6979 http://tools.ietf.org/html/rfc6979

verifySig :: Hash256 -> Signature -> PubKey -> BoolSource

Verify an ECDSA signature

isCanonicalHalfOrder :: Signature -> BoolSource

Returns True if the S component of a Signature is <= order/2. Signatures need to pass this test to be canonical.

Hash functions

type Hash512 = Ring Mod512Source

Data type representing a 512 bit unsigned integer. It is implemented as an Integer modulo 2^512.

type Hash256 = Ring Mod256Source

Data type representing a 256 bit unsigned integer. It is implemented as an Integer modulo 2^256.

type Hash160 = Ring Mod160Source

Data type representing a 160 bit unsigned integer. It is implemented as an Integer modulo 2^160.

data CheckSum32 Source

Data type representing a 32 bit checksum

hash512 :: ByteString -> Hash512Source

Computes SHA-512.

hash512BS :: ByteString -> ByteStringSource

Computes SHA-512 and returns the result as a bytestring.

hash256 :: ByteString -> Hash256Source

Computes SHA-256.

hash256BS :: ByteString -> ByteStringSource

Computes SHA-256 and returns the result as a bytestring.

hash160 :: ByteString -> Hash160Source

Computes RIPEMD-160.

hash160BS :: ByteString -> ByteStringSource

Computes RIPEMD-160 and returns the result as a bytestring.

doubleHash256 :: ByteString -> Hash256Source

Computes two rounds of SHA-256.

doubleHash256BS :: ByteString -> ByteStringSource

Computes two rounds of SHA-256 and returns the result as a bytestring.

chksum32 :: ByteString -> CheckSum32Source

Computes a 32 bit checksum.

hmac512 :: ByteString -> ByteString -> Hash512Source

Computes HMAC over SHA-512.

hmac512BS :: ByteString -> ByteString -> ByteStringSource

Computes HMAC over SHA-512 and return the result as a bytestring.

hmac256 :: ByteString -> ByteString -> Hash256Source

Computes HMAC over SHA-256.

hmac256BS :: ByteString -> ByteString -> ByteStringSource

Computes HMAC over SHA-256 and return the result as a bytestring.

split512 :: Hash512 -> (Hash256, Hash256)Source

Split a Hash512 into a pair of Hash256.

join512 :: (Hash256, Hash256) -> Hash512Source

Join a pair of Hash256 into a Hash512.

Base58 and Addresses

data Address Source

Data type representing a Bitcoin address

Constructors

PubKeyAddress

Public Key Hash Address

Fields

getAddress :: Hash160
 
ScriptAddress

Script Hash Address

Fields

getAddress :: Hash160
 

base58ToAddr :: String -> Maybe AddressSource

Decodes an Address from a base58 encoded String. This function can fail if the String is not properly encoded as base58 or the checksum fails.

addrToBase58 :: Address -> StringSource

Transforms an Address into a base58 encoded String

encodeBase58 :: ByteString -> ByteStringSource

Encode a bytestring to a base 58 representation.

decodeBase58 :: ByteString -> Maybe ByteStringSource

Decode a base 58 encoded bytestring. This can fail if the input bytestring contains invalid base 58 characters such as 0,O,l,I

encodeBase58Check :: ByteString -> ByteStringSource

Computes a checksum for the input bytestring and encodes the input and the checksum to a base 58 representation.

decodeBase58Check :: ByteString -> Maybe ByteStringSource

Decode a base 58 encoded bytestring that contains a checksum. This function returns Nothing if the input bytestring contains invalid base 58 characters or if the checksum fails.