| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Ledger.Tx
Synopsis
- data Language
- pubKeyHashTxOut :: Value -> PubKeyHash -> TxOut
- isPayToScriptOut :: TxOut -> Bool
- isPubKeyOut :: TxOut -> Bool
- txOutDatum :: TxOut -> Maybe DatumHash
- newtype TxId = TxId {}
- data ScriptTag
- data RedeemerPtr = RedeemerPtr ScriptTag Integer
- type Redeemers = Map RedeemerPtr Redeemer
- data TxOutRef = TxOutRef {
- txOutRefId :: TxId
- txOutRefIdx :: Integer
- data Versioned script = Versioned {
- unversioned :: script
- version :: Language
- type ReferenceScript = ReferenceScript BabbageEra
- data TxOutTx = TxOutTx {
- txOutTxTx :: Tx
- txOutTxOut :: TxOut
- data TxStripped = TxStripped {}
- data Tx = Tx {
- txInputs :: [TxInput]
- txReferenceInputs :: [TxInput]
- txCollateralInputs :: [TxInput]
- txOutputs :: [TxOut]
- txReturnCollateral :: Maybe TxOut
- txTotalCollateral :: Maybe Value
- txMint :: !Value
- txFee :: !Value
- txValidRange :: !SlotRange
- txMintingWitnesses :: MintingWitnessesMap
- txWithdrawals :: [Withdrawal]
- txCertificates :: [Certificate]
- txSignatures :: Map PubKey Signature
- txScripts :: ScriptsMap
- txData :: Map DatumHash Datum
- txMetadata :: Maybe BuiltinByteString
- type MintingWitnessesMap = Map MintingPolicyHash (Redeemer, Maybe (Versioned TxOutRef))
- type ScriptsMap = Map ScriptHash (Versioned Script)
- newtype TxOut = TxOut {}
- data Certificate = Certificate {}
- data Withdrawal = Withdrawal {}
- data TxInput = TxInput {
- txInputRef :: !TxOutRef
- txInputType :: !TxInputType
- data TxInputType
- data TxIn = TxIn {}
- data TxInType
- pubKeyTxIn :: TxOutRef -> TxIn
- scriptTxIn :: TxOutRef -> Versioned Validator -> Redeemer -> Maybe Datum -> TxIn
- inputRef :: Lens' TxInput TxOutRef
- inputType :: Lens' TxInput TxInputType
- inScripts :: TxIn -> Maybe (Versioned Validator, Redeemer, Maybe Datum)
- inRef :: Lens' TxInput TxOutRef
- inType :: Lens' TxInput TxInputType
- pubKeyTxInputs :: Fold [TxInput] TxInput
- scriptTxInputs :: Fold [TxInput] TxInput
- referenceScriptTxInputs :: Fold [TxInput] TxInput
- toSizedTxOut :: TxOut -> Sized (TxOut StandardBabbage)
- inputs :: Lens' Tx [TxInput]
- referenceInputs :: Lens' Tx [TxInput]
- collateralInputs :: Lens' Tx [TxInput]
- outputs :: Lens' Tx [TxOut]
- returnCollateral :: Lens' Tx (Maybe TxOut)
- totalCollateral :: Lens' Tx (Maybe Value)
- validRange :: Lens' Tx SlotRange
- signatures :: Lens' Tx (Map PubKey Signature)
- fee :: Lens' Tx Value
- mint :: Lens' Tx Value
- mintScripts :: Lens' Tx MintingWitnessesMap
- scriptWitnesses :: Lens' Tx ScriptsMap
- datumWitnesses :: Lens' Tx (Map DatumHash Datum)
- metadata :: Lens' Tx (Maybe BuiltinByteString)
- lookupSignature :: PubKey -> Tx -> Maybe Signature
- lookupDatum :: Tx -> DatumHash -> Maybe Datum
- validValuesTx :: Tx -> Bool
- txOutValue :: TxOut -> Value
- outValue :: Lens TxOut TxOut Value (TxOutValue BabbageEra)
- outValue' :: Lens' TxOut (TxOutValue BabbageEra)
- strip :: Tx -> TxStripped
- txOutTxDatum :: TxOutTx -> Maybe Datum
- txOutDatumHash :: TxOut -> Maybe DatumHash
- txOutPubKey :: TxOut -> Maybe PubKeyHash
- txOutAddress :: TxOut -> CardanoAddress
- outAddress :: Lens' TxOut (AddressInEra BabbageEra)
- outDatumHash :: Lens TxOut TxOut (Maybe DatumHash) (TxOutDatum CtxTx BabbageEra)
- txOutReferenceScript :: TxOut -> ReferenceScript
- outReferenceScript :: Lens' TxOut ReferenceScript
- lookupScript :: ScriptsMap -> ScriptHash -> Maybe (Versioned Script)
- lookupValidator :: ScriptsMap -> ValidatorHash -> Maybe (Versioned Validator)
- spentOutputs :: Tx -> [TxOutRef]
- referencedOutputs :: Tx -> [TxOutRef]
- lookupMintingPolicy :: ScriptsMap -> MintingPolicyHash -> Maybe (Versioned MintingPolicy)
- lookupStakeValidator :: ScriptsMap -> StakeValidatorHash -> Maybe (Versioned StakeValidator)
- fillTxInputWitnesses :: Tx -> TxInput -> TxIn
- pubKeyTxInput :: TxOutRef -> TxInput
- addMintingPolicy :: Versioned MintingPolicy -> (Redeemer, Maybe (Versioned TxOutRef)) -> Tx -> Tx
- addScriptTxInput :: TxOutRef -> Versioned Validator -> Redeemer -> Maybe Datum -> Tx -> Tx
- addReferenceTxInput :: TxOutRef -> Versioned TxOutRef -> Redeemer -> Maybe Datum -> Tx -> Tx
- txRedeemers :: Tx -> Map ScriptPurpose Redeemer
- txSpendingRedeemers :: Tx -> Map TxOutRef Redeemer
- txMintingRedeemers :: Tx -> Map MintingPolicyHash Redeemer
- txRewardingRedeemers :: Tx -> Map Credential Redeemer
- txCertifyingRedeemers :: Tx -> Map DCert Redeemer
- data DecoratedTxOut
- = PublicKeyDecoratedTxOut { }
- | ScriptDecoratedTxOut {
- _decoratedTxOutValidatorHash :: ValidatorHash
- _decoratedTxOutStakingCredential :: Maybe StakingCredential
- _decoratedTxOutValue :: Value
- _decoratedTxOutScriptDatum :: (DatumHash, DatumFromQuery)
- _decoratedTxOutReferenceScript :: Maybe (Versioned Script)
- _decoratedTxOutValidator :: Maybe (Versioned Validator)
- toTxOut :: NetworkId -> DecoratedTxOut -> Either ToCardanoError TxOut
- toTxInfoTxOut :: DecoratedTxOut -> TxOut
- decoratedTxOutPubKeyHash :: Traversal' DecoratedTxOut PubKeyHash
- decoratedTxOutAddress :: Getter DecoratedTxOut Address
- decoratedTxOutDatum :: Traversal' DecoratedTxOut (DatumHash, DatumFromQuery)
- decoratedTxOutValue :: Lens' DecoratedTxOut Value
- decoratedTxOutPubKeyDatum :: Traversal' DecoratedTxOut (Maybe (DatumHash, DatumFromQuery))
- decoratedTxOutScriptDatum :: Traversal' DecoratedTxOut (DatumHash, DatumFromQuery)
- decoratedTxOutStakingCredential :: Lens' DecoratedTxOut (Maybe StakingCredential)
- decoratedTxOutReferenceScript :: Lens' DecoratedTxOut (Maybe (Versioned Script))
- decoratedTxOutValidatorHash :: Traversal' DecoratedTxOut ValidatorHash
- decoratedTxOutValidator :: Traversal' DecoratedTxOut (Maybe (Versioned Validator))
- _PublicKeyDecoratedTxOut :: Prism' DecoratedTxOut (PubKeyHash, Maybe StakingCredential, Value, Maybe (DatumHash, DatumFromQuery), Maybe (Versioned Script))
- _ScriptDecoratedTxOut :: Prism' DecoratedTxOut (ValidatorHash, Maybe StakingCredential, Value, (DatumHash, DatumFromQuery), Maybe (Versioned Script), Maybe (Versioned Validator))
- _decoratedTxOutAddress :: DecoratedTxOut -> Address
- mkDecoratedTxOut :: CardanoAddress -> Value -> (DatumHash, DatumFromQuery) -> Maybe (Versioned Script) -> DecoratedTxOut
- mkPubkeyDecoratedTxOut :: CardanoAddress -> Value -> Maybe (DatumHash, DatumFromQuery) -> Maybe (Versioned Script) -> Maybe DecoratedTxOut
- mkScriptDecoratedTxOut :: CardanoAddress -> Value -> (DatumHash, DatumFromQuery) -> Maybe (Versioned Script) -> Maybe (Versioned Validator) -> Maybe DecoratedTxOut
- data DatumFromQuery
- datumInDatumFromQuery :: Traversal' DatumFromQuery Datum
- data CardanoTx
- = EmulatorTx {
- _emulatorTx :: Tx
- | CardanoApiTx { }
- = EmulatorTx {
- cardanoApiTx :: Traversal' CardanoTx SomeCardanoApiTx
- emulatorTx :: Traversal' CardanoTx Tx
- onCardanoTx :: (Tx -> r) -> (SomeCardanoApiTx -> r) -> CardanoTx -> r
- cardanoTxMap :: (Tx -> Tx) -> (SomeCardanoApiTx -> SomeCardanoApiTx) -> CardanoTx -> CardanoTx
- getCardanoTxId :: CardanoTx -> TxId
- getCardanoTxInputs :: CardanoTx -> [TxIn]
- getCardanoTxCollateralInputs :: CardanoTx -> [TxIn]
- getCardanoTxOutRefs :: CardanoTx -> [(TxOut, TxOutRef)]
- getCardanoTxOutputs :: CardanoTx -> [TxOut]
- getCardanoTxRedeemers :: CardanoTx -> Map ScriptPurpose Redeemer
- getCardanoTxSpentOutputs :: CardanoTx -> Set TxOutRef
- getCardanoTxProducedOutputs :: CardanoTx -> Map TxOutRef TxOut
- getCardanoTxReturnCollateral :: CardanoTx -> Maybe TxOut
- getCardanoTxProducedReturnCollateral :: CardanoTx -> Map TxOutRef TxOut
- getCardanoTxTotalCollateral :: CardanoTx -> Maybe Value
- getCardanoTxFee :: CardanoTx -> Value
- getCardanoTxMint :: CardanoTx -> Value
- getCardanoTxValidityRange :: CardanoTx -> SlotRange
- getCardanoTxData :: CardanoTx -> Map DatumHash Datum
- data SomeCardanoApiTx where
- SomeTx :: IsCardanoEra era => Tx era -> EraInMode era CardanoMode -> SomeCardanoApiTx
- pattern CardanoApiEmulatorEraTx :: Tx BabbageEra -> SomeCardanoApiTx
- data ToCardanoError
- = TxBodyError String
- | DeserialisationError
- | InvalidValidityRange
- | ValueNotPureAda
- | OutputHasZeroAda
- | StakingPointersNotSupported
- | SimpleScriptsNotSupportedToCardano
- | MissingInputValidator
- | MissingDatum
- | MissingMintingPolicy
- | ScriptPurposeNotSupported ScriptTag
- | MissingMintingPolicyRedeemer
- | MissingStakeValidator
- | UnsupportedPlutusVersion Language
- | Tag String ToCardanoError
- addSignature :: PrivateKey -> Passphrase -> Tx -> Tx
- addSignature' :: PrivateKey -> Tx -> Tx
- addCardanoTxSignature :: PrivateKey -> CardanoTx -> CardanoTx
- pubKeyTxOut :: Value -> PaymentPubKey -> Maybe StakingCredential -> Either ToCardanoError TxOut
- updateUtxo :: CardanoTx -> Map TxOutRef TxOut -> Map TxOutRef TxOut
- updateUtxoCollateral :: CardanoTx -> Map TxOutRef TxOut -> Map TxOutRef TxOut
- txOutRefs :: Tx -> [(TxOut, TxOutRef)]
- unspentOutputsTx :: Tx -> Map TxOutRef TxOut
- getTxBodyContentInputs :: TxBodyContent ctx era -> [TxIn]
- getTxBodyContentCollateralInputs :: TxBodyContent ctx era -> [TxIn]
- getTxBodyContentReturnCollateral :: TxBodyContent ctx BabbageEra -> Maybe TxOut
- getTxBodyContentMint :: TxBodyContent ctx era -> Value
- txBodyContentIns :: Lens' (TxBodyContent BuildTx BabbageEra) [(TxIn, BuildTxWith BuildTx (Witness WitCtxTxIn BabbageEra))]
- txBodyContentCollateralIns :: Lens' (TxBodyContent BuildTx BabbageEra) [TxIn]
- txBodyContentOuts :: Lens' (TxBodyContent ctx BabbageEra) [TxOut]
- txId :: Tx -> TxId
Documentation
Non-Native Script language. This is an Enumerated type. This is expected to be an open type. We will add new Constuctors to this type as additional Non-Native scripting language as are added. We use an enumerated type for two reasons. 1) We can write total functions by case analysis over the constructors 2) We will use DataKinds to make some datatypes indexed by Language For now, the only Non-Native Scriting language is Plutus We might add new languages in the futures.
Note that the the serialization of Language depends on the ordering.
Instances
| Bounded Language | |
| Enum Language | |
Defined in Cardano.Ledger.Alonzo.Language Methods succ :: Language -> Language Source # pred :: Language -> Language Source # toEnum :: Int -> Language Source # fromEnum :: Language -> Int Source # enumFrom :: Language -> [Language] Source # enumFromThen :: Language -> Language -> [Language] Source # enumFromTo :: Language -> Language -> [Language] Source # enumFromThenTo :: Language -> Language -> Language -> [Language] Source # | |
| Eq Language | |
| Ord Language | |
Defined in Cardano.Ledger.Alonzo.Language | |
| Show Language | |
| Ix Language | |
Defined in Cardano.Ledger.Alonzo.Language | |
| Generic Language | |
| NFData Language | |
Defined in Cardano.Ledger.Alonzo.Language | |
| FromCBOR Language | |
| ToCBOR Language | |
| NoThunks Language | |
| ToSchema Language Source # | |
Defined in Ledger.Orphans Methods declareNamedSchema :: Proxy Language -> Declare (Definitions Schema) NamedSchema Source # | |
| type Rep Language | |
Defined in Cardano.Ledger.Alonzo.Language | |
pubKeyHashTxOut :: Value -> PubKeyHash -> TxOut Source #
Create a transaction output locked by a public key.
isPayToScriptOut :: TxOut -> Bool Source #
Whether the output is a pay-to-script output.
isPubKeyOut :: TxOut -> Bool Source #
Whether the output is a pay-to-pubkey output.
A transaction ID, using a SHA256 hash as the transaction id.
Constructors
| TxId | |
Fields | |
Instances
A tag indicating the type of script that we are pointing to.
Instances
| Eq ScriptTag | |
| Ord ScriptTag | |
Defined in Plutus.V1.Ledger.Tx | |
| Show ScriptTag | |
| Generic ScriptTag | |
| NFData ScriptTag | |
Defined in Plutus.V1.Ledger.Tx | |
| ToJSON ScriptTag Source # | |
| FromJSON ScriptTag Source # | |
| ToSchema ScriptTag Source # | |
Defined in Ledger.Orphans Methods declareNamedSchema :: Proxy ScriptTag -> Declare (Definitions Schema) NamedSchema Source # | |
| Serialise ScriptTag Source # | |
| type Rep ScriptTag | |
Defined in Plutus.V1.Ledger.Tx type Rep ScriptTag = D1 ('MetaData "ScriptTag" "Plutus.V1.Ledger.Tx" "plutus-ledger-api-1.0.0.1-EUjexvcAhXiGIaLon6olWb" 'False) ((C1 ('MetaCons "Spend" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Mint" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Cert" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Reward" 'PrefixI 'False) (U1 :: Type -> Type))) | |
data RedeemerPtr Source #
A redeemer pointer is a pair of a script type tag t and an index i, picking out the ith script of type t in the transaction.
Constructors
| RedeemerPtr ScriptTag Integer |
Instances
A reference to a transaction output. This is a pair of a transaction reference, and an index indicating which of the outputs of that transaction we are referring to.
Constructors
| TxOutRef | |
Fields
| |
Instances
data Versioned script Source #
A script of some kind with its Plutus language version
Constructors
| Versioned | |
Fields
| |
Instances
A TxOut along with the Tx it comes from, which may have additional information e.g.
the full data script that goes with the TxOut.
Constructors
| TxOutTx | |
Fields
| |
Instances
| Eq TxOutTx Source # | |
| Show TxOutTx Source # | |
| Generic TxOutTx Source # | |
| ToJSON TxOutTx Source # | |
| FromJSON TxOutTx Source # | |
| Serialise TxOutTx Source # | |
| type Rep TxOutTx Source # | |
Defined in Ledger.Tx.Internal type Rep TxOutTx = D1 ('MetaData "TxOutTx" "Ledger.Tx.Internal" "plutus-ledger-1.1.0.0-JskZbcPMCdRJVHaAZ0to82" 'False) (C1 ('MetaCons "TxOutTx" 'PrefixI 'True) (S1 ('MetaSel ('Just "txOutTxTx") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Tx) :*: S1 ('MetaSel ('Just "txOutTxOut") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TxOut))) | |
data TxStripped Source #
A babbage era transaction without witnesses for its inputs.
Constructors
| TxStripped | |
Fields
| |
Instances
A Babbage-era transaction, including witnesses for its inputs.
Constructors
| Tx | |
Fields
| |
Instances
type MintingWitnessesMap = Map MintingPolicyHash (Redeemer, Maybe (Versioned TxOutRef)) Source #
type ScriptsMap = Map ScriptHash (Versioned Script) Source #
Validator, redeemer, and data scripts of a transaction input that spends a "pay to script" output. inScripts :: Tx -> TxInput -> Maybe (LedgerPlutusVersion, Validator, Redeemer, Datum) inScripts tx i@TxInput{txInputType=TxConsumeScriptAddress pv _ _ _} = case txInType $ fillTxInputWitnesses tx i of Just (ConsumeScriptAddress v r d) -> Just (pv, v, r, d) _ -> Nothing inScripts _ _ = Nothing
Constructors
| TxOut | |
Fields | |
Instances
| Eq TxOut Source # | |
| Show TxOut Source # | |
| Generic TxOut Source # | |
| NFData TxOut Source # | |
Defined in Ledger.Tx.Internal | |
| ToJSON TxOut Source # | |
| FromJSON TxOut Source # | |
| FromCBOR TxOut Source # | |
| ToCBOR TxOut Source # | |
| ToSchema TxOut Source # | |
Defined in Ledger.Tx.Internal Methods declareNamedSchema :: Proxy TxOut -> Declare (Definitions Schema) NamedSchema Source # | |
| Pretty TxOut Source # | |
| Serialise TxOut Source # | |
| type Rep TxOut Source # | |
Defined in Ledger.Tx.Internal type Rep TxOut = D1 ('MetaData "TxOut" "Ledger.Tx.Internal" "plutus-ledger-1.1.0.0-JskZbcPMCdRJVHaAZ0to82" 'True) (C1 ('MetaCons "TxOut" 'PrefixI 'True) (S1 ('MetaSel ('Just "getTxOut") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (TxOut CtxTx BabbageEra)))) | |
data Certificate Source #
Constructors
| Certificate | |
Fields
| |
Instances
data Withdrawal Source #
Stake withdrawal, if applicable the script should be included in txScripts.
Constructors
| Withdrawal | |
Fields
| |
Instances
A transaction input, consisting of a transaction output reference and an input type. Differs with TxIn by: TxIn *maybe* contains *full* data witnesses, TxInput always contains redeemer witness, but datum/validator hashes.
Constructors
| TxInput | |
Fields
| |
Instances
| Eq TxInput Source # | |
| Ord TxInput Source # | |
Defined in Ledger.Tx.Internal | |
| Show TxInput Source # | |
| Generic TxInput Source # | |
| NFData TxInput Source # | |
Defined in Ledger.Tx.Internal | |
| ToJSON TxInput Source # | |
| FromJSON TxInput Source # | |
| ToSchema TxInput Source # | |
Defined in Ledger.Tx.Internal Methods declareNamedSchema :: Proxy TxInput -> Declare (Definitions Schema) NamedSchema Source # | |
| Pretty TxInput Source # | |
| Serialise TxInput Source # | |
| type Rep TxInput Source # | |
Defined in Ledger.Tx.Internal type Rep TxInput = D1 ('MetaData "TxInput" "Ledger.Tx.Internal" "plutus-ledger-1.1.0.0-JskZbcPMCdRJVHaAZ0to82" 'False) (C1 ('MetaCons "TxInput" 'PrefixI 'True) (S1 ('MetaSel ('Just "txInputRef") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 TxOutRef) :*: S1 ('MetaSel ('Just "txInputType") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 TxInputType))) | |
data TxInputType Source #
The type of a transaction input with hashes.
Constructors
| TxScriptAddress !Redeemer !(Either ValidatorHash (Versioned TxOutRef)) !(Maybe DatumHash) | A transaction input that consumes (with a validator hash) or references (with a txOutRef) a script address with the given the redeemer and datum hash. |
| TxConsumePublicKeyAddress | A transaction input that consumes a public key address. |
| TxConsumeSimpleScriptAddress | Consume a simple script |
Instances
A transaction input, consisting of a transaction output reference and an input type.
Instances
| Eq TxIn Source # | |
| Ord TxIn Source # | |
| Show TxIn Source # | |
| Generic TxIn Source # | |
| NFData TxIn Source # | |
Defined in Ledger.Tx.Internal | |
| ToJSON TxIn Source # | |
| FromJSON TxIn Source # | |
| ToSchema TxIn Source # | |
Defined in Ledger.Tx.Internal Methods declareNamedSchema :: Proxy TxIn -> Declare (Definitions Schema) NamedSchema Source # | |
| Pretty TxIn Source # | |
| Serialise TxIn Source # | |
| type Rep TxIn Source # | |
Defined in Ledger.Tx.Internal type Rep TxIn = D1 ('MetaData "TxIn" "Ledger.Tx.Internal" "plutus-ledger-1.1.0.0-JskZbcPMCdRJVHaAZ0to82" 'False) (C1 ('MetaCons "TxIn" 'PrefixI 'True) (S1 ('MetaSel ('Just "txInRef") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 TxOutRef) :*: S1 ('MetaSel ('Just "txInType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe TxInType)))) | |
The type of a transaction input.
Constructors
| ScriptAddress !(Either (Versioned Validator) (Versioned TxOutRef)) !Redeemer !(Maybe Datum) | A transaction input that consumes (with a validator) or references (with a txOutRef) a script address with the given the redeemer and datum. Datum is optional if the input refers to a script output which contains an inline datum |
| ConsumePublicKeyAddress | A transaction input that consumes a public key address. |
| ConsumeSimpleScriptAddress | Consume a simple script |
Instances
pubKeyTxIn :: TxOutRef -> TxIn Source #
A transaction input that spends a "pay to public key" output, given the witness.
scriptTxIn :: TxOutRef -> Versioned Validator -> Redeemer -> Maybe Datum -> TxIn Source #
A transaction input that spends a "pay to script" output, given witnesses. Datum is optional if the input refers to a script output which contains an inline datum
inScripts :: TxIn -> Maybe (Versioned Validator, Redeemer, Maybe Datum) Source #
Validator, redeemer, and data scripts of a transaction input that spends a "pay to script" output.
scriptTxInputs :: Fold [TxInput] TxInput Source #
Filter to get only the scripts that consume or reference a script address
referenceScriptTxInputs :: Fold [TxInput] TxInput Source #
Filter to get only the scripts that reference a script address
toSizedTxOut :: TxOut -> Sized (TxOut StandardBabbage) Source #
collateralInputs :: Lens' Tx [TxInput] Source #
The collateral inputs of a transaction for paying fees when validating the transaction fails.
validValuesTx :: Tx -> Bool Source #
Check that all values in a transaction are non-negative.
txOutValue :: TxOut -> Value Source #
strip :: Tx -> TxStripped Source #
txOutDatumHash :: TxOut -> Maybe DatumHash Source #
Get a hash from the stored TxOutDatum (either dirctly or by hashing the inlined datum)
txOutPubKey :: TxOut -> Maybe PubKeyHash Source #
txOutAddress :: TxOut -> CardanoAddress Source #
lookupScript :: ScriptsMap -> ScriptHash -> Maybe (Versioned Script) Source #
lookupValidator :: ScriptsMap -> ValidatorHash -> Maybe (Versioned Validator) Source #
spentOutputs :: Tx -> [TxOutRef] Source #
The transaction output references consumed by a transaction.
referencedOutputs :: Tx -> [TxOutRef] Source #
The transaction output references referenced by a transaction.
lookupStakeValidator :: ScriptsMap -> StakeValidatorHash -> Maybe (Versioned StakeValidator) Source #
fillTxInputWitnesses :: Tx -> TxInput -> TxIn Source #
Translate TxInput to old Plutus.V1.Ledger.Api TxIn taking script and datum witnesses from Tx.
pubKeyTxInput :: TxOutRef -> TxInput Source #
addMintingPolicy :: Versioned MintingPolicy -> (Redeemer, Maybe (Versioned TxOutRef)) -> Tx -> Tx Source #
Add minting policy together with the redeemer into txMintingWitnesses and txScripts accordingly. Doesn't alter txMint.
addScriptTxInput :: TxOutRef -> Versioned Validator -> Redeemer -> Maybe Datum -> Tx -> Tx Source #
Add validator together with the redeemer and datum into txInputs, txData and txScripts accordingly. Datum is optional if the input refers to a script output which contains an inline datum
addReferenceTxInput :: TxOutRef -> Versioned TxOutRef -> Redeemer -> Maybe Datum -> Tx -> Tx Source #
Add script reference together with the redeemer and datum into txInputs and txData accordingly. Datum is optional if the input refers to a script output which contains an inline datum
txRedeemers :: Tx -> Map ScriptPurpose Redeemer Source #
DecoratedTxOut
data DecoratedTxOut Source #
Offchain view of a transaction output.
Constructors
| PublicKeyDecoratedTxOut | |
Fields
| |
| ScriptDecoratedTxOut | |
Fields
| |
Instances
toTxOut :: NetworkId -> DecoratedTxOut -> Either ToCardanoError TxOut Source #
toTxInfoTxOut :: DecoratedTxOut -> TxOut Source #
Converts a transaction output from the chain index to the plutus-ledger-api transaction output.
Note that DecoratedTxOut supports features such inline datums and
reference scripts which are not supported by V1 TxOut. Converting from
DecoratedTxOut to TxOut and back is therefore lossy.
Lenses and Prisms
_PublicKeyDecoratedTxOut :: Prism' DecoratedTxOut (PubKeyHash, Maybe StakingCredential, Value, Maybe (DatumHash, DatumFromQuery), Maybe (Versioned Script)) Source #
_ScriptDecoratedTxOut :: Prism' DecoratedTxOut (ValidatorHash, Maybe StakingCredential, Value, (DatumHash, DatumFromQuery), Maybe (Versioned Script), Maybe (Versioned Validator)) Source #
smart Constructors
mkDecoratedTxOut :: CardanoAddress -> Value -> (DatumHash, DatumFromQuery) -> Maybe (Versioned Script) -> DecoratedTxOut Source #
mkPubkeyDecoratedTxOut :: CardanoAddress -> Value -> Maybe (DatumHash, DatumFromQuery) -> Maybe (Versioned Script) -> Maybe DecoratedTxOut Source #
mkScriptDecoratedTxOut :: CardanoAddress -> Value -> (DatumHash, DatumFromQuery) -> Maybe (Versioned Script) -> Maybe (Versioned Validator) -> Maybe DecoratedTxOut Source #
DatumFromQuery
data DatumFromQuery Source #
A datum in a transaction output that comes from a chain index query.
Constructors
| DatumUnknown | |
| DatumInline Datum | |
| DatumInBody Datum |
Instances
Transactions
Constructors
| EmulatorTx | |
Fields
| |
| CardanoApiTx | |
Fields | |
Instances
| Eq CardanoTx Source # | |
| Show CardanoTx Source # | |
| Generic CardanoTx Source # | |
| ToJSON CardanoTx Source # | |
| FromJSON CardanoTx Source # | |
| ToSchema CardanoTx Source # | |
Defined in Ledger.Tx Methods declareNamedSchema :: Proxy CardanoTx -> Declare (Definitions Schema) NamedSchema Source # | |
| Pretty CardanoTx Source # | |
| Serialise CardanoTx Source # | |
| type Rep CardanoTx Source # | |
Defined in Ledger.Tx type Rep CardanoTx = D1 ('MetaData "CardanoTx" "Ledger.Tx" "plutus-ledger-1.1.0.0-JskZbcPMCdRJVHaAZ0to82" 'False) (C1 ('MetaCons "EmulatorTx" 'PrefixI 'True) (S1 ('MetaSel ('Just "_emulatorTx") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Tx)) :+: C1 ('MetaCons "CardanoApiTx" 'PrefixI 'True) (S1 ('MetaSel ('Just "_cardanoApiTx") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SomeCardanoApiTx))) | |
onCardanoTx :: (Tx -> r) -> (SomeCardanoApiTx -> r) -> CardanoTx -> r Source #
cardanoTxMap :: (Tx -> Tx) -> (SomeCardanoApiTx -> SomeCardanoApiTx) -> CardanoTx -> CardanoTx Source #
getCardanoTxId :: CardanoTx -> TxId Source #
getCardanoTxInputs :: CardanoTx -> [TxIn] Source #
getCardanoTxCollateralInputs :: CardanoTx -> [TxIn] Source #
getCardanoTxOutputs :: CardanoTx -> [TxOut] Source #
getCardanoTxFee :: CardanoTx -> Value Source #
getCardanoTxMint :: CardanoTx -> Value Source #
data SomeCardanoApiTx where Source #
Cardano tx from any era.
Constructors
| SomeTx :: IsCardanoEra era => Tx era -> EraInMode era CardanoMode -> SomeCardanoApiTx |
Bundled Patterns
| pattern CardanoApiEmulatorEraTx :: Tx BabbageEra -> SomeCardanoApiTx |
Instances
data ToCardanoError Source #
Constructors
Instances
addSignature :: PrivateKey -> Passphrase -> Tx -> Tx Source #
Sign the transaction with a PrivateKey and passphrase (ByteString) and add the signature to the
transaction's list of signatures.
addSignature' :: PrivateKey -> Tx -> Tx Source #
Sign the transaction with a PrivateKey that has no passphrase and add the signature to the
transaction's list of signatures
addCardanoTxSignature :: PrivateKey -> CardanoTx -> CardanoTx Source #
pubKeyTxOut :: Value -> PaymentPubKey -> Maybe StakingCredential -> Either ToCardanoError TxOut Source #
Create a transaction output locked by a public payment key and optionnaly a public stake key.
updateUtxo :: CardanoTx -> Map TxOutRef TxOut -> Map TxOutRef TxOut Source #
Update a map of unspent transaction outputs and signatures based on the inputs and outputs of a transaction.
updateUtxoCollateral :: CardanoTx -> Map TxOutRef TxOut -> Map TxOutRef TxOut Source #
Update a map of unspent transaction outputs and signatures based on the collateral inputs of a transaction (for when it is invalid).
txOutRefs :: Tx -> [(TxOut, TxOutRef)] Source #
A list of a transaction's outputs paired with a TxOutRefs referring to them.
TxBodyContent functions
getTxBodyContentInputs :: TxBodyContent ctx era -> [TxIn] Source #
getTxBodyContentCollateralInputs :: TxBodyContent ctx era -> [TxIn] Source #
getTxBodyContentMint :: TxBodyContent ctx era -> Value Source #
txBodyContentIns :: Lens' (TxBodyContent BuildTx BabbageEra) [(TxIn, BuildTxWith BuildTx (Witness WitCtxTxIn BabbageEra))] Source #
txBodyContentOuts :: Lens' (TxBodyContent ctx BabbageEra) [TxOut] Source #
Hashing transactions
Orphan instances
| Pretty SomeCardanoApiTx Source # | |
Methods pretty :: SomeCardanoApiTx -> Doc ann Source # prettyList :: [SomeCardanoApiTx] -> Doc ann Source # | |
| Pretty CardanoBuildTx Source # | |
Methods pretty :: CardanoBuildTx -> Doc ann Source # prettyList :: [CardanoBuildTx] -> Doc ann Source # | |
| Pretty Tx Source # | |