haskoin-core-0.5.2: Bitcoin & Bitcoin Cash library for Haskell

Safe HaskellNone
LanguageHaskell2010

Network.Haskoin.Crypto

Contents

Synopsis

Signatures

data Sig #

Instances
Eq Sig 
Instance details

Defined in Crypto.Secp256k1

Methods

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

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

Read Sig 
Instance details

Defined in Crypto.Secp256k1

Show Sig 
Instance details

Defined in Crypto.Secp256k1

Methods

showsPrec :: Int -> Sig -> ShowS #

show :: Sig -> String #

showList :: [Sig] -> ShowS #

IsString Sig 
Instance details

Defined in Crypto.Secp256k1

Methods

fromString :: String -> Sig #

putSig :: Putter Sig Source #

Serialize an ECDSA signatur for Bitcoin use.

getSig :: Get Sig Source #

Deserialize an ECDSA signature as commonly encoded in Bitcoin.

signHash :: SecKey -> Hash256 -> Sig Source #

Sign a 256-bit hash using secp256k1 elliptic curve.

verifyHashSig :: Hash256 -> Sig -> PubKey -> Bool Source #

Verify an ECDSA signature for a 256-bit hash.

isCanonicalHalfOrder :: Sig -> Bool Source #

Is canonical half order.

decodeStrictSig :: ByteString -> Maybe Sig Source #

Decode signature strictly.

exportSig :: Sig -> ByteString #

Encode signature as strict DER.

Hashes

data Hash512 Source #

Type for 512-bit hashes.

Instances
Eq Hash512 Source # 
Instance details

Defined in Network.Haskoin.Crypto.Hash

Methods

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

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

Ord Hash512 Source # 
Instance details

Defined in Network.Haskoin.Crypto.Hash

Read Hash512 Source # 
Instance details

Defined in Network.Haskoin.Crypto.Hash

Show Hash512 Source # 
Instance details

Defined in Network.Haskoin.Crypto.Hash

IsString Hash512 Source # 
Instance details

Defined in Network.Haskoin.Crypto.Hash

Methods

fromString :: String -> Hash512 #

Hashable Hash512 Source # 
Instance details

Defined in Network.Haskoin.Crypto.Hash

Methods

hashWithSalt :: Int -> Hash512 -> Int #

hash :: Hash512 -> Int #

Serialize Hash512 Source # 
Instance details

Defined in Network.Haskoin.Crypto.Hash

NFData Hash512 Source # 
Instance details

Defined in Network.Haskoin.Crypto.Hash

Methods

rnf :: Hash512 -> () #

data Hash256 Source #

Type for 256-bit hashes.

Instances
Eq Hash256 Source # 
Instance details

Defined in Network.Haskoin.Crypto.Hash

Methods

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

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

Ord Hash256 Source # 
Instance details

Defined in Network.Haskoin.Crypto.Hash

Read Hash256 Source # 
Instance details

Defined in Network.Haskoin.Crypto.Hash

Show Hash256 Source # 
Instance details

Defined in Network.Haskoin.Crypto.Hash

IsString Hash256 Source # 
Instance details

Defined in Network.Haskoin.Crypto.Hash

Methods

fromString :: String -> Hash256 #

Hashable Hash256 Source # 
Instance details

Defined in Network.Haskoin.Crypto.Hash

Methods

hashWithSalt :: Int -> Hash256 -> Int #

hash :: Hash256 -> Int #

Serialize Hash256 Source # 
Instance details

Defined in Network.Haskoin.Crypto.Hash

NFData Hash256 Source # 
Instance details

Defined in Network.Haskoin.Crypto.Hash

Methods

rnf :: Hash256 -> () #

data Hash160 Source #

Type for 160-bit hashes.

Instances
Eq Hash160 Source # 
Instance details

Defined in Network.Haskoin.Crypto.Hash

Methods

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

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

Ord Hash160 Source # 
Instance details

Defined in Network.Haskoin.Crypto.Hash

Read Hash160 Source # 
Instance details

Defined in Network.Haskoin.Crypto.Hash

Show Hash160 Source # 
Instance details

Defined in Network.Haskoin.Crypto.Hash

IsString Hash160 Source # 
Instance details

Defined in Network.Haskoin.Crypto.Hash

Methods

fromString :: String -> Hash160 #

Hashable Hash160 Source # 
Instance details

Defined in Network.Haskoin.Crypto.Hash

Methods

hashWithSalt :: Int -> Hash160 -> Int #

hash :: Hash160 -> Int #

Serialize Hash160 Source # 
Instance details

Defined in Network.Haskoin.Crypto.Hash

NFData Hash160 Source # 
Instance details

Defined in Network.Haskoin.Crypto.Hash

Methods

rnf :: Hash160 -> () #

sha512 :: ByteArrayAccess b => b -> Hash512 Source #

Calculate SHA512 hash.

sha256 :: ByteArrayAccess b => b -> Hash256 Source #

Calculate SHA256 hash.

ripemd160 :: ByteArrayAccess b => b -> Hash160 Source #

Calculate RIPEMD160 hash.

sha1 :: ByteArrayAccess b => b -> Hash160 Source #

Claculate SHA1 hash.

doubleSHA256 :: ByteArrayAccess b => b -> Hash256 Source #

Compute two rounds of SHA-256.

addressHash :: ByteArrayAccess b => b -> Hash160 Source #

Compute SHA-256 followed by RIPMED-160.

checkSum32 :: ByteArrayAccess b => b -> CheckSum32 Source #

Computes a 32 bit checksum.

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

Computes HMAC over SHA-512.

hmac256 :: (ByteArrayAccess k, ByteArrayAccess m) => k -> m -> 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.