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

Haskoin.Transaction.Common

Contents

Description

Code related to transactions parsing and serialization.

Synopsis

Transactions

data Tx Source #

Data type representing a transaction.

Constructors

Tx 

Fields

Instances

Instances details
FromJSON Tx Source # 
Instance details

Defined in Haskoin.Transaction.Common

Methods

parseJSON :: Value -> Parser Tx

parseJSONList :: Value -> Parser [Tx]

omittedField :: Maybe Tx

ToJSON Tx Source # 
Instance details

Defined in Haskoin.Transaction.Common

Methods

toJSON :: Tx -> Value

toEncoding :: Tx -> Encoding

toJSONList :: [Tx] -> Value

toEncodingList :: [Tx] -> Encoding

omitField :: Tx -> Bool

IsString Tx Source # 
Instance details

Defined in Haskoin.Transaction.Common

Methods

fromString :: String -> Tx #

Generic Tx Source # 
Instance details

Defined in Haskoin.Transaction.Common

Associated Types

type Rep Tx :: Type -> Type #

Methods

from :: Tx -> Rep Tx x #

to :: Rep Tx x -> Tx #

Read Tx Source # 
Instance details

Defined in Haskoin.Transaction.Common

Show Tx Source # 
Instance details

Defined in Haskoin.Transaction.Common

Methods

showsPrec :: Int -> Tx -> ShowS #

show :: Tx -> String #

showList :: [Tx] -> ShowS #

Binary Tx Source # 
Instance details

Defined in Haskoin.Transaction.Common

Methods

put :: Tx -> Put #

get :: Get Tx #

putList :: [Tx] -> Put #

Serial Tx Source # 
Instance details

Defined in Haskoin.Transaction.Common

Methods

serialize :: MonadPut m => Tx -> m ()

deserialize :: MonadGet m => m Tx

Serialize Tx Source # 
Instance details

Defined in Haskoin.Transaction.Common

Methods

put :: Putter Tx

get :: Get Tx

NFData Tx Source # 
Instance details

Defined in Haskoin.Transaction.Common

Methods

rnf :: Tx -> () #

Eq Tx Source # 
Instance details

Defined in Haskoin.Transaction.Common

Methods

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

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

Ord Tx Source # 
Instance details

Defined in Haskoin.Transaction.Common

Methods

compare :: Tx -> Tx -> Ordering #

(<) :: Tx -> Tx -> Bool #

(<=) :: Tx -> Tx -> Bool #

(>) :: Tx -> Tx -> Bool #

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

max :: Tx -> Tx -> Tx #

min :: Tx -> Tx -> Tx #

Hashable Tx Source # 
Instance details

Defined in Haskoin.Transaction.Common

Methods

hashWithSalt :: Int -> Tx -> Int

hash :: Tx -> Int

type Rep Tx Source # 
Instance details

Defined in Haskoin.Transaction.Common

data TxIn Source #

Data type representing a transaction input.

Constructors

TxIn 

Fields

Instances

Instances details
FromJSON TxIn Source # 
Instance details

Defined in Haskoin.Transaction.Common

Methods

parseJSON :: Value -> Parser TxIn

parseJSONList :: Value -> Parser [TxIn]

omittedField :: Maybe TxIn

ToJSON TxIn Source # 
Instance details

Defined in Haskoin.Transaction.Common

Methods

toJSON :: TxIn -> Value

toEncoding :: TxIn -> Encoding

toJSONList :: [TxIn] -> Value

toEncodingList :: [TxIn] -> Encoding

omitField :: TxIn -> Bool

Generic TxIn Source # 
Instance details

Defined in Haskoin.Transaction.Common

Associated Types

type Rep TxIn :: Type -> Type #

Methods

from :: TxIn -> Rep TxIn x #

to :: Rep TxIn x -> TxIn #

Read TxIn Source # 
Instance details

Defined in Haskoin.Transaction.Common

Show TxIn Source # 
Instance details

Defined in Haskoin.Transaction.Common

Methods

showsPrec :: Int -> TxIn -> ShowS #

show :: TxIn -> String #

showList :: [TxIn] -> ShowS #

Binary TxIn Source # 
Instance details

Defined in Haskoin.Transaction.Common

Methods

put :: TxIn -> Put #

get :: Get TxIn #

putList :: [TxIn] -> Put #

Serial TxIn Source # 
Instance details

Defined in Haskoin.Transaction.Common

Methods

serialize :: MonadPut m => TxIn -> m ()

deserialize :: MonadGet m => m TxIn

Serialize TxIn Source # 
Instance details

Defined in Haskoin.Transaction.Common

Methods

put :: Putter TxIn

get :: Get TxIn

NFData TxIn Source # 
Instance details

Defined in Haskoin.Transaction.Common

Methods

rnf :: TxIn -> () #

Eq TxIn Source # 
Instance details

Defined in Haskoin.Transaction.Common

Methods

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

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

Ord TxIn Source # 
Instance details

Defined in Haskoin.Transaction.Common

Methods

compare :: TxIn -> TxIn -> Ordering #

(<) :: TxIn -> TxIn -> Bool #

(<=) :: TxIn -> TxIn -> Bool #

(>) :: TxIn -> TxIn -> Bool #

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

max :: TxIn -> TxIn -> TxIn #

min :: TxIn -> TxIn -> TxIn #

Hashable TxIn Source # 
Instance details

Defined in Haskoin.Transaction.Common

Methods

hashWithSalt :: Int -> TxIn -> Int

hash :: TxIn -> Int

type Rep TxIn Source # 
Instance details

Defined in Haskoin.Transaction.Common

type Rep TxIn = D1 ('MetaData "TxIn" "Haskoin.Transaction.Common" "haskoin-core-0.22.0-inplace" 'False) (C1 ('MetaCons "TxIn" 'PrefixI 'True) (S1 ('MetaSel ('Just "prevOutput") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 OutPoint) :*: (S1 ('MetaSel ('Just "scriptInput") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ByteString) :*: S1 ('MetaSel ('Just "txInSequence") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word32))))

data TxOut Source #

Data type representing a transaction output.

Constructors

TxOut 

Fields

Instances

Instances details
FromJSON TxOut Source # 
Instance details

Defined in Haskoin.Transaction.Common

Methods

parseJSON :: Value -> Parser TxOut

parseJSONList :: Value -> Parser [TxOut]

omittedField :: Maybe TxOut

ToJSON TxOut Source # 
Instance details

Defined in Haskoin.Transaction.Common

Methods

toJSON :: TxOut -> Value

toEncoding :: TxOut -> Encoding

toJSONList :: [TxOut] -> Value

toEncodingList :: [TxOut] -> Encoding

omitField :: TxOut -> Bool

Generic TxOut Source # 
Instance details

Defined in Haskoin.Transaction.Common

Associated Types

type Rep TxOut :: Type -> Type #

Methods

from :: TxOut -> Rep TxOut x #

to :: Rep TxOut x -> TxOut #

Read TxOut Source # 
Instance details

Defined in Haskoin.Transaction.Common

Show TxOut Source # 
Instance details

Defined in Haskoin.Transaction.Common

Methods

showsPrec :: Int -> TxOut -> ShowS #

show :: TxOut -> String #

showList :: [TxOut] -> ShowS #

Binary TxOut Source # 
Instance details

Defined in Haskoin.Transaction.Common

Methods

put :: TxOut -> Put #

get :: Get TxOut #

putList :: [TxOut] -> Put #

Serial TxOut Source # 
Instance details

Defined in Haskoin.Transaction.Common

Methods

serialize :: MonadPut m => TxOut -> m ()

deserialize :: MonadGet m => m TxOut

Serialize TxOut Source # 
Instance details

Defined in Haskoin.Transaction.Common

Methods

put :: Putter TxOut

get :: Get TxOut

NFData TxOut Source # 
Instance details

Defined in Haskoin.Transaction.Common

Methods

rnf :: TxOut -> () #

Eq TxOut Source # 
Instance details

Defined in Haskoin.Transaction.Common

Methods

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

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

Ord TxOut Source # 
Instance details

Defined in Haskoin.Transaction.Common

Methods

compare :: TxOut -> TxOut -> Ordering #

(<) :: TxOut -> TxOut -> Bool #

(<=) :: TxOut -> TxOut -> Bool #

(>) :: TxOut -> TxOut -> Bool #

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

max :: TxOut -> TxOut -> TxOut #

min :: TxOut -> TxOut -> TxOut #

Hashable TxOut Source # 
Instance details

Defined in Haskoin.Transaction.Common

Methods

hashWithSalt :: Int -> TxOut -> Int

hash :: TxOut -> Int

type Rep TxOut Source # 
Instance details

Defined in Haskoin.Transaction.Common

type Rep TxOut = D1 ('MetaData "TxOut" "Haskoin.Transaction.Common" "haskoin-core-0.22.0-inplace" 'False) (C1 ('MetaCons "TxOut" 'PrefixI 'True) (S1 ('MetaSel ('Just "outValue") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word64) :*: S1 ('MetaSel ('Just "scriptOutput") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ByteString)))

data OutPoint Source #

The OutPoint refers to a transaction output being spent.

Constructors

OutPoint 

Fields

Instances

Instances details
FromJSON OutPoint Source # 
Instance details

Defined in Haskoin.Transaction.Common

Methods

parseJSON :: Value -> Parser OutPoint

parseJSONList :: Value -> Parser [OutPoint]

omittedField :: Maybe OutPoint

ToJSON OutPoint Source # 
Instance details

Defined in Haskoin.Transaction.Common

Methods

toJSON :: OutPoint -> Value

toEncoding :: OutPoint -> Encoding

toJSONList :: [OutPoint] -> Value

toEncodingList :: [OutPoint] -> Encoding

omitField :: OutPoint -> Bool

Generic OutPoint Source # 
Instance details

Defined in Haskoin.Transaction.Common

Associated Types

type Rep OutPoint :: Type -> Type #

Methods

from :: OutPoint -> Rep OutPoint x #

to :: Rep OutPoint x -> OutPoint #

Read OutPoint Source # 
Instance details

Defined in Haskoin.Transaction.Common

Show OutPoint Source # 
Instance details

Defined in Haskoin.Transaction.Common

Binary OutPoint Source # 
Instance details

Defined in Haskoin.Transaction.Common

Methods

put :: OutPoint -> Put #

get :: Get OutPoint #

putList :: [OutPoint] -> Put #

Serial OutPoint Source # 
Instance details

Defined in Haskoin.Transaction.Common

Methods

serialize :: MonadPut m => OutPoint -> m ()

deserialize :: MonadGet m => m OutPoint

Serialize OutPoint Source # 
Instance details

Defined in Haskoin.Transaction.Common

Methods

put :: Putter OutPoint

get :: Get OutPoint

NFData OutPoint Source # 
Instance details

Defined in Haskoin.Transaction.Common

Methods

rnf :: OutPoint -> () #

Eq OutPoint Source # 
Instance details

Defined in Haskoin.Transaction.Common

Ord OutPoint Source # 
Instance details

Defined in Haskoin.Transaction.Common

Hashable OutPoint Source # 
Instance details

Defined in Haskoin.Transaction.Common

type Rep OutPoint Source # 
Instance details

Defined in Haskoin.Transaction.Common

type Rep OutPoint = D1 ('MetaData "OutPoint" "Haskoin.Transaction.Common" "haskoin-core-0.22.0-inplace" 'False) (C1 ('MetaCons "OutPoint" 'PrefixI 'True) (S1 ('MetaSel ('Just "outPointHash") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 TxHash) :*: S1 ('MetaSel ('Just "outPointIndex") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word32)))

newtype TxHash Source #

Transaction id: hash of transaction excluding witness data.

Constructors

TxHash 

Fields

Instances

Instances details
FromJSON TxHash Source # 
Instance details

Defined in Haskoin.Transaction.Common

Methods

parseJSON :: Value -> Parser TxHash

parseJSONList :: Value -> Parser [TxHash]

omittedField :: Maybe TxHash

ToJSON TxHash Source # 
Instance details

Defined in Haskoin.Transaction.Common

Methods

toJSON :: TxHash -> Value

toEncoding :: TxHash -> Encoding

toJSONList :: [TxHash] -> Value

toEncodingList :: [TxHash] -> Encoding

omitField :: TxHash -> Bool

IsString TxHash Source # 
Instance details

Defined in Haskoin.Transaction.Common

Methods

fromString :: String -> TxHash #

Generic TxHash Source # 
Instance details

Defined in Haskoin.Transaction.Common

Associated Types

type Rep TxHash :: Type -> Type #

Methods

from :: TxHash -> Rep TxHash x #

to :: Rep TxHash x -> TxHash #

Read TxHash Source # 
Instance details

Defined in Haskoin.Transaction.Common

Show TxHash Source # 
Instance details

Defined in Haskoin.Transaction.Common

Binary TxHash Source # 
Instance details

Defined in Haskoin.Transaction.Common

Methods

put :: TxHash -> Put #

get :: Get TxHash #

putList :: [TxHash] -> Put #

Serial TxHash Source # 
Instance details

Defined in Haskoin.Transaction.Common

Methods

serialize :: MonadPut m => TxHash -> m ()

deserialize :: MonadGet m => m TxHash

Serialize TxHash Source # 
Instance details

Defined in Haskoin.Transaction.Common

Methods

put :: Putter TxHash

get :: Get TxHash

NFData TxHash Source # 
Instance details

Defined in Haskoin.Transaction.Common

Methods

rnf :: TxHash -> () #

Eq TxHash Source # 
Instance details

Defined in Haskoin.Transaction.Common

Methods

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

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

Ord TxHash Source # 
Instance details

Defined in Haskoin.Transaction.Common

Hashable TxHash Source # 
Instance details

Defined in Haskoin.Transaction.Common

Methods

hashWithSalt :: Int -> TxHash -> Int

hash :: TxHash -> Int

type Rep TxHash Source # 
Instance details

Defined in Haskoin.Transaction.Common

type Rep TxHash = D1 ('MetaData "TxHash" "Haskoin.Transaction.Common" "haskoin-core-0.22.0-inplace" 'True) (C1 ('MetaCons "TxHash" 'PrefixI 'True) (S1 ('MetaSel ('Just "getTxHash") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Hash256)))

type WitnessData = [WitnessStack] Source #

Witness stack for SegWit transactions.

type WitnessStack = [WitnessStackItem] Source #

Witness stack for SegWit transactions.

type WitnessStackItem = ByteString Source #

Witness stack item for SegWit transactions.

txHash :: Tx -> TxHash Source #

Compute transaction hash.

hexToTxHash :: Text -> Maybe TxHash Source #

Convert transaction hash from hex, reversing bytes.

txHashToHex :: TxHash -> Text Source #

Convert transaction hash to hex form, reversing bytes.

nosigTxHash :: Tx -> TxHash Source #

Transaction hash excluding signatures.

nullOutPoint :: OutPoint Source #

Outpoint used in coinbase transactions.