haskoin-core-0.4.2: Implementation of the core Bitcoin protocol features.

Safe HaskellNone
LanguageHaskell98

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; as well as mnemonic keys from BIP-0039.

Synopsis

Elliptic Curve Keys

Public Keys

type PubKey = PubKeyI Generic 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.

type PubKeyC = PubKeyI Compressed Source #

type PubKeyU = PubKeyI Uncompressed Source #

derivePubKey :: PrvKeyI c -> PubKeyI c Source #

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

pubKeyAddr :: Serialize (PubKeyI c) => PubKeyI c -> Address Source #

Computes an Address from a public key

tweakPubKeyC :: PubKeyC -> Hash256 -> Maybe PubKeyC Source #

Tweak a compressed public key

Private Keys

type PrvKey = PrvKeyI Generic Source #

type PrvKeyC = PrvKeyI Compressed Source #

type PrvKeyU = PrvKeyI Uncompressed Source #

encodePrvKey :: PrvKeyI c -> ByteString Source #

Serialize private key as 32-byte big-endian ByteString

decodePrvKey :: (SecKey -> PrvKeyI c) -> ByteString -> Maybe (PrvKeyI c) Source #

Deserialize private key as 32-byte big-endian ByteString

fromWif :: ByteString -> Maybe PrvKey Source #

Decodes a private key from a WIF encoded ByteString. 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 :: PrvKeyI c -> ByteString Source #

Encodes a private key into WIF format

tweakPrvKeyC :: PrvKeyC -> Hash256 -> Maybe PrvKeyC Source #

Tweak a private key

ECDSA

SecretT Monad

The SecretT monad is a monadic wrapper around HMAC DRBG (deterministic random byte generator) using SHA-256. 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.

type SecretT m = StateT (SecretState m) m Source #

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 a Source #

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

getEntropy :: Int -> IO ByteString #

Get a specific number of bytes of cryptographically secure random data using the system-specific facilities.

Use RDRAND if available and XOR with '/dev/urandom' on *nix and CryptAPI when on Windows. In short, this entropy is considered cryptographically secure but not true entropy.

genPrvKey :: Monad m => SecretT m PrvKey Source #

Produce a new PrvKey randomly from the SecretT monad.

Signatures

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

signMsg :: Hash256 -> PrvKeyI c -> Signature Source #

Sign a message

verifySig :: Hash256 -> Signature -> PubKeyI c -> Bool Source #

Verify an ECDSA signature

Hash functions

checkSum32 :: ByteString -> CheckSum32 Source #

Computes a 32 bit checksum.

hash512 :: ByteString -> Hash512 Source #

Compute SHA-512.

hash256 :: ByteString -> Hash256 Source #

Compute SHA-256.

hash160 :: ByteString -> Hash160 Source #

Compute RIPEMD-160.

sha1 :: ByteString -> Hash160 Source #

Compute SHA1

doubleHash256 :: ByteString -> Hash256 Source #

Compute two rounds of SHA-256.

hmac512 :: ByteString -> ByteString -> Hash512 Source #

Computes HMAC over SHA-512.

hmac256 :: ByteString -> ByteString -> Hash256 Source #

Computes HMAC over SHA-256.

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

Split a Hash512 into a pair of Hash256.

join512 :: (Hash256, Hash256) -> Hash512 Source #

Join a pair of Hash256 into a Hash512.

Base58 and Addresses

base58ToAddr :: ByteString -> Maybe Address Source #

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 -> ByteString Source #

Transforms an Address into a base58 encoded String

encodeBase58 :: ByteString -> ByteString Source #

Encode a ByteString to a base 58 representation.

decodeBase58 :: ByteString -> Maybe ByteString Source #

Decode a base58-encoded ByteString. This can fail if the input ByteString contains invalid base58 characters such as 0, O, l, I.

encodeBase58Check :: ByteString -> ByteString Source #

Computes a checksum for the input ByteString and encodes the input and the checksum to a base58 representation.

decodeBase58Check :: ByteString -> Maybe ByteString Source #

Decode a base58-encoded string that contains a checksum. This function returns Nothing if the input string contains invalid base58 characters or if the checksum fails.

Mnemonic keys (BIP-0039)

toMnemonic :: Entropy -> Either String Mnemonic Source #

Provide intial entropy as a ByteString of length multiple of 4 bytes. Output a mnemonic sentence.

mnemonicToSeed :: Passphrase -> Mnemonic -> Either String Seed Source #

Get a 512-bit seed from a mnemonic sentence. Will calculate checksum. Passphrase can be used to protect the mnemonic. Use an empty string as passphrase if none is required.

Extended Keys

Extended Private Keys

data XPrvKey Source #

Data type representing an extended BIP32 private key. An extended key is a node in a tree of key derivations. It has a depth in the tree, a parent node and an index to differentiate it from other siblings.

Constructors

XPrvKey 

Fields

makeXPrvKey :: ByteString -> XPrvKey Source #

Build a BIP32 compatible extended private key from a bytestring. This will produce a root node (depth=0 and parent=0).

xPrvIsHard :: XPrvKey -> Bool Source #

Returns True if the extended private key was derived through a hard derivation.

xPrvChild :: XPrvKey -> KeyIndex Source #

Returns the derivation index of this extended private key without the hard bit set.

xPrvID :: XPrvKey -> Hash160 Source #

Computes the key identifier of an extended private key.

xPrvFP :: XPrvKey -> Word32 Source #

Computes the key fingerprint of an extended private key.

xPrvExport :: XPrvKey -> ByteString Source #

Exports an extended private key to the BIP32 key export format (base 58).

xPrvImport :: ByteString -> Maybe XPrvKey Source #

Decodes a BIP32 encoded extended private key. This function will fail if invalid base 58 characters are detected or if the checksum fails.

xPrvWif :: XPrvKey -> ByteString Source #

Export an extended private key to WIF (Wallet Import Format).

Extended Public Keys

data XPubKey Source #

Data type representing an extended BIP32 public key.

Constructors

XPubKey 

Fields

deriveXPubKey :: XPrvKey -> XPubKey Source #

Derive an extended public key from an extended private key. This function will preserve the depth, parent, index and chaincode fields of the extended private keys.

xPubIsHard :: XPubKey -> Bool Source #

Returns True if the extended public key was derived through a hard derivation.

xPubChild :: XPubKey -> KeyIndex Source #

Returns the derivation index of this extended public key without the hard bit set.

xPubID :: XPubKey -> Hash160 Source #

Computes the key identifier of an extended public key.

xPubFP :: XPubKey -> Word32 Source #

Computes the key fingerprint of an extended public key.

xPubAddr :: XPubKey -> Address Source #

Computer the Address of an extended public key.

xPubExport :: XPubKey -> ByteString Source #

Exports an extended public key to the BIP32 key export format (base 58).

xPubImport :: ByteString -> Maybe XPubKey Source #

Decodes a BIP32 encoded extended public key. This function will fail if invalid base 58 characters are detected or if the checksum fails.

Child key derivations

prvSubKey Source #

Arguments

:: XPrvKey

Extended parent private key

-> KeyIndex

Child derivation index

-> XPrvKey

Extended child private key

Compute a private, soft child key derivation. A private soft derivation will allow the equivalent extended public key to derive the public key for this child. Given a parent key m and a derivation index i, this function will compute m/i/.

Soft derivations allow for more flexibility such as read-only wallets. However, care must be taken not the leak both the parent extended public key and one of the extended child private keys as this would compromise the extended parent private key.

pubSubKey Source #

Arguments

:: XPubKey

Extended Parent public key

-> KeyIndex

Child derivation index

-> XPubKey

Extended child public key

Compute a public, soft child key derivation. Given a parent key M and a derivation index i, this function will compute M/i/.

hardSubKey Source #

Arguments

:: XPrvKey

Extended Parent private key

-> KeyIndex

Child derivation index

-> XPrvKey

Extended child private key

Compute a hard child key derivation. Hard derivations can only be computed for private keys. Hard derivations do not allow the parent public key to derive the child public keys. However, they are safer as a breach of the parent public key and child private keys does not lead to a breach of the parent private key. Given a parent key m and a derivation index i, this function will compute m/i'/.

prvSubKeys :: XPrvKey -> KeyIndex -> [(XPrvKey, KeyIndex)] Source #

Cyclic list of all private soft child key derivations of a parent key starting from an offset index.

pubSubKeys :: XPubKey -> KeyIndex -> [(XPubKey, KeyIndex)] Source #

Cyclic list of all public soft child key derivations of a parent key starting from an offset index.

hardSubKeys :: XPrvKey -> KeyIndex -> [(XPrvKey, KeyIndex)] Source #

Cyclic list of all hard child key derivations of a parent key starting from an offset index.

Address derivations

deriveAddr :: XPubKey -> KeyIndex -> (Address, PubKeyC) Source #

Derive an address from a public key and an index. The derivation type is a public, soft derivation.

deriveAddrs :: XPubKey -> KeyIndex -> [(Address, PubKeyC, KeyIndex)] Source #

Cyclic list of all addresses derived from a public key starting from an offset index. The derivation types are public, soft derivations.

deriveMSAddr :: [XPubKey] -> Int -> KeyIndex -> (Address, RedeemScript) Source #

Derive a multisig address from a list of public keys, the number of required signatures (m) and a derivation index. The derivation type is a public, soft derivation.

deriveMSAddrs :: [XPubKey] -> Int -> KeyIndex -> [(Address, RedeemScript, KeyIndex)] Source #

Cyclic list of all multisig addresses derived from a list of public keys, a number of required signatures (m) and starting from an offset index. The derivation type is a public, soft derivation.

Derivation paths

data DerivPathI t where Source #

Data type representing a derivation path. Two constructors are provided for specifying soft or hard derivations. The path 01'/2 for example can be expressed as Deriv : 0 :| 1 : 2. The HardOrGeneric and GenericOrSoft type classes are used to constrain the valid values for the phantom type t. If you mix hard (:|) and soft (:/) paths, the only valid type for t is Generic. Otherwise, t can be Hard if you only have hard derivation or Soft if you only have soft derivations.

Using this type is as easy as writing the required derivation like in these example: Deriv : 0 : 1 :/ 2 :: SoftPath Deriv :| 0 :| 1 :| 2 :: HardPath Deriv :| 0 : 1 : 2 :: DerivPath

Constructors

(:|) :: HardOrGeneric t => !(DerivPathI t) -> !KeyIndex -> DerivPathI t 
(:/) :: GenericOrSoft t => !(DerivPathI t) -> !KeyIndex -> DerivPathI t 
Deriv :: DerivPathI t 

Instances

Read SoftPath Source # 
Read DerivPath Source # 
Read HardPath Source # 
Show SoftPath Source # 
Show DerivPath Source # 
Show HardPath Source # 
IsString SoftPath Source # 
IsString DerivPath Source # 
IsString HardPath Source # 
FromJSON SoftPath Source # 
FromJSON DerivPath Source # 
FromJSON HardPath Source # 
Eq (DerivPathI t) Source # 

Methods

(==) :: DerivPathI t -> DerivPathI t -> Bool #

(/=) :: DerivPathI t -> DerivPathI t -> Bool #

ToJSON (DerivPathI t) Source # 
NFData (DerivPathI t) Source # 

Methods

rnf :: DerivPathI t -> () #

type DerivPath = DerivPathI Generic Source #

derivePath :: DerivPathI t -> XPrvKey -> XPrvKey Source #

Derive a private key from a derivation path

derivePubPath :: SoftPath -> XPubKey -> XPubKey Source #

Derive a public key from a soft derivation path

(++/) :: DerivPathI t1 -> DerivPathI t2 -> DerivPath Source #

Append two derivation paths together. The result will be a mixed derivation path.

Derivation path parsing

data XKey Source #

Constructors

XPrv 

Fields

XPub 

Fields

Instances

Eq XKey Source # 

Methods

(==) :: XKey -> XKey -> Bool #

(/=) :: XKey -> XKey -> Bool #

Show XKey Source # 

Methods

showsPrec :: Int -> XKey -> ShowS #

show :: XKey -> String #

showList :: [XKey] -> ShowS #

parsePath :: String -> Maybe ParsedPath Source #

Parse derivation path string for extended key. Forms: “m0'2”, “M23/4”.

applyPath :: ParsedPath -> XKey -> Either String XKey Source #

Apply a parsed path to an extended key to derive the new key defined in the path. If the path starts with m/, a private key will be returned and if the path starts with M/, a public key will be returned. Private derivations on a public key, and public derivations with a hard segment, return an error value.

Custom path address derivations

derivePathAddr :: XPubKey -> SoftPath -> KeyIndex -> (Address, PubKeyC) Source #

Derive an address from a given parent path.

derivePathAddrs :: XPubKey -> SoftPath -> KeyIndex -> [(Address, PubKeyC, KeyIndex)] Source #

Cyclic list of all addresses derived from a given parent path and starting from the given offset index.

derivePathMSAddr :: [XPubKey] -> SoftPath -> Int -> KeyIndex -> (Address, RedeemScript) Source #

Derive a multisig address from a given parent path. The number of required signatures (m in m of n) is also needed.

derivePathMSAddrs :: [XPubKey] -> SoftPath -> Int -> KeyIndex -> [(Address, RedeemScript, KeyIndex)] Source #

Cyclic list of all multisig addresses derived from a given parent path and starting from the given offset index. The number of required signatures (m in m of n) is also needed.