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

Safe HaskellNone
LanguageHaskell2010

Bitcoin.SpendCond.Cond

Synopsis

Documentation

class Show c => SpendCondition c where Source #

Script that defines a condition to spend

Minimal complete definition

conditionScript

Methods

conditionScript :: c -> Script Source #

The script will, depending on transaction type, be placed either in output, input or witness of transaction

class SpendFulfillment f c where Source #

Script that can spend funds sent to conditionScript

Minimal complete definition

signatureScript, rawSigs

Methods

signatureScript :: f -> c -> Script Source #

Script fulfilling conditionScript

rawSigs :: f -> c -> [(PubKey, BtcSig)] Source #

Return all pubkeys-and-signature pairs from "f" and "c". Used for signature verification.

class ScriptPubKey c t where Source #

Script we put in the output of a transaction

Minimal complete definition

scriptPubKey

Methods

scriptPubKey :: c -> TxOutputScript t Source #

Instances

SpendCondition c => ScriptPubKey c P2SH Source # 

Methods

scriptPubKey :: c -> TxOutputScript P2SH Source #

SpendCondition c => ScriptPubKey c P2S Source # 

Methods

scriptPubKey :: c -> TxOutputScript P2S Source #

class SignatureScript c f t where Source #

Minimal complete definition

inputScript, witnessScript

Methods

inputScript :: f -> c -> TxInputScript t Source #

The script we put inside a transaction input

witnessScript :: f -> c -> WitnessScript t Source #

The script we put inside a transaction witness

Instances

(SpendCondition c, SpendFulfillment f c) => SignatureScript c f P2SH Source # 

Methods

inputScript :: f -> c -> TxInputScript P2SH Source #

witnessScript :: f -> c -> WitnessScript P2SH Source #

SpendFulfillment f c => SignatureScript c f P2S Source # 

Methods

inputScript :: f -> c -> TxInputScript P2S Source #

witnessScript :: f -> c -> WitnessScript P2S Source #

SignatureScript PubkeyHash SpendPKH Void Source # 

Methods

inputScript :: SpendPKH -> PubkeyHash -> TxInputScript Void Source #

witnessScript :: SpendPKH -> PubkeyHash -> WitnessScript Void Source #

newtype Pay2 a Source #

Pay to something

Constructors

Pay2 a 

Instances

SpendCondition c => ScriptPubKey c P2SH Source # 

Methods

scriptPubKey :: c -> TxOutputScript P2SH Source #

SpendCondition c => ScriptPubKey c P2S Source # 

Methods

scriptPubKey :: c -> TxOutputScript P2S Source #

(SpendCondition c, SpendFulfillment f c) => SignatureScript c f P2SH Source # 

Methods

inputScript :: f -> c -> TxInputScript P2SH Source #

witnessScript :: f -> c -> WitnessScript P2SH Source #

SpendFulfillment f c => SignatureScript c f P2S Source # 

Methods

inputScript :: f -> c -> TxInputScript P2S Source #

witnessScript :: f -> c -> WitnessScript P2S Source #

Eq a => Eq (Pay2 a) Source # 

Methods

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

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

Show a => Show (Pay2 a) Source # 

Methods

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

show :: Pay2 a -> String #

showList :: [Pay2 a] -> ShowS #

Generic (Pay2 a) Source # 

Associated Types

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

Methods

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

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

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

Methods

put :: Putter (Pay2 a) #

get :: Get (Pay2 a) #

NFData a => NFData (Pay2 a) Source # 

Methods

rnf :: Pay2 a -> () #

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

newtype ScriptHash a Source #

Turns something into its SegWit counterpart newtype Witness a = Witness a deriving (Eq, Show, Typeable, Generic, JSON.ToJSON, JSON.FromJSON, Bin.Serialize, NFData)

Hash a SpendCondition

Constructors

ScriptHash a 

Instances

SpendCondition c => ScriptPubKey c P2SH Source # 

Methods

scriptPubKey :: c -> TxOutputScript P2SH Source #

(SpendCondition c, SpendFulfillment f c) => SignatureScript c f P2SH Source # 

Methods

inputScript :: f -> c -> TxInputScript P2SH Source #

witnessScript :: f -> c -> WitnessScript P2SH Source #

Eq a => Eq (ScriptHash a) Source # 

Methods

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

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

Show a => Show (ScriptHash a) Source # 
Generic (ScriptHash a) Source # 

Associated Types

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

Methods

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

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

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

Methods

put :: Putter (ScriptHash a) #

get :: Get (ScriptHash a) #

NFData a => NFData (ScriptHash a) Source # 

Methods

rnf :: ScriptHash a -> () #

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

data Cond Source #

Represents a SpendCondition

Constructors

Cond 

Instances

Eq Cond Source # 

Methods

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

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

Show Cond Source # 

Methods

showsPrec :: Int -> Cond -> ShowS #

show :: Cond -> String #

showList :: [Cond] -> ShowS #

Generic Cond Source # 

Associated Types

type Rep Cond :: * -> * #

Methods

from :: Cond -> Rep Cond x #

to :: Rep Cond x -> Cond #

ToJSON Cond Source # 
FromJSON Cond Source # 
Serialize Cond Source # 

Methods

put :: Putter Cond #

get :: Get Cond #

NFData Cond Source # 

Methods

rnf :: Cond -> () #

SpendCondition c => ScriptPubKey c P2SH Source # 

Methods

scriptPubKey :: c -> TxOutputScript P2SH Source #

SpendCondition c => ScriptPubKey c P2S Source # 

Methods

scriptPubKey :: c -> TxOutputScript P2S Source #

(SpendCondition c, SpendFulfillment f c) => SignatureScript c f P2SH Source # 

Methods

inputScript :: f -> c -> TxInputScript P2SH Source #

witnessScript :: f -> c -> WitnessScript P2SH Source #

SpendFulfillment f c => SignatureScript c f P2S Source # 

Methods

inputScript :: f -> c -> TxInputScript P2S Source #

witnessScript :: f -> c -> WitnessScript P2S Source #

type Rep Cond Source # 
type Rep Cond = D1 (MetaData "Cond" "Bitcoin.SpendCond.Cond" "bitcoin-payment-channel-1.2.0.0-7YwDEKAOCp2BNoMt0JxEOM" False) (C1 (MetaCons "Cond" PrefixI False) U1)

p2shScriptPubKey :: TxOutputScript a -> TxOutputScript b Source #

data PubkeyHash Source #

Constructors

PubkeyHash PubKey 

Instances

Eq PubkeyHash Source # 
Show PubkeyHash Source # 
Generic PubkeyHash Source # 

Associated Types

type Rep PubkeyHash :: * -> * #

ToJSON PubkeyHash Source # 
FromJSON PubkeyHash Source # 
Serialize PubkeyHash Source # 
NFData PubkeyHash Source # 

Methods

rnf :: PubkeyHash -> () #

SpendCondition PubkeyHash Source # 
SpendFulfillment SpendPKH PubkeyHash Source # 
SignatureScript PubkeyHash SpendPKH Void Source # 

Methods

inputScript :: SpendPKH -> PubkeyHash -> TxInputScript Void Source #

witnessScript :: SpendPKH -> PubkeyHash -> WitnessScript Void Source #

type Rep PubkeyHash Source # 
type Rep PubkeyHash = D1 (MetaData "PubkeyHash" "Bitcoin.SpendCond.Cond" "bitcoin-payment-channel-1.2.0.0-7YwDEKAOCp2BNoMt0JxEOM" False) (C1 (MetaCons "PubkeyHash" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PubKey)))

data SpendPKH Source #

Constructors

SpendPKH BtcSig 

Instances