Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- awaitSlot :: forall w s e. AsContractError e => Slot -> Contract w s e Slot
- isSlot :: forall w s e. AsContractError e => Slot -> Promise w s e Slot
- currentSlot :: forall w s e. AsContractError e => Contract w s e Slot
- currentPABSlot :: forall w s e. AsContractError e => Contract w s e Slot
- currentNodeClientSlot :: forall w s e. AsContractError e => Contract w s e Slot
- currentChainIndexSlot :: forall w s e. AsContractError e => Contract w s e Slot
- waitNSlots :: forall w s e. AsContractError e => Natural -> Contract w s e Slot
- awaitTime :: forall w s e. AsContractError e => POSIXTime -> Contract w s e POSIXTime
- isTime :: forall w s e. AsContractError e => POSIXTime -> Promise w s e POSIXTime
- currentTime :: forall w s e. AsContractError e => Contract w s e POSIXTime
- currentNodeClientTimeRange :: forall w s e. AsContractError e => Contract w s e (POSIXTime, POSIXTime)
- waitNMilliSeconds :: forall w s e. AsContractError e => DiffMilliSeconds -> Contract w s e POSIXTime
- datumFromHash :: forall w s e. AsContractError e => DatumHash -> Contract w s e (Maybe Datum)
- datumsAt :: forall w s e. AsContractError e => CardanoAddress -> Contract w s e [Datum]
- validatorFromHash :: forall w s e. AsContractError e => ValidatorHash -> Contract w s e (Maybe (Versioned Validator))
- mintingPolicyFromHash :: forall w s e. AsContractError e => MintingPolicyHash -> Contract w s e (Maybe (Versioned MintingPolicy))
- stakeValidatorFromHash :: forall w s e. AsContractError e => StakeValidatorHash -> Contract w s e (Maybe (Versioned StakeValidator))
- redeemerFromHash :: forall w s e. AsContractError e => RedeemerHash -> Contract w s e (Maybe Redeemer)
- txOutFromRef :: forall w s e. AsContractError e => TxOutRef -> Contract w s e (Maybe DecoratedTxOut)
- txFromTxId :: forall w s e. AsContractError e => TxId -> Contract w s e (Maybe ChainIndexTx)
- findReferenceValidatorScripByHash :: forall w s e. AsContractError e => ValidatorHash -> CardanoAddress -> Contract w s e TxOutRef
- unspentTxOutFromRef :: forall w s e. AsContractError e => TxOutRef -> Contract w s e (Maybe DecoratedTxOut)
- utxoRefMembership :: forall w s e. AsContractError e => TxOutRef -> Contract w s e IsUtxoResponse
- utxoRefsAt :: forall w s e. AsContractError e => PageQuery TxOutRef -> CardanoAddress -> Contract w s e UtxosResponse
- utxoRefsWithCurrency :: forall w s e. AsContractError e => PageQuery TxOutRef -> AssetClass -> Contract w s e UtxosResponse
- utxosAt :: forall w s e. AsContractError e => CardanoAddress -> Contract w s e (Map TxOutRef DecoratedTxOut)
- utxosTxOutTxFromTx :: AsContractError e => ChainIndexTx -> Contract w s e [(TxOutRef, (DecoratedTxOut, ChainIndexTx))]
- utxosTxOutTxAt :: forall w s e. AsContractError e => CardanoAddress -> Contract w s e (Map TxOutRef (DecoratedTxOut, ChainIndexTx))
- txsFromTxIds :: forall w s e. AsContractError e => [TxId] -> Contract w s e [ChainIndexTx]
- txoRefsAt :: forall w s e. AsContractError e => PageQuery TxOutRef -> CardanoAddress -> Contract w s e TxosResponse
- txsAt :: forall w s e. AsContractError e => CardanoAddress -> Contract w s e [ChainIndexTx]
- getTip :: forall w s e. AsContractError e => Contract w s e Tip
- collectQueryResponse :: Monad m => (PageQuery TxOutRef -> m (QueryResponse a)) -> m [a]
- fundsAtAddressGt :: forall w s e. AsContractError e => CardanoAddress -> Value -> Contract w s e (Map TxOutRef DecoratedTxOut)
- fundsAtAddressGeq :: forall w s e. AsContractError e => CardanoAddress -> Value -> Contract w s e (Map TxOutRef DecoratedTxOut)
- fundsAtAddressCondition :: forall w s e. AsContractError e => (Value -> Bool) -> CardanoAddress -> Contract w s e (Map TxOutRef DecoratedTxOut)
- watchAddressUntilSlot :: forall w s e. AsContractError e => CardanoAddress -> Slot -> Contract w s e (Map TxOutRef DecoratedTxOut)
- watchAddressUntilTime :: forall w s e. AsContractError e => CardanoAddress -> POSIXTime -> Contract w s e (Map TxOutRef DecoratedTxOut)
- awaitUtxoSpent :: forall w s e. AsContractError e => TxOutRef -> Contract w s e ChainIndexTx
- utxoIsSpent :: forall w s e. AsContractError e => TxOutRef -> Promise w s e ChainIndexTx
- awaitUtxoProduced :: forall w s e. AsContractError e => CardanoAddress -> Contract w s e (NonEmpty ChainIndexTx)
- utxoIsProduced :: forall w s e. AsContractError e => CardanoAddress -> Promise w s e (NonEmpty ChainIndexTx)
- data RollbackState a = Unknown
- type TxStatus = RollbackState ()
- awaitTxStatusChange :: forall w s e. AsContractError e => TxId -> Contract w s e TxStatus
- awaitTxConfirmed :: forall w s e. AsContractError e => TxId -> Contract w s e ()
- isTxConfirmed :: forall w s e. AsContractError e => TxId -> Promise w s e ()
- type TxOutStatus = RollbackState TxOutState
- awaitTxOutStatusChange :: forall w s e. AsContractError e => TxOutRef -> Contract w s e TxOutStatus
- ownInstanceId :: forall w s e. AsContractError e => Contract w s e ContractInstanceId
- type HasEndpoint l a s = (HasType l (EndpointValue a) (Input s), HasType l ActiveEndpoint (Output s), KnownSymbol l, ContractRow s)
- newtype EndpointDescription = EndpointDescription String
- type Endpoint l a = l .== (EndpointValue a, ActiveEndpoint)
- endpoint :: forall l a w s e b. (HasEndpoint l a s, AsContractError e, FromJSON a) => (a -> Contract w s e b) -> Promise w s e b
- handleEndpoint :: forall l a w s e1 e2 b. (HasEndpoint l a s, AsContractError e1, FromJSON a) => (Either e1 a -> Contract w s e2 b) -> Promise w s e2 b
- endpointWithMeta :: forall l a w s e meta b. (HasEndpoint l a s, AsContractError e, ToJSON meta, FromJSON a) => meta -> (a -> Contract w s e b) -> Promise w s e b
- endpointDescription :: forall l. KnownSymbol l => Proxy l -> EndpointDescription
- endpointReq :: forall l a s. HasEndpoint l a s => ActiveEndpoint
- endpointResp :: forall l a s. (HasEndpoint l a s, ToJSON a) => a -> PABResp
- ownPaymentPubKeyHash :: forall w s e. AsContractError e => Contract w s e PaymentPubKeyHash
- ownPaymentPubKeyHashes :: forall w s e. AsContractError e => Contract w s e [PaymentPubKeyHash]
- ownFirstPaymentPubKeyHash :: forall w s e. AsContractError e => Contract w s e PaymentPubKeyHash
- ownAddresses :: forall w s e. AsContractError e => Contract w s e (NonEmpty CardanoAddress)
- ownAddress :: forall w s e. AsContractError e => Contract w s e CardanoAddress
- ownUtxos :: forall w s e. AsContractError e => Contract w s e (Map TxOutRef DecoratedTxOut)
- getUnspentOutput :: AsContractError e => Contract w s e TxOutRef
- adjustUnbalancedTx :: forall w s e. AsContractError e => UnbalancedTx -> Contract w s e UnbalancedTx
- submitUnbalancedTx :: forall w s e. AsContractError e => UnbalancedTx -> Contract w s e CardanoTx
- submitBalancedTx :: forall w s e. AsContractError e => CardanoTx -> Contract w s e CardanoTx
- balanceTx :: forall w s e. AsContractError e => UnbalancedTx -> Contract w s e CardanoTx
- submitTx :: forall w s e. AsContractError e => TxConstraints Void Void -> Contract w s e CardanoTx
- submitTxConstraints :: forall a w s e. (ToData (RedeemerType a), FromData (DatumType a), ToData (DatumType a), AsContractError e) => TypedValidator a -> TxConstraints (RedeemerType a) (DatumType a) -> Contract w s e CardanoTx
- submitTxConstraintsSpending :: forall a w s e. (ToData (RedeemerType a), FromData (DatumType a), ToData (DatumType a), AsContractError e) => TypedValidator a -> Map TxOutRef DecoratedTxOut -> TxConstraints (RedeemerType a) (DatumType a) -> Contract w s e CardanoTx
- submitTxConstraintsWith :: forall a w s e. (ToData (RedeemerType a), FromData (DatumType a), ToData (DatumType a), AsContractError e) => ScriptLookups a -> TxConstraints (RedeemerType a) (DatumType a) -> Contract w s e CardanoTx
- submitTxConfirmed :: forall w s e. AsContractError e => UnbalancedTx -> Contract w s e ()
- mkTxConstraints :: forall a w s e. (ToData (RedeemerType a), FromData (DatumType a), ToData (DatumType a), AsContractError e) => ScriptLookups a -> TxConstraints (RedeemerType a) (DatumType a) -> Contract w s e UnbalancedTx
- yieldUnbalancedTx :: forall w s e. AsContractError e => UnbalancedTx -> Contract w s e ()
- getParams :: forall w s e. AsContractError e => Contract w s e Params
- type ContractRow s = (AllUniqueLabels (Input s), AllUniqueLabels (Output s))
- pabReq :: forall w s e a. AsContractError e => PABReq -> Prism' PABResp a -> Contract w s e a
- data MkTxLog = MkTxLog {
- mkTxLogLookups :: ScriptLookups Any
- mkTxLogTxConstraints :: TxConstraints BuiltinData BuiltinData
- mkTxLogResult :: Either MkTxError UnbalancedTx
PAB requests
Waiting
awaitSlot :: forall w s e. AsContractError e => Slot -> Contract w s e Slot Source #
Wait until the slot
currentSlot :: forall w s e. AsContractError e => Contract w s e Slot Source #
Deprecated: Use currentNodeClientSlot instead
Get the current slot number
currentPABSlot :: forall w s e. AsContractError e => Contract w s e Slot Source #
Deprecated: Use currentNodeClientSlot instead
Get the current slot number of PAB
currentNodeClientSlot :: forall w s e. AsContractError e => Contract w s e Slot Source #
Get the current slot number of the node client (the local or remote node) that the application is connected to.
currentChainIndexSlot :: forall w s e. AsContractError e => Contract w s e Slot Source #
Get the current node slot number querying slot number from plutus chain index to be aligned with slot at local running node
waitNSlots :: forall w s e. AsContractError e => Natural -> Contract w s e Slot Source #
Wait for a number of slots to pass
awaitTime :: forall w s e. AsContractError e => POSIXTime -> Contract w s e POSIXTime Source #
Wait until the slot where the given time falls into and return latest time we know has passed.
Example: if starting time is 0 and slot length is 3s, then `awaitTime 4` waits until slot 2 and returns the value `POSIXTime 5`.
isTime :: forall w s e. AsContractError e => POSIXTime -> Promise w s e POSIXTime Source #
Wait until the slot where the given time falls into and return latest time we know has passed.
currentTime :: forall w s e. AsContractError e => Contract w s e POSIXTime Source #
Deprecated: Use currentNodeClientTimeRange instead
Get the latest time of the current slot.
Example: if slot length is 3s and current slot is 2, then currentTime
returns the value `POSIXTime 5`
currentNodeClientTimeRange :: forall w s e. AsContractError e => Contract w s e (POSIXTime, POSIXTime) Source #
Get the POSIXTime
range of the current slot.
Example: if slot length is 3s and current slot is 2, then currentTimeRange
returns the time interval [3, 5[
.
waitNMilliSeconds :: forall w s e. AsContractError e => DiffMilliSeconds -> Contract w s e POSIXTime Source #
Wait for a number of milliseconds starting at the ending time of the current slot, and return the latest time we know has passed.
Example: if starting time is 0, slot length is 3000ms and current slot is 0, then `waitNMilliSeconds 0` returns the value `POSIXTime 2000` and `waitNMilliSeconds 1000` returns the value `POSIXTime 5`.
Chain index queries
datumFromHash :: forall w s e. AsContractError e => DatumHash -> Contract w s e (Maybe Datum) Source #
datumsAt :: forall w s e. AsContractError e => CardanoAddress -> Contract w s e [Datum] Source #
Get the all datums at an address whether or not the corresponding utxo have been consumed or not.
validatorFromHash :: forall w s e. AsContractError e => ValidatorHash -> Contract w s e (Maybe (Versioned Validator)) Source #
mintingPolicyFromHash :: forall w s e. AsContractError e => MintingPolicyHash -> Contract w s e (Maybe (Versioned MintingPolicy)) Source #
stakeValidatorFromHash :: forall w s e. AsContractError e => StakeValidatorHash -> Contract w s e (Maybe (Versioned StakeValidator)) Source #
redeemerFromHash :: forall w s e. AsContractError e => RedeemerHash -> Contract w s e (Maybe Redeemer) Source #
txOutFromRef :: forall w s e. AsContractError e => TxOutRef -> Contract w s e (Maybe DecoratedTxOut) Source #
txFromTxId :: forall w s e. AsContractError e => TxId -> Contract w s e (Maybe ChainIndexTx) Source #
findReferenceValidatorScripByHash :: forall w s e. AsContractError e => ValidatorHash -> CardanoAddress -> Contract w s e TxOutRef Source #
Find the reference to an utxo containing a reference script by its the script hash, amongst the utxos at a given address
unspentTxOutFromRef :: forall w s e. AsContractError e => TxOutRef -> Contract w s e (Maybe DecoratedTxOut) Source #
utxoRefMembership :: forall w s e. AsContractError e => TxOutRef -> Contract w s e IsUtxoResponse Source #
utxoRefsAt :: forall w s e. AsContractError e => PageQuery TxOutRef -> CardanoAddress -> Contract w s e UtxosResponse Source #
Get the unspent transaction output references at an address.
utxoRefsWithCurrency :: forall w s e. AsContractError e => PageQuery TxOutRef -> AssetClass -> Contract w s e UtxosResponse Source #
Get the unspent transaction output references with a specific currrency (AssetClass
).
utxosAt :: forall w s e. AsContractError e => CardanoAddress -> Contract w s e (Map TxOutRef DecoratedTxOut) Source #
Get the unspent transaction outputs at an address.
utxosTxOutTxFromTx :: AsContractError e => ChainIndexTx -> Contract w s e [(TxOutRef, (DecoratedTxOut, ChainIndexTx))] Source #
Get the unspent transaction outputs from a ChainIndexTx
.
utxosTxOutTxAt :: forall w s e. AsContractError e => CardanoAddress -> Contract w s e (Map TxOutRef (DecoratedTxOut, ChainIndexTx)) Source #
Get unspent transaction outputs with transaction from address.
txsFromTxIds :: forall w s e. AsContractError e => [TxId] -> Contract w s e [ChainIndexTx] Source #
Get the transactions for a list of transaction ids.
txoRefsAt :: forall w s e. AsContractError e => PageQuery TxOutRef -> CardanoAddress -> Contract w s e TxosResponse Source #
Get the transaction outputs at an address.
txsAt :: forall w s e. AsContractError e => CardanoAddress -> Contract w s e [ChainIndexTx] Source #
Get the transactions at an address.
getTip :: forall w s e. AsContractError e => Contract w s e Tip Source #
collectQueryResponse :: Monad m => (PageQuery TxOutRef -> m (QueryResponse a)) -> m [a] #
Waiting for changes to the UTXO set
fundsAtAddressGt :: forall w s e. AsContractError e => CardanoAddress -> Value -> Contract w s e (Map TxOutRef DecoratedTxOut) Source #
Watch an address for changes, and return the outputs at that address when the total value at the address has surpassed the given value.
fundsAtAddressGeq :: forall w s e. AsContractError e => CardanoAddress -> Value -> Contract w s e (Map TxOutRef DecoratedTxOut) Source #
Watch an address for changes, and return the outputs at that address when the total value at the address has reached or surpassed the given value.
fundsAtAddressCondition :: forall w s e. AsContractError e => (Value -> Bool) -> CardanoAddress -> Contract w s e (Map TxOutRef DecoratedTxOut) Source #
watchAddressUntilSlot :: forall w s e. AsContractError e => CardanoAddress -> Slot -> Contract w s e (Map TxOutRef DecoratedTxOut) Source #
Wait until the target slot and get the unspent transaction outputs at an address.
watchAddressUntilTime :: forall w s e. AsContractError e => CardanoAddress -> POSIXTime -> Contract w s e (Map TxOutRef DecoratedTxOut) Source #
Wait until the target time and get the unspent transaction outputs at an address.
awaitUtxoSpent :: forall w s e. AsContractError e => TxOutRef -> Contract w s e ChainIndexTx Source #
Wait until the UTXO has been spent, returning the transaction that spends it.
utxoIsSpent :: forall w s e. AsContractError e => TxOutRef -> Promise w s e ChainIndexTx Source #
Wait until the UTXO has been spent, returning the transaction that spends it.
awaitUtxoProduced :: forall w s e. AsContractError e => CardanoAddress -> Contract w s e (NonEmpty ChainIndexTx) Source #
Wait until one or more unspent outputs are produced at an address.
utxoIsProduced :: forall w s e. AsContractError e => CardanoAddress -> Promise w s e (NonEmpty ChainIndexTx) Source #
Wait until one or more unspent outputs are produced at an address.
Tx and tx output confirmation
data RollbackState a #
Instances
type TxStatus = RollbackState () #
awaitTxStatusChange :: forall w s e. AsContractError e => TxId -> Contract w s e TxStatus Source #
Wait for the status of a transaction to change
awaitTxConfirmed :: forall w s e. AsContractError e => TxId -> Contract w s e () Source #
Wait until a transaction is confirmed (added to the ledger).
If the transaction is never added to the ledger then awaitTxConfirmed
never
returns
isTxConfirmed :: forall w s e. AsContractError e => TxId -> Promise w s e () Source #
Wait until a transaction is confirmed (added to the ledger).
type TxOutStatus = RollbackState TxOutState #
awaitTxOutStatusChange :: forall w s e. AsContractError e => TxOutRef -> Contract w s e TxOutStatus Source #
Wait for the status of a transaction output to change.
Contract instances
ownInstanceId :: forall w s e. AsContractError e => Contract w s e ContractInstanceId Source #
Get the ContractInstanceId
of this instance.
Exposing endpoints
type HasEndpoint l a s = (HasType l (EndpointValue a) (Input s), HasType l ActiveEndpoint (Output s), KnownSymbol l, ContractRow s) Source #
newtype EndpointDescription Source #
Instances
type Endpoint l a = l .== (EndpointValue a, ActiveEndpoint) Source #
endpoint :: forall l a w s e b. (HasEndpoint l a s, AsContractError e, FromJSON a) => (a -> Contract w s e b) -> Promise w s e b Source #
Expose an endpoint, return the data that was entered
handleEndpoint :: forall l a w s e1 e2 b. (HasEndpoint l a s, AsContractError e1, FromJSON a) => (Either e1 a -> Contract w s e2 b) -> Promise w s e2 b Source #
endpointWithMeta :: forall l a w s e meta b. (HasEndpoint l a s, AsContractError e, ToJSON meta, FromJSON a) => meta -> (a -> Contract w s e b) -> Promise w s e b Source #
Expose an endpoint with some metadata. Return the data that was entered.
endpointDescription :: forall l. KnownSymbol l => Proxy l -> EndpointDescription Source #
endpointReq :: forall l a s. HasEndpoint l a s => ActiveEndpoint Source #
endpointResp :: forall l a s. (HasEndpoint l a s, ToJSON a) => a -> PABResp Source #
Wallet information
ownPaymentPubKeyHash :: forall w s e. AsContractError e => Contract w s e PaymentPubKeyHash Source #
Deprecated: Use ownFirstPaymentPubKeyHash, ownPaymentPubKeyHashes or ownAddresses instead
Get the hash of a public key belonging to the wallet that runs this contract.
* Any funds paid to this public key hash will be treated as the wallet's own
funds
* The wallet is able to sign transactions with the private key of this
public key, for example, if the public key is added to the
requiredSignatures
field of Tx
.
* There is a 1-n relationship between wallets and public keys (although in
the mockchain n=1)
ownPaymentPubKeyHashes :: forall w s e. AsContractError e => Contract w s e [PaymentPubKeyHash] Source #
ownFirstPaymentPubKeyHash :: forall w s e. AsContractError e => Contract w s e PaymentPubKeyHash Source #
ownAddresses :: forall w s e. AsContractError e => Contract w s e (NonEmpty CardanoAddress) Source #
Get the addresses belonging to the wallet that runs this contract.
* Any funds paid to one of these addresses will be treated as the wallet's own
funds
* The wallet is able to sign transactions with the private key of one of its
public key, for example, if the public key is added to the
requiredSignatures
field of Tx
.
* There is a 1-n relationship between wallets and addresses (although in
the mockchain n=1)
ownAddress :: forall w s e. AsContractError e => Contract w s e CardanoAddress Source #
Get the first address of the wallet that runs this contract.
ownUtxos :: forall w s e. AsContractError e => Contract w s e (Map TxOutRef DecoratedTxOut) Source #
Get all utxos belonging to the wallet that runs this contract.
getUnspentOutput :: AsContractError e => Contract w s e TxOutRef Source #
Get an unspent output belonging to the wallet.
Submitting transactions
adjustUnbalancedTx :: forall w s e. AsContractError e => UnbalancedTx -> Contract w s e UnbalancedTx Source #
Adjust the unbalanced tx
submitUnbalancedTx :: forall w s e. AsContractError e => UnbalancedTx -> Contract w s e CardanoTx Source #
Send an unbalanced transaction to be balanced and signed. Returns the ID of the final transaction when the transaction was submitted. Throws an error if balancing or signing failed.
submitBalancedTx :: forall w s e. AsContractError e => CardanoTx -> Contract w s e CardanoTx Source #
Send an balanced transaction to be signed. Returns the ID of the final transaction when the transaction was submitted. Throws an error if signing failed.
balanceTx :: forall w s e. AsContractError e => UnbalancedTx -> Contract w s e CardanoTx Source #
Send an unbalanced transaction to be balanced. Returns the balanced transaction. Throws an error if balancing failed.
submitTx :: forall w s e. AsContractError e => TxConstraints Void Void -> Contract w s e CardanoTx Source #
Build a transaction that satisfies the constraints, then submit it to the network. The constraints do not refer to any typed script inputs or outputs.
submitTxConstraints :: forall a w s e. (ToData (RedeemerType a), FromData (DatumType a), ToData (DatumType a), AsContractError e) => TypedValidator a -> TxConstraints (RedeemerType a) (DatumType a) -> Contract w s e CardanoTx Source #
Build a transaction that satisfies the constraints, then submit it to the network. Using the current outputs at the contract address and the contract's own public key to solve the constraints.
submitTxConstraintsSpending :: forall a w s e. (ToData (RedeemerType a), FromData (DatumType a), ToData (DatumType a), AsContractError e) => TypedValidator a -> Map TxOutRef DecoratedTxOut -> TxConstraints (RedeemerType a) (DatumType a) -> Contract w s e CardanoTx Source #
Build a transaction that satisfies the constraints using the UTXO map
to resolve any input constraints (see InputConstraint
)
submitTxConstraintsWith :: forall a w s e. (ToData (RedeemerType a), FromData (DatumType a), ToData (DatumType a), AsContractError e) => ScriptLookups a -> TxConstraints (RedeemerType a) (DatumType a) -> Contract w s e CardanoTx Source #
Build a transaction that satisfies the constraints, then submit it to the network. Using the given constraints.
submitTxConfirmed :: forall w s e. AsContractError e => UnbalancedTx -> Contract w s e () Source #
A version of submitTx
that waits until the transaction has been
confirmed on the ledger before returning.
mkTxConstraints :: forall a w s e. (ToData (RedeemerType a), FromData (DatumType a), ToData (DatumType a), AsContractError e) => ScriptLookups a -> TxConstraints (RedeemerType a) (DatumType a) -> Contract w s e UnbalancedTx Source #
Build a transaction that satisfies the constraints
yieldUnbalancedTx :: forall w s e. AsContractError e => UnbalancedTx -> Contract w s e () Source #
Take an UnbalancedTx
then balance, sign and submit it to the blockchain
without returning any results.
Parameters
getParams :: forall w s e. AsContractError e => Contract w s e Params Source #
Get the configured parameter set.
Etc.
type ContractRow s = (AllUniqueLabels (Input s), AllUniqueLabels (Output s)) Source #
Constraints on the contract schema, ensuring that the labels of the schema are unique.
:: forall w s e a. AsContractError e | |
=> PABReq | The request to send |
-> Prism' PABResp a | Prism for the response |
-> Contract w s e a |
Arguments and result of a call to mkTx
MkTxLog | |
|
Instances
Show MkTxLog Source # | |
Generic MkTxLog Source # | |
FromJSON MkTxLog Source # | |
Defined in Plutus.Contract.Request parseJSON :: Value -> Parser MkTxLog parseJSONList :: Value -> Parser [MkTxLog] | |
ToJSON MkTxLog Source # | |
Defined in Plutus.Contract.Request toEncoding :: MkTxLog -> Encoding toJSONList :: [MkTxLog] -> Value toEncodingList :: [MkTxLog] -> Encoding | |
type Rep MkTxLog Source # | |
Defined in Plutus.Contract.Request type Rep MkTxLog = D1 ('MetaData "MkTxLog" "Plutus.Contract.Request" "plutus-contract-1.2.0.0-FH8LC9wh7UV4Nmv68NHXrC" 'False) (C1 ('MetaCons "MkTxLog" 'PrefixI 'True) (S1 ('MetaSel ('Just "mkTxLogLookups") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ScriptLookups Any)) :*: (S1 ('MetaSel ('Just "mkTxLogTxConstraints") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (TxConstraints BuiltinData BuiltinData)) :*: S1 ('MetaSel ('Just "mkTxLogResult") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Either MkTxError UnbalancedTx))))) |