byron-spec-ledger-1.0.1.0: Executable specification of Cardano ledger
Safe HaskellSafe-Inferred
LanguageHaskell2010

Byron.Spec.Ledger.UTxO

Synopsis

Documentation

newtype TxId Source #

A unique ID of a transaction, which is computable from the transaction.

Constructors

TxId 

Fields

Instances

Instances details
Data TxId Source # 
Instance details

Defined in Byron.Spec.Ledger.UTxO

Methods

gfoldl ∷ (∀ d b. Data d ⇒ c (d → b) → d → c b) → (∀ g. g → c g) → TxId → c TxId #

gunfold ∷ (∀ b r. Data b ⇒ c (b → r) → c r) → (∀ r. r → c r) → Constr → c TxId #

toConstrTxId → Constr #

dataTypeOfTxIdDataType #

dataCast1Typeable t ⇒ (∀ d. Data d ⇒ c (t d)) → Maybe (c TxId) #

dataCast2Typeable t ⇒ (∀ d e. (Data d, Data e) ⇒ c (t d e)) → Maybe (c TxId) #

gmapT ∷ (∀ b. Data b ⇒ b → b) → TxIdTxId #

gmapQl ∷ (r → r' → r) → r → (∀ d. Data d ⇒ d → r') → TxId → r #

gmapQr ∷ ∀ r r'. (r' → r → r) → r → (∀ d. Data d ⇒ d → r') → TxId → r #

gmapQ ∷ (∀ d. Data d ⇒ d → u) → TxId → [u] #

gmapQiInt → (∀ d. Data d ⇒ d → u) → TxId → u #

gmapMMonad m ⇒ (∀ d. Data d ⇒ d → m d) → TxId → m TxId #

gmapMpMonadPlus m ⇒ (∀ d. Data d ⇒ d → m d) → TxId → m TxId #

gmapMoMonadPlus m ⇒ (∀ d. Data d ⇒ d → m d) → TxId → m TxId #

Generic TxId Source # 
Instance details

Defined in Byron.Spec.Ledger.UTxO

Associated Types

type Rep TxIdTypeType #

Methods

fromTxIdRep TxId x #

toRep TxId x → TxId #

Show TxId Source # 
Instance details

Defined in Byron.Spec.Ledger.UTxO

Methods

showsPrecIntTxIdShowS #

showTxIdString #

showList ∷ [TxId] → ShowS #

HasTypeReps TxId Source # 
Instance details

Defined in Byron.Spec.Ledger.UTxO

Methods

typeRepsTxIdSeq TypeRep Source #

Eq TxId Source # 
Instance details

Defined in Byron.Spec.Ledger.UTxO

Methods

(==)TxIdTxIdBool #

(/=)TxIdTxIdBool #

Ord TxId Source # 
Instance details

Defined in Byron.Spec.Ledger.UTxO

Methods

compareTxIdTxIdOrdering #

(<)TxIdTxIdBool #

(<=)TxIdTxIdBool #

(>)TxIdTxIdBool #

(>=)TxIdTxIdBool #

maxTxIdTxIdTxId #

minTxIdTxIdTxId #

Hashable TxId Source # 
Instance details

Defined in Byron.Spec.Ledger.UTxO

Methods

hashWithSaltIntTxIdInt Source #

hashTxIdInt Source #

NoThunks TxId Source # 
Instance details

Defined in Byron.Spec.Ledger.UTxO

type Rep TxId Source # 
Instance details

Defined in Byron.Spec.Ledger.UTxO

type Rep TxId = D1 ('MetaData "TxId" "Byron.Spec.Ledger.UTxO" "byron-spec-ledger-1.0.1.0-inplace" 'True) (C1 ('MetaCons "TxId" 'PrefixI 'True) (S1 ('MetaSel ('Just "getTxId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Hash)))

data TxIn Source #

The input of a UTxO.

  • TODO - is it okay to use list indices instead of implementing the Ix Type?

Constructors

TxIn TxId Natural 

Instances

Instances details
Data TxIn Source # 
Instance details

Defined in Byron.Spec.Ledger.UTxO

Methods

gfoldl ∷ (∀ d b. Data d ⇒ c (d → b) → d → c b) → (∀ g. g → c g) → TxIn → c TxIn #

gunfold ∷ (∀ b r. Data b ⇒ c (b → r) → c r) → (∀ r. r → c r) → Constr → c TxIn #

toConstrTxIn → Constr #

dataTypeOfTxInDataType #

dataCast1Typeable t ⇒ (∀ d. Data d ⇒ c (t d)) → Maybe (c TxIn) #

dataCast2Typeable t ⇒ (∀ d e. (Data d, Data e) ⇒ c (t d e)) → Maybe (c TxIn) #

gmapT ∷ (∀ b. Data b ⇒ b → b) → TxInTxIn #

gmapQl ∷ (r → r' → r) → r → (∀ d. Data d ⇒ d → r') → TxIn → r #

gmapQr ∷ ∀ r r'. (r' → r → r) → r → (∀ d. Data d ⇒ d → r') → TxIn → r #

gmapQ ∷ (∀ d. Data d ⇒ d → u) → TxIn → [u] #

gmapQiInt → (∀ d. Data d ⇒ d → u) → TxIn → u #

gmapMMonad m ⇒ (∀ d. Data d ⇒ d → m d) → TxIn → m TxIn #

gmapMpMonadPlus m ⇒ (∀ d. Data d ⇒ d → m d) → TxIn → m TxIn #

gmapMoMonadPlus m ⇒ (∀ d. Data d ⇒ d → m d) → TxIn → m TxIn #

Generic TxIn Source # 
Instance details

Defined in Byron.Spec.Ledger.UTxO

Associated Types

type Rep TxInTypeType #

Methods

fromTxInRep TxIn x #

toRep TxIn x → TxIn #

Show TxIn Source # 
Instance details

Defined in Byron.Spec.Ledger.UTxO

Methods

showsPrecIntTxInShowS #

showTxInString #

showList ∷ [TxIn] → ShowS #

HasTypeReps TxIn Source # 
Instance details

Defined in Byron.Spec.Ledger.UTxO

Methods

typeRepsTxInSeq TypeRep Source #

Eq TxIn Source # 
Instance details

Defined in Byron.Spec.Ledger.UTxO

Methods

(==)TxInTxInBool #

(/=)TxInTxInBool #

Ord TxIn Source # 
Instance details

Defined in Byron.Spec.Ledger.UTxO

Methods

compareTxInTxInOrdering #

(<)TxInTxInBool #

(<=)TxInTxInBool #

(>)TxInTxInBool #

(>=)TxInTxInBool #

maxTxInTxInTxIn #

minTxInTxInTxIn #

Hashable TxIn Source # 
Instance details

Defined in Byron.Spec.Ledger.UTxO

Methods

hashWithSaltIntTxInInt Source #

hashTxInInt Source #

NoThunks TxIn Source # 
Instance details

Defined in Byron.Spec.Ledger.UTxO

type Rep TxIn Source # 
Instance details

Defined in Byron.Spec.Ledger.UTxO

type Rep TxIn = D1 ('MetaData "TxIn" "Byron.Spec.Ledger.UTxO" "byron-spec-ledger-1.0.1.0-inplace" 'False) (C1 ('MetaCons "TxIn" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 TxId) :*: S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Natural)))

data TxOut Source #

The output of a UTxO.

Constructors

TxOut 

Fields

Instances

Instances details
Data TxOut Source # 
Instance details

Defined in Byron.Spec.Ledger.UTxO

Methods

gfoldl ∷ (∀ d b. Data d ⇒ c (d → b) → d → c b) → (∀ g. g → c g) → TxOut → c TxOut #

gunfold ∷ (∀ b r. Data b ⇒ c (b → r) → c r) → (∀ r. r → c r) → Constr → c TxOut #

toConstrTxOut → Constr #

dataTypeOfTxOutDataType #

dataCast1Typeable t ⇒ (∀ d. Data d ⇒ c (t d)) → Maybe (c TxOut) #

dataCast2Typeable t ⇒ (∀ d e. (Data d, Data e) ⇒ c (t d e)) → Maybe (c TxOut) #

gmapT ∷ (∀ b. Data b ⇒ b → b) → TxOutTxOut #

gmapQl ∷ (r → r' → r) → r → (∀ d. Data d ⇒ d → r') → TxOut → r #

gmapQr ∷ ∀ r r'. (r' → r → r) → r → (∀ d. Data d ⇒ d → r') → TxOut → r #

gmapQ ∷ (∀ d. Data d ⇒ d → u) → TxOut → [u] #

gmapQiInt → (∀ d. Data d ⇒ d → u) → TxOut → u #

gmapMMonad m ⇒ (∀ d. Data d ⇒ d → m d) → TxOut → m TxOut #

gmapMpMonadPlus m ⇒ (∀ d. Data d ⇒ d → m d) → TxOut → m TxOut #

gmapMoMonadPlus m ⇒ (∀ d. Data d ⇒ d → m d) → TxOut → m TxOut #

Generic TxOut Source # 
Instance details

Defined in Byron.Spec.Ledger.UTxO

Associated Types

type Rep TxOutTypeType #

Methods

fromTxOutRep TxOut x #

toRep TxOut x → TxOut #

Show TxOut Source # 
Instance details

Defined in Byron.Spec.Ledger.UTxO

Methods

showsPrecIntTxOutShowS #

showTxOutString #

showList ∷ [TxOut] → ShowS #

HasTypeReps TxOut Source # 
Instance details

Defined in Byron.Spec.Ledger.UTxO

Methods

typeRepsTxOutSeq TypeRep Source #

Eq TxOut Source # 
Instance details

Defined in Byron.Spec.Ledger.UTxO

Methods

(==)TxOutTxOutBool #

(/=)TxOutTxOutBool #

Ord TxOut Source # 
Instance details

Defined in Byron.Spec.Ledger.UTxO

Methods

compareTxOutTxOutOrdering #

(<)TxOutTxOutBool #

(<=)TxOutTxOutBool #

(>)TxOutTxOutBool #

(>=)TxOutTxOutBool #

maxTxOutTxOutTxOut #

minTxOutTxOutTxOut #

Hashable TxOut Source # 
Instance details

Defined in Byron.Spec.Ledger.UTxO

Methods

hashWithSaltIntTxOutInt Source #

hashTxOutInt Source #

NoThunks TxOut Source # 
Instance details

Defined in Byron.Spec.Ledger.UTxO

type Rep TxOut Source # 
Instance details

Defined in Byron.Spec.Ledger.UTxO

type Rep TxOut = D1 ('MetaData "TxOut" "Byron.Spec.Ledger.UTxO" "byron-spec-ledger-1.0.1.0-inplace" 'False) (C1 ('MetaCons "TxOut" 'PrefixI 'True) (S1 ('MetaSel ('Just "addr") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Addr) :*: S1 ('MetaSel ('Just "value") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Lovelace)))

newtype UTxO Source #

The unspent transaction outputs.

Constructors

UTxO 

Fields

Instances

Instances details
Data UTxO Source # 
Instance details

Defined in Byron.Spec.Ledger.UTxO

Methods

gfoldl ∷ (∀ d b. Data d ⇒ c (d → b) → d → c b) → (∀ g. g → c g) → UTxO → c UTxO #

gunfold ∷ (∀ b r. Data b ⇒ c (b → r) → c r) → (∀ r. r → c r) → Constr → c UTxO #

toConstrUTxO → Constr #

dataTypeOfUTxODataType #

dataCast1Typeable t ⇒ (∀ d. Data d ⇒ c (t d)) → Maybe (c UTxO) #

dataCast2Typeable t ⇒ (∀ d e. (Data d, Data e) ⇒ c (t d e)) → Maybe (c UTxO) #

gmapT ∷ (∀ b. Data b ⇒ b → b) → UTxOUTxO #

gmapQl ∷ (r → r' → r) → r → (∀ d. Data d ⇒ d → r') → UTxO → r #

gmapQr ∷ ∀ r r'. (r' → r → r) → r → (∀ d. Data d ⇒ d → r') → UTxO → r #

gmapQ ∷ (∀ d. Data d ⇒ d → u) → UTxO → [u] #

gmapQiInt → (∀ d. Data d ⇒ d → u) → UTxO → u #

gmapMMonad m ⇒ (∀ d. Data d ⇒ d → m d) → UTxO → m UTxO #

gmapMpMonadPlus m ⇒ (∀ d. Data d ⇒ d → m d) → UTxO → m UTxO #

gmapMoMonadPlus m ⇒ (∀ d. Data d ⇒ d → m d) → UTxO → m UTxO #

Monoid UTxO Source # 
Instance details

Defined in Byron.Spec.Ledger.UTxO

Methods

memptyUTxO #

mappendUTxOUTxOUTxO #

mconcat ∷ [UTxO] → UTxO #

Semigroup UTxO Source # 
Instance details

Defined in Byron.Spec.Ledger.UTxO

Methods

(<>)UTxOUTxOUTxO #

sconcatNonEmpty UTxOUTxO #

stimesIntegral b ⇒ b → UTxOUTxO #

Show UTxO Source # 
Instance details

Defined in Byron.Spec.Ledger.UTxO

Methods

showsPrecIntUTxOShowS #

showUTxOString #

showList ∷ [UTxO] → ShowS #

Relation UTxO Source # 
Instance details

Defined in Byron.Spec.Ledger.UTxO

Associated Types

type Domain UTxO Source #

type Range UTxO Source #

Methods

singletonDomain UTxORange UTxOUTxO Source #

domUTxOSet (Domain UTxO) Source #

rangeUTxOSet (Range UTxO) Source #

(◁) ∷ (Ord (Domain UTxO), Foldable f) ⇒ f (Domain UTxO) → UTxOUTxO Source #

(<|) ∷ (Ord (Domain UTxO), Foldable f) ⇒ f (Domain UTxO) → UTxOUTxO Source #

(⋪) ∷ (Ord (Domain UTxO), Foldable f) ⇒ f (Domain UTxO) → UTxOUTxO Source #

(</|) ∷ (Ord (Domain UTxO), Foldable f) ⇒ f (Domain UTxO) → UTxOUTxO Source #

(▷)UTxOSet (Range UTxO) → UTxO Source #

(|>)UTxOSet (Range UTxO) → UTxO Source #

(⋫)UTxOSet (Range UTxO) → UTxO Source #

(|/>)UTxOSet (Range UTxO) → UTxO Source #

(∪)UTxOUTxOUTxO Source #

(⨃) ∷ (Ord (Domain UTxO), Ord (Range UTxO), Foldable f) ⇒ UTxO → f (Domain UTxO, Range UTxO) → UTxO Source #

(<=◁)Domain UTxOUTxOUTxO Source #

(▷<=)UTxORange UTxOUTxO Source #

(▷>=)UTxORange UTxOUTxO Source #

sizeIntegral n ⇒ UTxO → n Source #

Eq UTxO Source # 
Instance details

Defined in Byron.Spec.Ledger.UTxO

Methods

(==)UTxOUTxOBool #

(/=)UTxOUTxOBool #

NoThunks UTxO Source # 
Instance details

Defined in Byron.Spec.Ledger.UTxO

type Domain UTxO Source # 
Instance details

Defined in Byron.Spec.Ledger.UTxO

type Range UTxO Source # 
Instance details

Defined in Byron.Spec.Ledger.UTxO

mapUTxOValues ∷ (LovelaceLovelace) → UTxOUTxO Source #

Apply function uniformly across all outputs

fromTxOuts ∷ [TxOut] → UTxO Source #

Construct a UTxO from initial TxOuts

data TxBody Source #

A raw transaction

Constructors

TxBody 

Fields

Instances

Instances details
Data TxBody Source # 
Instance details

Defined in Byron.Spec.Ledger.UTxO

Methods

gfoldl ∷ (∀ d b. Data d ⇒ c (d → b) → d → c b) → (∀ g. g → c g) → TxBody → c TxBody #

gunfold ∷ (∀ b r. Data b ⇒ c (b → r) → c r) → (∀ r. r → c r) → Constr → c TxBody #

toConstrTxBody → Constr #

dataTypeOfTxBodyDataType #

dataCast1Typeable t ⇒ (∀ d. Data d ⇒ c (t d)) → Maybe (c TxBody) #

dataCast2Typeable t ⇒ (∀ d e. (Data d, Data e) ⇒ c (t d e)) → Maybe (c TxBody) #

gmapT ∷ (∀ b. Data b ⇒ b → b) → TxBodyTxBody #

gmapQl ∷ (r → r' → r) → r → (∀ d. Data d ⇒ d → r') → TxBody → r #

gmapQr ∷ ∀ r r'. (r' → r → r) → r → (∀ d. Data d ⇒ d → r') → TxBody → r #

gmapQ ∷ (∀ d. Data d ⇒ d → u) → TxBody → [u] #

gmapQiInt → (∀ d. Data d ⇒ d → u) → TxBody → u #

gmapMMonad m ⇒ (∀ d. Data d ⇒ d → m d) → TxBody → m TxBody #

gmapMpMonadPlus m ⇒ (∀ d. Data d ⇒ d → m d) → TxBody → m TxBody #

gmapMoMonadPlus m ⇒ (∀ d. Data d ⇒ d → m d) → TxBody → m TxBody #

Generic TxBody Source # 
Instance details

Defined in Byron.Spec.Ledger.UTxO

Associated Types

type Rep TxBodyTypeType #

Methods

fromTxBodyRep TxBody x #

toRep TxBody x → TxBody #

Show TxBody Source # 
Instance details

Defined in Byron.Spec.Ledger.UTxO

Methods

showsPrecIntTxBodyShowS #

showTxBodyString #

showList ∷ [TxBody] → ShowS #

HasHash TxBody Source # 
Instance details

Defined in Byron.Spec.Ledger.UTxO

Methods

hashTxBodyHash Source #

HasTypeReps TxBody Source # 
Instance details

Defined in Byron.Spec.Ledger.UTxO

Methods

typeRepsTxBodySeq TypeRep Source #

Eq TxBody Source # 
Instance details

Defined in Byron.Spec.Ledger.UTxO

Methods

(==)TxBodyTxBodyBool #

(/=)TxBodyTxBodyBool #

Ord TxBody Source # 
Instance details

Defined in Byron.Spec.Ledger.UTxO

Methods

compareTxBodyTxBodyOrdering #

(<)TxBodyTxBodyBool #

(<=)TxBodyTxBodyBool #

(>)TxBodyTxBodyBool #

(>=)TxBodyTxBodyBool #

maxTxBodyTxBodyTxBody #

minTxBodyTxBodyTxBody #

Hashable TxBody Source # 
Instance details

Defined in Byron.Spec.Ledger.UTxO

Methods

hashWithSaltIntTxBodyInt Source #

hashTxBodyInt Source #

NoThunks TxBody Source # 
Instance details

Defined in Byron.Spec.Ledger.UTxO

type Rep TxBody Source # 
Instance details

Defined in Byron.Spec.Ledger.UTxO

type Rep TxBody = D1 ('MetaData "TxBody" "Byron.Spec.Ledger.UTxO" "byron-spec-ledger-1.0.1.0-inplace" 'False) (C1 ('MetaCons "TxBody" 'PrefixI 'True) (S1 ('MetaSel ('Just "inputs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [TxIn]) :*: S1 ('MetaSel ('Just "outputs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [TxOut])))

txValueTxBodyLovelace Source #

Total value of a transaction.

txinsTxBody → [TxIn] Source #

Compute the UTxO inputs of a transaction.

txoutsTxBodyUTxO Source #

Compute the UTxO outputs of a transaction.

balanceUTxOLovelace Source #

Determine the total balance contained in the UTxO.

txsizeTxInt Source #

data Wit Source #

Proof/Witness that a transaction is authorized by the given key holder.

Constructors

Wit VKey (Sig TxBody) 

Instances

Instances details
Data Wit Source # 
Instance details

Defined in Byron.Spec.Ledger.UTxO

Methods

gfoldl ∷ (∀ d b. Data d ⇒ c (d → b) → d → c b) → (∀ g. g → c g) → Wit → c Wit #

gunfold ∷ (∀ b r. Data b ⇒ c (b → r) → c r) → (∀ r. r → c r) → Constr → c Wit #

toConstrWit → Constr #

dataTypeOfWitDataType #

dataCast1Typeable t ⇒ (∀ d. Data d ⇒ c (t d)) → Maybe (c Wit) #

dataCast2Typeable t ⇒ (∀ d e. (Data d, Data e) ⇒ c (t d e)) → Maybe (c Wit) #

gmapT ∷ (∀ b. Data b ⇒ b → b) → WitWit #

gmapQl ∷ (r → r' → r) → r → (∀ d. Data d ⇒ d → r') → Wit → r #

gmapQr ∷ ∀ r r'. (r' → r → r) → r → (∀ d. Data d ⇒ d → r') → Wit → r #

gmapQ ∷ (∀ d. Data d ⇒ d → u) → Wit → [u] #

gmapQiInt → (∀ d. Data d ⇒ d → u) → Wit → u #

gmapMMonad m ⇒ (∀ d. Data d ⇒ d → m d) → Wit → m Wit #

gmapMpMonadPlus m ⇒ (∀ d. Data d ⇒ d → m d) → Wit → m Wit #

gmapMoMonadPlus m ⇒ (∀ d. Data d ⇒ d → m d) → Wit → m Wit #

Generic Wit Source # 
Instance details

Defined in Byron.Spec.Ledger.UTxO

Associated Types

type Rep WitTypeType #

Methods

fromWitRep Wit x #

toRep Wit x → Wit #

Show Wit Source # 
Instance details

Defined in Byron.Spec.Ledger.UTxO

Methods

showsPrecIntWitShowS #

showWitString #

showList ∷ [Wit] → ShowS #

HasTypeReps Wit Source # 
Instance details

Defined in Byron.Spec.Ledger.UTxO

Methods

typeRepsWitSeq TypeRep Source #

Eq Wit Source # 
Instance details

Defined in Byron.Spec.Ledger.UTxO

Methods

(==)WitWitBool #

(/=)WitWitBool #

Ord Wit Source # 
Instance details

Defined in Byron.Spec.Ledger.UTxO

Methods

compareWitWitOrdering #

(<)WitWitBool #

(<=)WitWitBool #

(>)WitWitBool #

(>=)WitWitBool #

maxWitWitWit #

minWitWitWit #

Hashable Wit Source # 
Instance details

Defined in Byron.Spec.Ledger.UTxO

Methods

hashWithSaltIntWitInt Source #

hashWitInt Source #

NoThunks Wit Source # 
Instance details

Defined in Byron.Spec.Ledger.UTxO

type Rep Wit Source # 
Instance details

Defined in Byron.Spec.Ledger.UTxO

type Rep Wit = D1 ('MetaData "Wit" "Byron.Spec.Ledger.UTxO" "byron-spec-ledger-1.0.1.0-inplace" 'False) (C1 ('MetaCons "Wit" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 VKey) :*: S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Sig TxBody))))

data Tx Source #

A fully formed transaction.

Constructors

Tx 

Fields

Instances

Instances details
Data Tx Source # 
Instance details

Defined in Byron.Spec.Ledger.UTxO

Methods

gfoldl ∷ (∀ d b. Data d ⇒ c (d → b) → d → c b) → (∀ g. g → c g) → Tx → c Tx #

gunfold ∷ (∀ b r. Data b ⇒ c (b → r) → c r) → (∀ r. r → c r) → Constr → c Tx #

toConstrTx → Constr #

dataTypeOfTxDataType #

dataCast1Typeable t ⇒ (∀ d. Data d ⇒ c (t d)) → Maybe (c Tx) #

dataCast2Typeable t ⇒ (∀ d e. (Data d, Data e) ⇒ c (t d e)) → Maybe (c Tx) #

gmapT ∷ (∀ b. Data b ⇒ b → b) → TxTx #

gmapQl ∷ (r → r' → r) → r → (∀ d. Data d ⇒ d → r') → Tx → r #

gmapQr ∷ ∀ r r'. (r' → r → r) → r → (∀ d. Data d ⇒ d → r') → Tx → r #

gmapQ ∷ (∀ d. Data d ⇒ d → u) → Tx → [u] #

gmapQiInt → (∀ d. Data d ⇒ d → u) → Tx → u #

gmapMMonad m ⇒ (∀ d. Data d ⇒ d → m d) → Tx → m Tx #

gmapMpMonadPlus m ⇒ (∀ d. Data d ⇒ d → m d) → Tx → m Tx #

gmapMoMonadPlus m ⇒ (∀ d. Data d ⇒ d → m d) → Tx → m Tx #

Generic Tx Source # 
Instance details

Defined in Byron.Spec.Ledger.UTxO

Associated Types

type Rep TxTypeType #

Methods

fromTxRep Tx x #

toRep Tx x → Tx #

Show Tx Source # 
Instance details

Defined in Byron.Spec.Ledger.UTxO

Methods

showsPrecIntTxShowS #

showTxString #

showList ∷ [Tx] → ShowS #

HasTypeReps Tx Source # 
Instance details

Defined in Byron.Spec.Ledger.UTxO

Methods

typeRepsTxSeq TypeRep Source #

Eq Tx Source # 
Instance details

Defined in Byron.Spec.Ledger.UTxO

Methods

(==)TxTxBool #

(/=)TxTxBool #

Hashable Tx Source # 
Instance details

Defined in Byron.Spec.Ledger.UTxO

Methods

hashWithSaltIntTxInt Source #

hashTxInt Source #

NoThunks Tx Source # 
Instance details

Defined in Byron.Spec.Ledger.UTxO

HasHash [Tx] Source # 
Instance details

Defined in Byron.Spec.Ledger.UTxO

Methods

hash ∷ [Tx] → Hash Source #

type Rep Tx Source # 
Instance details

Defined in Byron.Spec.Ledger.UTxO

type Rep Tx = D1 ('MetaData "Tx" "Byron.Spec.Ledger.UTxO" "byron-spec-ledger-1.0.1.0-inplace" 'False) (C1 ('MetaCons "Tx" 'PrefixI 'True) (S1 ('MetaSel ('Just "body") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 TxBody) :*: S1 ('MetaSel ('Just "witnesses") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Wit])))

makeWitnessKeyPairTxBodyWit Source #

Create a witness for transaction