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

Copyright(c) Rune K. Svendsen 2016
LicensePublicDomain
Maintainerrunesvend@gmail.com
Stabilityexperimental
PortabilityPOSIX
Safe HaskellNone
LanguageHaskell2010

PaymentChannel

Contents

Description

TODO: Outdated

In order to set up a payment channel between a sender and a receiver, the two parties must first agree on three [1] parameters for the channel:

  1. sender public key
  2. receiver public key
  3. channel expiration date

These parameters are contained in ChanParams, from which the Bitcoin address used to fund the payment channel can be derived using getFundingAddress. The transaction which pays to this address is the channel funding transaction, and information about it is contained in a FundingTxInfo. So, the channel funding transaction will contain an output which pays to the address returned by getFundingAddress, and once this transaction is created and in the blockchain, a ClientPayChan and ServerPayChan instance can be created, after first creating the FundingTxInfo instance. FundingTxInfo contains three pieces of information about the funding transaction:

  1. hash/transaction ID
  2. index/vout of the funding output (paying to getFundingAddress address),
  3. value of the funding output (paying to getFundingAddress address)

With ChanParams and FundingTxInfo, the sender can create a new ClientPayChanI, plus the first channel payment, using channelWithInitialPaymentOf. channelWithInitialPaymentOf takes two additional arguments:

  1. a signing function which, given a hash, produces a signature that verifies against cpSenderPubKey in ChanParams
  2. the value of the first channel payment

The sender will want to use flip signMsg senderPrivKey as the signing function, where senderPrivKey is the private key from which cpSenderPubKey is derived. channelWithInitialPaymentOf will return the first channel Payment as well as the new ClientPayChanI state. The new state is stored, and the Payment transferred to the receiver.

The receiver will now create its own channel state object, ServerPayChan, using channelFromInitialPayment. channelFromInitialPayment takes [TODO].

Now the payment channel is open and ready for transmitting value. A new Payment is created by the sender with createPayment, which yields a new payment, that increases the total value transmitted to the receiver by the specified amount, and an updated ClientPayChanI state. The receiver will verify and register this Payment on its side using acceptPayment, which, on success, returns the value received with this payment plus the updated ServerPayChan state object.

Payments can flow from the sender to receiver until either the channel is exhausted, or getting close to expiration (see important note below). In either case the receiver will use getSignedSettlementTx to create the settlement Bitcoin transaction, and publish this transaction to the Bitcoin network. The settlement Bitcoin transaction pays the total value transmitted over the channel to the receiver and the rest back to the sender.

A settlement transaction can be produced by the value receiver using getSignedSettlementTx. The receiver will want to use flip signMsg receiverPrivKey as the signing function passed to getSignedSettlementTx, where receiverPrivKey is the private key from which cpReceiverPubKey is derived.

1
In addition to this, two configuration options must also be agreed upon: a "dust limit", and a "settlement period" (measured in hours), which is subtracted from the channel expiration date in order to arrive at the effective (earlier) expiration date. This is necessary to give the server/receiver time to publish the settlement transaction before the refund transaction becomes valid. The dust limit is the minimum amount that the server is willing to accept as the client change value in the payment transaction. It's only relevant if the channel is emptied of value completely, but it is necessary because the server doesn't want to accept payments based on transactions it cannot publish via the Bitcoin P2P network, because they contain an output of minuscule value. Sensible values are contained in defaultConfig, but clientsender and serverreceiver need to agree on these parameter as well, although they are only relevant 1) (in the case of the dust limit) if the channel is compleltely exchausted and 2) (in case of the "settlemend period") if the client tries to make payments close to expiration (and, in case the client does, it will just receive an error in response, saying the channel is now closed).

IMPORTANT: Channel setup is risk free because the sender can derive a refund Bitcoin transaction using getRefundBitcoinTx, which returns the bitcoins used to fund the channel back to the sender. This refund transaction, however, is not valid until the expiration date specified in ChanParams, but it is paramount that the value receiver get a settlement transaction included in a block before the refund transaction becomes valid. Due to the fact that Bitcoin network time is allowed to drift up to two hours from actual time, and the fact that finding new Bitcoin blocks does not occur according to any schedule, it would be wise for the receiver to publish a settlement transaction at least 6 hours before the specified channel expiration time, and possibly earlier, if the receiver wants to be cautious.

Synopsis

Initialization

hasMinimumDuration :: (HasLockTimeDate lockTime, MonadTime m) => ServerSettings -> lockTime -> m (Either OpenError ()) Source #

Funding

getFundingAddress :: ChanParams -> Address Source #

Derive a Bitcoin address, for funding a payment channel, from ChanParams. The transaction which pays to this address is the channel funding transaction, and information about this transaction is contained in FundingTxInfo.

validFundingInfo :: SendPubKey -> LockTimeDate -> FundingInfo -> Either ChannelCreationError ChanParams Source #

State creation

channelWithInitialPayment Source #

Arguments

:: PrvKeyC

Client private key. Its corresponding public key was provided to server when fetching FundingInfo

-> LockTimeDate

Channel expiration date (was also provided to the server when fetching FundingInfo)

-> (Tx, Vout)

Funding transaction, plus transaction output index to use

-> FundingInfo

Server-returned funding info

-> Either ChannelCreationError (ClientPayChanI BtcSig, SignedPayment)

Client state and first payment (or error).

channelFromInitialPayment Source #

Arguments

:: MonadTime m 
=> ServerSettings

Derived from/matches the client's FundingInfo

-> Tx

Funding transaction

-> PaymentData

Opening payment produced by client (channelWithInitialPayment)

-> m (Either PayChanError ServerPayChan)

Server channel state

Create new ServerPayChan

Payment

createPayment Source #

Arguments

:: ClientPayChan

Sender state object

-> BtcAmount

Amount to send

-> Either BtcError (ClientPayChan, SignedPayment)

Updated sender state & payment

Create new payment of specified value, along with updated state containing this payment.

createPaymentCapped Source #

Arguments

:: ClientPayChan

Sender state object

-> Capped BtcAmount

Maximum amount to send

-> (ClientPayChan, SignedPayment, BtcAmount)

Updated sender state, payment and actual payment value

Create new payment of, at most, specified value, along with updated state containing this payment.

newtype Capped val Source #

At most the specified fee. Will not fail if the specified amount is more than is available.

Constructors

Capped val 

Instances

HasFee fee => HasFee (Capped fee) Source # 

Methods

absoluteFee :: BtcAmount -> TxByteSize -> Capped fee -> BtcAmount Source #

PaymentValueSpec (Capped BtcAmount) Source # 

Methods

paymentValue :: BtcAmount -> ServerSettings -> Capped BtcAmount -> BtcAmount Source #

acceptPayment Source #

Arguments

:: MonadTime m 
=> PaymentData

Payment to verify and register

-> ServerPayChanI kd

Receiver state object

-> m (Either PayChanError (ServerPayChanI kd, BtcAmount))

Value received plus new receiver state object

Register, on the receiving side, a payment made by createPayment on the sending side. Returns error if either the signature or payment amount is invalid, and otherwise the amount received with this Payment and a new state object. | NB: Throws BadSignatureInState on invalid old/in-state payment.

getClosedState :: ClosedServerChanI kd -> ServerPayChanI kd Source #

Settlement

getRefundBitcoinTx Source #

Arguments

:: (Monad m, ToChangeOutFee fee) 
=> ClientPayChan 
-> Address

Refund address

-> fee

Refund transaction fee

-> m (Either BtcError RefundTx)

Refund Bitcoin transaction. Error only in case of insufficient value to cover fee (dust outputs are accepted).

Produces a Bitcoin transaction which sends all channel funds back to the sender. Will not be accepted by the Bitcoin network until the expiration time specified in ChanParams. Receiver should be aware of Bitcoin network time drift and the unpreditable nature of finding new blocks.

createClosingPayment Source #

Arguments

:: (ToChangeOutFee fee, HasFee fee) 
=> ClientPayChanI BtcSig

Client state

-> Address

Client change address

-> fee

Settlement transaction fee (which equals value of closing payment)

-> (ClientPayChanI BtcSig, SignedPayment, BtcAmount)

Closed state; closing payment; actual fee (capped to remaining channel value)

acceptClosingPayment Source #

Arguments

:: MonadTime m 
=> PaymentData

Payment to verify and register

-> ServerPayChanI kd

Receiver state object

-> m (Either PayChanError (ClosedServerChanI kd)) 

Accept the payment that closes the payment channel. The payment accepted here is allowed to have a different client change address from that found in the state. | NB: Throws BadSignatureInState on invalid old/in-state payment.

getSignedSettlementTx :: forall signKey coi kd. DeriveChangeOut SignedPayment coi signKey ChanParams => ServerPayChanI kd -> coi -> SignM signKey (Either ReceiverError SignedTx) Source #

The value transmitted over the channel is settled when this transaction is in the Blockchain. The receiver will want to make sure a transaction produced by this function is included in a Bitcoin block before the refund transaction becomes valid (see getRefundBitcoinTx). The sender can only close the channel before expiration by requesting this transaction from the receiver and publishing it to the Bitcoin network.

closedGetSettlementTxSimple Source #

Arguments

:: PrvKeyC 
-> ClosedServerChanI a

Produced by acceptClosingPayment

-> Address

Receiver destination address. Funds sent over the channel will be sent to this address, the rest back to the client change address (an argument to channelWithInitialPaymentOf).

-> SatoshisPerByte

Minimum transaction fee

-> DustPolicy

Whether to keep or drop receiver change output if below dust limit

-> Either ReceiverError SettleTx

Settling Bitcoin transaction

Get the settlement tx for a ClosedServerChanI, where the closing payment pays the Bitcoin transaction fee

closedGetSettlementTxDerive :: DeriveChangeOut SignedPayment (TxFee, DustPolicy) signKey ChanParams => ClosedServerChanI a -> SatoshisPerByte -> DustPolicy -> SignM signKey (Either ReceiverError SettleTx) Source #

Same as closedGetSettlementTx, but allow more advanced signing types

data DustPolicy Source #

Constructors

KeepDust 
DropDust 

Instances

Eq DustPolicy Source # 
Show DustPolicy Source # 
Generic DustPolicy Source # 

Associated Types

type Rep DustPolicy :: * -> * #

ToJSON DustPolicy Source # 
FromJSON DustPolicy Source # 
Serialize DustPolicy Source # 
Default DustPolicy Source # 

Methods

def :: DustPolicy #

NFData DustPolicy Source # 

Methods

rnf :: DustPolicy -> () #

(SpendCondition r, IsTxLike tx t r sd) => DeriveChangeOut (tx t r sd) (TxFee, DustPolicy) () r Source # 

Methods

createChangeOut :: tx t r sd -> () -> (TxFee, DustPolicy) -> ChangeOut 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 DustPolicy Source # 
type Rep DustPolicy = D1 (MetaData "DustPolicy" "Bitcoin.Types.Tx" "bitcoin-payment-channel-1.2.0.0-7YwDEKAOCp2BNoMt0JxEOM" False) ((:+:) (C1 (MetaCons "KeepDust" PrefixI False) U1) (C1 (MetaCons "DropDust" PrefixI False) U1))

class HasFee fee => ToChangeOutFee fee where Source #

Minimal complete definition

mkChangeFee

Methods

mkChangeFee :: fee -> TxFee Source #

Instances

ToChangeOutFee BtcAmount Source # 

Methods

mkChangeFee :: BtcAmount -> TxFee Source #

ToChangeOutFee SatoshisPerByte Source # 

Methods

mkChangeFee :: SatoshisPerByte -> TxFee Source #

type RefundTx = BtcTx P2SH ChanParams RefundScriptSig Source #

type SettleTx = BtcTx P2SH ChanParams PaymentScriptSig Source #

Types

RESTful Bitcoin Payment Channel Protocol