haskoin-core-1.1.0: Bitcoin & Bitcoin Cash library for Haskell
CopyrightNo rights reserved
LicenseMIT
Maintainerjprupp@protonmail.ch
Stabilityexperimental
PortabilityPOSIX
Safe HaskellSafe-Inferred
LanguageHaskell2010

Haskoin.Address

Contents

Description

Base58, CashAddr, Bech32 address and WIF private key serialization support.

Synopsis

Addresses

data Address Source #

Address format for Bitcoin and Bitcoin Cash.

Constructors

PubKeyAddress

pay to public key hash (regular)

Fields

ScriptAddress

pay to script hash

Fields

WitnessPubKeyAddress

pay to witness public key hash

Fields

WitnessScriptAddress

pay to witness script hash

Fields

WitnessAddress

other witness address

Fields

Instances

Instances details
Generic Address Source # 
Instance details

Defined in Haskoin.Address

Associated Types

type Rep Address :: Type -> Type #

Methods

from :: Address -> Rep Address x #

to :: Rep Address x -> Address #

Read Address Source # 
Instance details

Defined in Haskoin.Address

Show Address Source # 
Instance details

Defined in Haskoin.Address

Binary Address Source # 
Instance details

Defined in Haskoin.Address

Methods

put :: Address -> Put #

get :: Get Address #

putList :: [Address] -> Put #

Serial Address Source # 
Instance details

Defined in Haskoin.Address

Methods

serialize :: MonadPut m => Address -> m () #

deserialize :: MonadGet m => m Address #

Serialize Address Source # 
Instance details

Defined in Haskoin.Address

NFData Address Source # 
Instance details

Defined in Haskoin.Address

Methods

rnf :: Address -> () #

Eq Address Source # 
Instance details

Defined in Haskoin.Address

Methods

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

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

Ord Address Source # 
Instance details

Defined in Haskoin.Address

Hashable Address Source # 
Instance details

Defined in Haskoin.Address

Methods

hashWithSalt :: Int -> Address -> Int #

hash :: Address -> Int #

MarshalJSON Network Address Source # 
Instance details

Defined in Haskoin.Address

type Rep Address Source # 
Instance details

Defined in Haskoin.Address

type Rep Address = D1 ('MetaData "Address" "Haskoin.Address" "haskoin-core-1.1.0-EPeWWz60EKPlWai44F9WC" 'False) ((C1 ('MetaCons "PubKeyAddress" 'PrefixI 'True) (S1 ('MetaSel ('Just "hash160") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Hash160)) :+: C1 ('MetaCons "ScriptAddress" 'PrefixI 'True) (S1 ('MetaSel ('Just "hash160") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Hash160))) :+: (C1 ('MetaCons "WitnessPubKeyAddress" 'PrefixI 'True) (S1 ('MetaSel ('Just "hash160") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Hash160)) :+: (C1 ('MetaCons "WitnessScriptAddress" 'PrefixI 'True) (S1 ('MetaSel ('Just "hash256") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Hash256)) :+: C1 ('MetaCons "WitnessAddress" 'PrefixI 'True) (S1 ('MetaSel ('Just "version") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word8) :*: S1 ('MetaSel ('Just "bytes") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ByteString)))))

isPubKeyAddress :: Address -> Bool Source #

Address pays to a public key hash.

isScriptAddress :: Address -> Bool Source #

Address pays to a script hash.

isWitnessPubKeyAddress :: Address -> Bool Source #

Address pays to a witness public key hash. Only valid for SegWit networks.

addrToText :: Network -> Address -> Maybe Text Source #

Convert address to human-readable string. Uses Base58, Bech32Encoding, or CashAddr depending on network.

textToAddr :: Network -> Text -> Maybe Address Source #

Parse Base58, Bech32Encoding or CashAddr address, depending on network.

pubKeyAddr :: Ctx -> PublicKey -> Address Source #

Obtain a standard pay-to-public-key-hash address from a public key.

pubKeyWitnessAddr :: Ctx -> PublicKey -> Address Source #

Obtain a SegWit pay-to-witness-public-key-hash (P2WPKH) address from a public key.

pubKeyCompatWitnessAddr :: Ctx -> PublicKey -> Address Source #

Obtain a backwards-compatible SegWit P2SH-P2WPKH address from a public key.

p2pkhAddr :: Hash160 -> Address Source #

Obtain a standard pay-to-public-key-hash (P2PKH) address from a Hash160.

p2wpkhAddr :: Hash160 -> Address Source #

Obtain a SegWit pay-to-witness-public-key-hash (P2WPKH) address from a Hash160.

p2shAddr :: Hash160 -> Address Source #

Obtain a standard pay-to-script-hash (P2SH) address from a Hash160.

p2wshAddr :: Hash256 -> Address Source #

Obtain a SegWit pay-to-witness-script-hash (P2WSH) address from a Hash256

addressToScript :: Ctx -> Address -> Script Source #

Get output script AST for an Address.

addressToScriptBS :: Ctx -> Address -> ByteString Source #

Encode address as output script in ByteString form.

addressToOutput :: Address -> ScriptOutput Source #

Encode an output script from an address. Will fail if using a pay-to-witness address on a non-SegWit network.

payToScriptAddress :: Ctx -> ScriptOutput -> Address Source #

Compute a standard pay-to-script-hash (P2SH) address for an output script.

payToWitnessScriptAddress :: Ctx -> ScriptOutput -> Address Source #

Compute a SegWit pay-to-witness-script-hash (P2WSH) address for an output script.

payToNestedScriptAddress :: Ctx -> ScriptOutput -> Address Source #

Compute a backwards-compatible SegWit P2SH-P2WSH address.

scriptToAddress :: Ctx -> Script -> Either String Address Source #

Decode an output script into an Address if it has such representation.

scriptToAddressBS :: Ctx -> ByteString -> Either String Address Source #

Decode a serialized script into an Address.