bitcoin-payment-channel-1.2.0.0: Instant, two-party Bitcoin payments

Safe HaskellNone
LanguageHaskell2010

Bitcoin.BIP32.Types

Contents

Synopsis

Key types

data RootPrv Source #

Source of all other key types

Instances

Generic RootPrv Source # 

Associated Types

type Rep RootPrv :: * -> * #

Methods

from :: RootPrv -> Rep RootPrv x #

to :: Rep RootPrv x -> RootPrv #

ToJSON RootPrv Source # 
FromJSON RootPrv Source # 
Serialize RootPrv Source # 
NFData RootPrv Source # 

Methods

rnf :: RootPrv -> () #

DerivationSeed r => HasSigningKey RootPrv r Source # 

Methods

getSignKey :: InputG t r oldSigData -> RootPrv -> PrvKeyC

IsChildKey RootPrv Internal ChildPair HardPath Source # 
IsChildKey RootPrv External ChildPub SoftPath Source # 
IsChildKey RootPrv External ChildPair SoftPath Source # 
DerivationSeed r => DeriveChangeOut (SigSinglePair t r sd) (TxFee, DustPolicy) RootPrv r Source # 

Methods

createChangeOut :: SigSinglePair t r sd -> RootPrv -> (TxFee, DustPolicy) -> ChangeOut Source #

type Rep RootPrv Source # 
type Rep RootPrv = D1 (MetaData "RootPrv" "Bitcoin.BIP32.Types" "bitcoin-payment-channel-1.2.0.0-7YwDEKAOCp2BNoMt0JxEOM" True) (C1 (MetaCons "RootPrv" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 XPrvKey)))

data RootPub Source #

The public counterpart of a RootPrv

data RootKeyId Source #

Unique ID for a 'RootPrv'/'RootPub' pair

data External a Source #

A key pair where the public part can be derived without knowledge of the private part (not safe if a single derived private key is exposed)

Instances

Functor External Source # 

Methods

fmap :: (a -> b) -> External a -> External b #

(<$) :: a -> External b -> External a #

HasKey External ChildPub XPubKey SoftPath Source # 
HasKey External ChildPub PubKeyC SoftPath Source # 
HasKey External ChildPub Address SoftPath Source # 
HasKey External ChildPair XPubKey SoftPath Source # 
HasKey External ChildPair PubKeyC SoftPath Source # 
HasKey External ChildPair PrvKeyC SoftPath Source # 
HasKey External ChildPair Address SoftPath Source # 
IsChildKey RootPub External ChildPub SoftPath Source # 
IsChildKey RootPrv External ChildPub SoftPath Source # 
IsChildKey RootPrv External ChildPair SoftPath Source # 
HasKey External ChildPair (PrvKeyC, XPubKey) SoftPath Source # 
Eq a => Eq (External a) Source # 

Methods

(==) :: External a -> External a -> Bool #

(/=) :: External a -> External a -> Bool #

Show a => Show (External a) Source # 

Methods

showsPrec :: Int -> External a -> ShowS #

show :: External a -> String #

showList :: [External a] -> ShowS #

Generic (External a) Source # 

Associated Types

type Rep (External a) :: * -> * #

Methods

from :: External a -> Rep (External a) x #

to :: Rep (External a) x -> External a #

ToJSON a => ToJSON (External a) Source # 
FromJSON a => FromJSON (External a) Source # 
Serialize a => Serialize (External a) Source # 

Methods

put :: Putter (External a) #

get :: Get (External a) #

NFData a => NFData (External a) Source # 

Methods

rnf :: External a -> () #

type Rep (External a) Source # 
type Rep (External a)

data Internal a Source #

A key pair where the public part cannot be derived without knowledge of the private part (safe if a single derived private key is exposed)

Instances

data ChildPair Source #

Key pair, containing both private and public extended keys. Derive subkeys using getKey

Instances

Eq ChildPair Source # 
Show ChildPair Source # 
Generic ChildPair Source # 

Associated Types

type Rep ChildPair :: * -> * #

NFData ChildPair Source # 

Methods

rnf :: ChildPair -> () #

HasKey Internal ChildPair XPubKey HardPath Source # 
HasKey Internal ChildPair PubKeyC HardPath Source # 
HasKey Internal ChildPair PrvKeyC HardPath Source # 
HasKey Internal ChildPair Address HardPath Source # 
HasKey External ChildPair XPubKey SoftPath Source # 
HasKey External ChildPair PubKeyC SoftPath Source # 
HasKey External ChildPair PrvKeyC SoftPath Source # 
HasKey External ChildPair Address SoftPath Source # 
IsChildKey RootPrv Internal ChildPair HardPath Source # 
IsChildKey RootPrv External ChildPair SoftPath Source # 
HasKey Internal ChildPair (PrvKeyC, XPubKey) HardPath Source # 
HasKey External ChildPair (PrvKeyC, XPubKey) SoftPath Source # 
type Rep ChildPair Source # 
type Rep ChildPair = D1 (MetaData "ChildPair" "Bitcoin.BIP32.Types" "bitcoin-payment-channel-1.2.0.0-7YwDEKAOCp2BNoMt0JxEOM" False) (C1 (MetaCons "ChildPair" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "pairPriv") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 XPrvKey)) (S1 (MetaSel (Just Symbol "pairPub'") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 XPubKey))))

data ChildPub Source #

Public part only of a ChildPair

Instances

Eq ChildPub Source # 
Show ChildPub Source # 
Generic ChildPub Source # 

Associated Types

type Rep ChildPub :: * -> * #

Methods

from :: ChildPub -> Rep ChildPub x #

to :: Rep ChildPub x -> ChildPub #

ToJSON ChildPub Source # 
FromJSON ChildPub Source # 
Serialize ChildPub Source # 
NFData ChildPub Source # 

Methods

rnf :: ChildPub -> () #

HasKey External ChildPub XPubKey SoftPath Source # 
HasKey External ChildPub PubKeyC SoftPath Source # 
HasKey External ChildPub Address SoftPath Source # 
IsChildKey RootPub External ChildPub SoftPath Source # 
IsChildKey RootPrv External ChildPub SoftPath Source # 
type Rep ChildPub Source # 
type Rep ChildPub = D1 (MetaData "ChildPub" "Bitcoin.BIP32.Types" "bitcoin-payment-channel-1.2.0.0-7YwDEKAOCp2BNoMt0JxEOM" True) (C1 (MetaCons "ChildPub" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 XPubKey)))

Child key operations

class HasKey t k key derivPath | t -> derivPath where Source #

Get a key of type key from an 'Internal'/'External' 'ChildPub'/'ChildPair'

Minimal complete definition

getKey

Methods

getKey :: t k -> key Source #

data KeyDeriveIndex Source #

Key index for a BIP32 child key

Instances

Enum KeyDeriveIndex Source # 
Eq KeyDeriveIndex Source # 
Integral KeyDeriveIndex Source # 
Num KeyDeriveIndex Source # 
Ord KeyDeriveIndex Source # 
Real KeyDeriveIndex Source # 
Show KeyDeriveIndex Source # 
ToJSON KeyDeriveIndex Source # 
FromJSON KeyDeriveIndex Source # 
Serialize KeyDeriveIndex Source # 
NFData KeyDeriveIndex Source # 

Methods

rnf :: KeyDeriveIndex -> () #

class HasKeyIndex a where Source #

Minimal complete definition

getKeyIndex

Util

keyId :: HasKeyId rk => rk -> RootKeyId Source #

Re-exports

type SoftPath = DerivPathI Soft #

type HardPath = DerivPathI Hard #