{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
module Plutus.Contract.Request(
awaitSlot
, isSlot
, currentSlot
, currentPABSlot
, currentNodeClientSlot
, currentChainIndexSlot
, waitNSlots
, awaitTime
, isTime
, currentTime
, currentNodeClientTimeRange
, waitNMilliSeconds
, datumFromHash
, datumsAt
, validatorFromHash
, mintingPolicyFromHash
, stakeValidatorFromHash
, redeemerFromHash
, txOutFromRef
, txFromTxId
, findReferenceValidatorScripByHash
, unspentTxOutFromRef
, utxoRefMembership
, utxoRefsAt
, utxoRefsWithCurrency
, utxosAt
, utxosTxOutTxFromTx
, utxosTxOutTxAt
, txsFromTxIds
, txoRefsAt
, txsAt
, getTip
, collectQueryResponse
, fundsAtAddressGt
, fundsAtAddressGeq
, fundsAtAddressCondition
, watchAddressUntilSlot
, watchAddressUntilTime
, awaitUtxoSpent
, utxoIsSpent
, awaitUtxoProduced
, utxoIsProduced
, RollbackState(..)
, TxStatus
, awaitTxStatusChange
, awaitTxConfirmed
, isTxConfirmed
, TxOutStatus
, awaitTxOutStatusChange
, ownInstanceId
, HasEndpoint
, EndpointDescription(..)
, Endpoint
, endpoint
, handleEndpoint
, endpointWithMeta
, endpointDescription
, endpointReq
, endpointResp
, ownPaymentPubKeyHash
, ownPaymentPubKeyHashes
, ownFirstPaymentPubKeyHash
, ownAddresses
, ownAddress
, ownUtxos
, getUnspentOutput
, adjustUnbalancedTx
, submitUnbalancedTx
, submitBalancedTx
, balanceTx
, submitTx
, submitTxConstraints
, submitTxConstraintsSpending
, submitTxConstraintsWith
, submitTxConfirmed
, mkTxConstraints
, yieldUnbalancedTx
, getParams
, ContractRow
, pabReq
, MkTxLog(..)
) where
import Cardano.Api qualified as C
import Cardano.Node.Emulator.Internal.Node.Params (Params)
import Control.Lens (Prism', _2, _Just, only, preview, review, to, view)
import Control.Monad.Freer.Error qualified as E
import Control.Monad.Trans.State.Strict (StateT (..), evalStateT)
import Data.Aeson (FromJSON, ToJSON)
import Data.Aeson qualified as JSON
import Data.Aeson.Types qualified as JSON
import Data.Bifunctor (Bifunctor (..))
import Data.Default (Default (def))
import Data.Foldable (fold)
import Data.List (find)
import Data.List.NonEmpty (NonEmpty)
import Data.List.NonEmpty qualified as NonEmpty
import Data.Map (Map)
import Data.Map qualified as Map
import Data.Maybe (catMaybes, isJust, mapMaybe)
import Data.Proxy (Proxy (Proxy))
import Data.Row (AllUniqueLabels, HasType, KnownSymbol, type (.==))
import Data.Text qualified as Text
import Data.Text.Extras (tshow)
import Data.Void (Void)
import GHC.Generics (Generic)
import GHC.Natural (Natural)
import GHC.TypeLits (Symbol, symbolVal)
import Ledger (CardanoAddress, DiffMilliSeconds, POSIXTime, PaymentPubKeyHash (PaymentPubKeyHash), Slot, TxOutRef,
ValidatorHash (ValidatorHash), cardanoPubKeyHash, decoratedTxOutReferenceScript, fromMilliSeconds,
getScriptHash, scriptHash, txOutRefId)
import Ledger.Tx (CardanoTx, DecoratedTxOut, Versioned, decoratedTxOutValue, getCardanoTxId)
import Ledger.Tx.CardanoAPI (toCardanoTxIn)
import Ledger.Tx.Constraints (TxConstraints)
import Ledger.Tx.Constraints.OffChain (ScriptLookups, UnbalancedTx)
import Ledger.Tx.Constraints.OffChain qualified as Constraints
import Ledger.Typed.Scripts (Any, TypedValidator, ValidatorTypes (DatumType, RedeemerType))
import Ledger.Value.CardanoAPI (valueGeq, valueLeq)
import Plutus.ChainIndex (ChainIndexTx, Page (nextPageQuery, pageItems), PageQuery, txOutRefs)
import Plutus.ChainIndex.Api (IsUtxoResponse, QueryResponse, TxosResponse, UtxosResponse, collectQueryResponse, paget)
import Plutus.ChainIndex.Types (RollbackState (Unknown), Tip, TxOutStatus, TxStatus)
import Plutus.Contract.Effects (ActiveEndpoint (ActiveEndpoint, aeDescription, aeMetadata),
PABReq (AdjustUnbalancedTxReq, AwaitSlotReq, AwaitTimeReq, AwaitTxOutStatusChangeReq, AwaitTxStatusChangeReq, AwaitUtxoProducedReq, AwaitUtxoSpentReq, BalanceTxReq, ChainIndexQueryReq, CurrentChainIndexSlotReq, CurrentNodeClientSlotReq, CurrentNodeClientTimeRangeReq, CurrentTimeReq, ExposeEndpointReq, GetParamsReq, OwnAddressesReq, OwnContractInstanceIdReq, WriteBalancedTxReq, YieldUnbalancedTxReq),
PABResp (ExposeEndpointResp))
import Plutus.Contract.Effects qualified as E
import Plutus.Contract.Error (AsContractError (_ChainIndexContractError, _ConstraintResolutionContractError, _EndpointDecodeContractError, _OtherContractError, _ResumableContractError, _ToCardanoConvertContractError, _WalletContractError),
ContractError (OtherContractError), _ContractError)
import Plutus.Contract.Logging (logDebug)
import Plutus.Contract.Resumable (prompt)
import Plutus.Contract.Schema (Input, Output)
import Plutus.Contract.Types (Contract (Contract), MatchingError (WrongVariantError), Promise (Promise), mapError,
runError, throwError)
import Plutus.Contract.Util (loopM)
import Plutus.V1.Ledger.Api (Datum, DatumHash, MintingPolicy, MintingPolicyHash, Redeemer, RedeemerHash, StakeValidator,
StakeValidatorHash, TxId, Validator)
import Plutus.V1.Ledger.Value (AssetClass)
import PlutusTx qualified
import Wallet.Emulator.Error (WalletAPIError (NoPaymentPubKeyHashError))
import Wallet.Types (ContractInstanceId, EndpointDescription (EndpointDescription),
EndpointValue (EndpointValue, unEndpointValue))
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
pabReq :: PABReq -> Prism' PABResp a -> Contract w s e a
pabReq PABReq
req Prism' PABResp a
prism = Eff (ContractEffs w e) a -> Contract w s e a
forall w (s :: Row *) e a.
Eff (ContractEffs w e) a -> Contract w s e a
Contract (Eff (ContractEffs w e) a -> Contract w s e a)
-> Eff (ContractEffs w e) a -> Contract w s e a
forall a b. (a -> b) -> a -> b
$ do
PABResp
x <- PABReq -> Eff (ContractEffs w e) PABResp
forall i o (effs :: [* -> *]).
Member (Resumable i o) effs =>
o -> Eff effs i
prompt @PABResp @PABReq PABReq
req
case Getting (First a) PABResp a -> PABResp -> Maybe a
forall s (m :: * -> *) a.
MonadReader s m =>
Getting (First a) s a -> m (Maybe a)
preview Getting (First a) PABResp a
Prism' PABResp a
prism PABResp
x of
Just a
r -> a -> Eff (ContractEffs w e) a
forall (f :: * -> *) a. Applicative f => a -> f a
pure a
r
Maybe a
_ ->
forall (effs :: [* -> *]) a.
Member (Error e) effs =>
e -> Eff effs a
forall e (effs :: [* -> *]) a.
Member (Error e) effs =>
e -> Eff effs a
E.throwError @e
(e -> Eff (ContractEffs w e) a) -> e -> Eff (ContractEffs w e) a
forall a b. (a -> b) -> a -> b
$ AReview e MatchingError -> MatchingError -> e
forall b (m :: * -> *) t. MonadReader b m => AReview t b -> m t
review AReview e MatchingError
forall r. AsContractError r => Prism' r MatchingError
_ResumableContractError
(MatchingError -> e) -> MatchingError -> e
forall a b. (a -> b) -> a -> b
$ Text -> MatchingError
WrongVariantError
(Text -> MatchingError) -> Text -> MatchingError
forall a b. (a -> b) -> a -> b
$ Text
"unexpected answer: " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> PABResp -> Text
forall a. Show a => a -> Text
tshow PABResp
x
adjustUnbalancedTx ::
forall w s e.
( AsContractError e
)
=> UnbalancedTx
-> Contract w s e UnbalancedTx
adjustUnbalancedTx :: UnbalancedTx -> Contract w s e UnbalancedTx
adjustUnbalancedTx UnbalancedTx
utx = PABReq
-> Prism' PABResp UnbalancedTx -> Contract w s e UnbalancedTx
forall w (s :: Row *) e a.
AsContractError e =>
PABReq -> Prism' PABResp a -> Contract w s e a
pabReq (UnbalancedTx -> PABReq
AdjustUnbalancedTxReq UnbalancedTx
utx) Prism' PABResp UnbalancedTx
E._AdjustUnbalancedTxResp
awaitSlot ::
forall w s e.
( AsContractError e
)
=> Slot
-> Contract w s e Slot
awaitSlot :: Slot -> Contract w s e Slot
awaitSlot Slot
s = PABReq -> Prism' PABResp Slot -> Contract w s e Slot
forall w (s :: Row *) e a.
AsContractError e =>
PABReq -> Prism' PABResp a -> Contract w s e a
pabReq (Slot -> PABReq
AwaitSlotReq Slot
s) Prism' PABResp Slot
E._AwaitSlotResp
isSlot ::
forall w s e.
( AsContractError e
)
=> Slot
-> Promise w s e Slot
isSlot :: Slot -> Promise w s e Slot
isSlot = Contract w s e Slot -> Promise w s e Slot
forall w (s :: Row *) e a. Contract w s e a -> Promise w s e a
Promise (Contract w s e Slot -> Promise w s e Slot)
-> (Slot -> Contract w s e Slot) -> Slot -> Promise w s e Slot
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Slot -> Contract w s e Slot
forall w (s :: Row *) e.
AsContractError e =>
Slot -> Contract w s e Slot
awaitSlot
{-# DEPRECATED currentSlot "Use currentNodeClientSlot instead" #-}
currentSlot ::
forall w s e.
( AsContractError e
)
=> Contract w s e Slot
currentSlot :: Contract w s e Slot
currentSlot = Contract w s e Slot
forall w (s :: Row *) e. AsContractError e => Contract w s e Slot
currentPABSlot
{-# DEPRECATED currentPABSlot "Use currentNodeClientSlot instead" #-}
currentPABSlot ::
forall w s e.
( AsContractError e
)
=> Contract w s e Slot
currentPABSlot :: Contract w s e Slot
currentPABSlot = PABReq -> Prism' PABResp Slot -> Contract w s e Slot
forall w (s :: Row *) e a.
AsContractError e =>
PABReq -> Prism' PABResp a -> Contract w s e a
pabReq PABReq
CurrentNodeClientSlotReq Prism' PABResp Slot
E._CurrentNodeClientSlotResp
currentNodeClientSlot ::
forall w s e.
( AsContractError e
)
=> Contract w s e Slot
currentNodeClientSlot :: Contract w s e Slot
currentNodeClientSlot = PABReq -> Prism' PABResp Slot -> Contract w s e Slot
forall w (s :: Row *) e a.
AsContractError e =>
PABReq -> Prism' PABResp a -> Contract w s e a
pabReq PABReq
CurrentNodeClientSlotReq Prism' PABResp Slot
E._CurrentNodeClientSlotResp
currentChainIndexSlot ::
forall w s e.
( AsContractError e
)
=> Contract w s e Slot
currentChainIndexSlot :: Contract w s e Slot
currentChainIndexSlot = PABReq -> Prism' PABResp Slot -> Contract w s e Slot
forall w (s :: Row *) e a.
AsContractError e =>
PABReq -> Prism' PABResp a -> Contract w s e a
pabReq PABReq
CurrentChainIndexSlotReq Prism' PABResp Slot
E._CurrentChainIndexSlotResp
waitNSlots ::
forall w s e.
( AsContractError e
)
=> Natural
-> Contract w s e Slot
waitNSlots :: Natural -> Contract w s e Slot
waitNSlots Natural
n = do
Slot
c <- Contract w s e Slot
forall w (s :: Row *) e. AsContractError e => Contract w s e Slot
currentSlot
Slot -> Contract w s e Slot
forall w (s :: Row *) e.
AsContractError e =>
Slot -> Contract w s e Slot
awaitSlot (Slot -> Contract w s e Slot) -> Slot -> Contract w s e Slot
forall a b. (a -> b) -> a -> b
$ Slot
c Slot -> Slot -> Slot
forall a. Num a => a -> a -> a
+ Natural -> Slot
forall a b. (Integral a, Num b) => a -> b
fromIntegral Natural
n
awaitTime ::
forall w s e.
( AsContractError e
)
=> POSIXTime
-> Contract w s e POSIXTime
awaitTime :: POSIXTime -> Contract w s e POSIXTime
awaitTime POSIXTime
s = PABReq -> Prism' PABResp POSIXTime -> Contract w s e POSIXTime
forall w (s :: Row *) e a.
AsContractError e =>
PABReq -> Prism' PABResp a -> Contract w s e a
pabReq (POSIXTime -> PABReq
AwaitTimeReq POSIXTime
s) Prism' PABResp POSIXTime
E._AwaitTimeResp
isTime ::
forall w s e.
( AsContractError e
)
=> POSIXTime
-> Promise w s e POSIXTime
isTime :: POSIXTime -> Promise w s e POSIXTime
isTime = Contract w s e POSIXTime -> Promise w s e POSIXTime
forall w (s :: Row *) e a. Contract w s e a -> Promise w s e a
Promise (Contract w s e POSIXTime -> Promise w s e POSIXTime)
-> (POSIXTime -> Contract w s e POSIXTime)
-> POSIXTime
-> Promise w s e POSIXTime
forall b c a. (b -> c) -> (a -> b) -> a -> c
. POSIXTime -> Contract w s e POSIXTime
forall w (s :: Row *) e.
AsContractError e =>
POSIXTime -> Contract w s e POSIXTime
awaitTime
{-# DEPRECATED currentTime "Use currentNodeClientTimeRange instead" #-}
currentTime ::
forall w s e.
( AsContractError e
)
=> Contract w s e POSIXTime
currentTime :: Contract w s e POSIXTime
currentTime = PABReq -> Prism' PABResp POSIXTime -> Contract w s e POSIXTime
forall w (s :: Row *) e a.
AsContractError e =>
PABReq -> Prism' PABResp a -> Contract w s e a
pabReq PABReq
CurrentTimeReq Prism' PABResp POSIXTime
E._CurrentTimeResp
currentNodeClientTimeRange ::
forall w s e.
( AsContractError e
)
=> Contract w s e (POSIXTime, POSIXTime)
currentNodeClientTimeRange :: Contract w s e (POSIXTime, POSIXTime)
currentNodeClientTimeRange = PABReq
-> Prism' PABResp (POSIXTime, POSIXTime)
-> Contract w s e (POSIXTime, POSIXTime)
forall w (s :: Row *) e a.
AsContractError e =>
PABReq -> Prism' PABResp a -> Contract w s e a
pabReq PABReq
CurrentNodeClientTimeRangeReq Prism' PABResp (POSIXTime, POSIXTime)
E._CurrentNodeClientTimeRangeResp
waitNMilliSeconds ::
forall w s e.
( AsContractError e
)
=> DiffMilliSeconds
-> Contract w s e POSIXTime
waitNMilliSeconds :: DiffMilliSeconds -> Contract w s e POSIXTime
waitNMilliSeconds DiffMilliSeconds
n = do
POSIXTime
t <- Contract w s e POSIXTime
forall w (s :: Row *) e.
AsContractError e =>
Contract w s e POSIXTime
currentTime
POSIXTime -> Contract w s e POSIXTime
forall w (s :: Row *) e.
AsContractError e =>
POSIXTime -> Contract w s e POSIXTime
awaitTime (POSIXTime -> Contract w s e POSIXTime)
-> POSIXTime -> Contract w s e POSIXTime
forall a b. (a -> b) -> a -> b
$ POSIXTime
t POSIXTime -> POSIXTime -> POSIXTime
forall a. Num a => a -> a -> a
+ DiffMilliSeconds -> POSIXTime
fromMilliSeconds DiffMilliSeconds
n
getParams ::
forall w s e.
( AsContractError e
)
=> Contract w s e Params
getParams :: Contract w s e Params
getParams = PABReq -> Prism' PABResp Params -> Contract w s e Params
forall w (s :: Row *) e a.
AsContractError e =>
PABReq -> Prism' PABResp a -> Contract w s e a
pabReq PABReq
GetParamsReq Prism' PABResp Params
E._GetParamsResp
datumFromHash ::
forall w s e.
( AsContractError e
)
=> DatumHash
-> Contract w s e (Maybe Datum)
datumFromHash :: DatumHash -> Contract w s e (Maybe Datum)
datumFromHash DatumHash
h = do
ChainIndexResponse
cir <- PABReq
-> Prism' PABResp ChainIndexResponse
-> Contract w s e ChainIndexResponse
forall w (s :: Row *) e a.
AsContractError e =>
PABReq -> Prism' PABResp a -> Contract w s e a
pabReq (ChainIndexQuery -> PABReq
ChainIndexQueryReq (ChainIndexQuery -> PABReq) -> ChainIndexQuery -> PABReq
forall a b. (a -> b) -> a -> b
$ DatumHash -> ChainIndexQuery
E.DatumFromHash DatumHash
h) Prism' PABResp ChainIndexResponse
E._ChainIndexQueryResp
case ChainIndexResponse
cir of
E.DatumHashResponse Maybe Datum
r -> Maybe Datum -> Contract w s e (Maybe Datum)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe Datum
r
ChainIndexResponse
r -> e -> Contract w s e (Maybe Datum)
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (e -> Contract w s e (Maybe Datum))
-> e -> Contract w s e (Maybe Datum)
forall a b. (a -> b) -> a -> b
$ AReview e (Text, ChainIndexResponse)
-> (Text, ChainIndexResponse) -> e
forall b (m :: * -> *) t. MonadReader b m => AReview t b -> m t
review AReview e (Text, ChainIndexResponse)
forall r. AsContractError r => Prism' r (Text, ChainIndexResponse)
_ChainIndexContractError (Text
"DatumHashResponse", ChainIndexResponse
r)
queryDatumsAt ::
forall w s e.
( AsContractError e
)
=> CardanoAddress
-> PageQuery TxOutRef
-> Contract w s e (QueryResponse [Datum])
queryDatumsAt :: CardanoAddress
-> PageQuery TxOutRef -> Contract w s e (QueryResponse [Datum])
queryDatumsAt CardanoAddress
addr PageQuery TxOutRef
pq = do
ChainIndexResponse
cir <- PABReq
-> Prism' PABResp ChainIndexResponse
-> Contract w s e ChainIndexResponse
forall w (s :: Row *) e a.
AsContractError e =>
PABReq -> Prism' PABResp a -> Contract w s e a
pabReq (ChainIndexQuery -> PABReq
ChainIndexQueryReq (ChainIndexQuery -> PABReq) -> ChainIndexQuery -> PABReq
forall a b. (a -> b) -> a -> b
$ PageQuery TxOutRef -> CardanoAddress -> ChainIndexQuery
E.DatumsAtAddress PageQuery TxOutRef
pq CardanoAddress
addr) Prism' PABResp ChainIndexResponse
E._ChainIndexQueryResp
case ChainIndexResponse
cir of
E.DatumsAtResponse QueryResponse [Datum]
r -> QueryResponse [Datum] -> Contract w s e (QueryResponse [Datum])
forall (f :: * -> *) a. Applicative f => a -> f a
pure QueryResponse [Datum]
r
ChainIndexResponse
r -> e -> Contract w s e (QueryResponse [Datum])
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (e -> Contract w s e (QueryResponse [Datum]))
-> e -> Contract w s e (QueryResponse [Datum])
forall a b. (a -> b) -> a -> b
$ AReview e (Text, ChainIndexResponse)
-> (Text, ChainIndexResponse) -> e
forall b (m :: * -> *) t. MonadReader b m => AReview t b -> m t
review AReview e (Text, ChainIndexResponse)
forall r. AsContractError r => Prism' r (Text, ChainIndexResponse)
_ChainIndexContractError (Text
"DatumsAtResponse", ChainIndexResponse
r)
datumsAt ::
forall w s e.
( AsContractError e
)
=> CardanoAddress
-> Contract w s e [Datum]
datumsAt :: CardanoAddress -> Contract w s e [Datum]
datumsAt CardanoAddress
addr =
[[Datum]] -> [Datum]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([[Datum]] -> [Datum])
-> Contract w s e [[Datum]] -> Contract w s e [Datum]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (PageQuery TxOutRef -> Contract w s e (QueryResponse [Datum]))
-> Contract w s e [[Datum]]
forall (m :: * -> *) a.
Monad m =>
(PageQuery TxOutRef -> m (QueryResponse a)) -> m [a]
collectQueryResponse (CardanoAddress
-> PageQuery TxOutRef -> Contract w s e (QueryResponse [Datum])
forall w (s :: Row *) e.
AsContractError e =>
CardanoAddress
-> PageQuery TxOutRef -> Contract w s e (QueryResponse [Datum])
queryDatumsAt CardanoAddress
addr)
validatorFromHash ::
forall w s e.
( AsContractError e
)
=> ValidatorHash
-> Contract w s e (Maybe (Versioned Validator))
validatorFromHash :: ValidatorHash -> Contract w s e (Maybe (Versioned Validator))
validatorFromHash ValidatorHash
h = do
ChainIndexResponse
cir <- PABReq
-> Prism' PABResp ChainIndexResponse
-> Contract w s e ChainIndexResponse
forall w (s :: Row *) e a.
AsContractError e =>
PABReq -> Prism' PABResp a -> Contract w s e a
pabReq (ChainIndexQuery -> PABReq
ChainIndexQueryReq (ChainIndexQuery -> PABReq) -> ChainIndexQuery -> PABReq
forall a b. (a -> b) -> a -> b
$ ValidatorHash -> ChainIndexQuery
E.ValidatorFromHash ValidatorHash
h) Prism' PABResp ChainIndexResponse
E._ChainIndexQueryResp
case ChainIndexResponse
cir of
E.ValidatorHashResponse Maybe (Versioned Validator)
r -> Maybe (Versioned Validator)
-> Contract w s e (Maybe (Versioned Validator))
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe (Versioned Validator)
r
ChainIndexResponse
r -> e -> Contract w s e (Maybe (Versioned Validator))
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (e -> Contract w s e (Maybe (Versioned Validator)))
-> e -> Contract w s e (Maybe (Versioned Validator))
forall a b. (a -> b) -> a -> b
$ AReview e (Text, ChainIndexResponse)
-> (Text, ChainIndexResponse) -> e
forall b (m :: * -> *) t. MonadReader b m => AReview t b -> m t
review AReview e (Text, ChainIndexResponse)
forall r. AsContractError r => Prism' r (Text, ChainIndexResponse)
_ChainIndexContractError (Text
"ValidatorHashResponse", ChainIndexResponse
r)
mintingPolicyFromHash ::
forall w s e.
( AsContractError e
)
=> MintingPolicyHash
-> Contract w s e (Maybe (Versioned MintingPolicy))
mintingPolicyFromHash :: MintingPolicyHash
-> Contract w s e (Maybe (Versioned MintingPolicy))
mintingPolicyFromHash MintingPolicyHash
h = do
ChainIndexResponse
cir <- PABReq
-> Prism' PABResp ChainIndexResponse
-> Contract w s e ChainIndexResponse
forall w (s :: Row *) e a.
AsContractError e =>
PABReq -> Prism' PABResp a -> Contract w s e a
pabReq (ChainIndexQuery -> PABReq
ChainIndexQueryReq (ChainIndexQuery -> PABReq) -> ChainIndexQuery -> PABReq
forall a b. (a -> b) -> a -> b
$ MintingPolicyHash -> ChainIndexQuery
E.MintingPolicyFromHash MintingPolicyHash
h) Prism' PABResp ChainIndexResponse
E._ChainIndexQueryResp
case ChainIndexResponse
cir of
E.MintingPolicyHashResponse Maybe (Versioned MintingPolicy)
r -> Maybe (Versioned MintingPolicy)
-> Contract w s e (Maybe (Versioned MintingPolicy))
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe (Versioned MintingPolicy)
r
ChainIndexResponse
r -> e -> Contract w s e (Maybe (Versioned MintingPolicy))
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (e -> Contract w s e (Maybe (Versioned MintingPolicy)))
-> e -> Contract w s e (Maybe (Versioned MintingPolicy))
forall a b. (a -> b) -> a -> b
$ AReview e (Text, ChainIndexResponse)
-> (Text, ChainIndexResponse) -> e
forall b (m :: * -> *) t. MonadReader b m => AReview t b -> m t
review AReview e (Text, ChainIndexResponse)
forall r. AsContractError r => Prism' r (Text, ChainIndexResponse)
_ChainIndexContractError (Text
"MintingPolicyHashResponse", ChainIndexResponse
r)
stakeValidatorFromHash ::
forall w s e.
( AsContractError e
)
=> StakeValidatorHash
-> Contract w s e (Maybe (Versioned StakeValidator))
stakeValidatorFromHash :: StakeValidatorHash
-> Contract w s e (Maybe (Versioned StakeValidator))
stakeValidatorFromHash StakeValidatorHash
h = do
ChainIndexResponse
cir <- PABReq
-> Prism' PABResp ChainIndexResponse
-> Contract w s e ChainIndexResponse
forall w (s :: Row *) e a.
AsContractError e =>
PABReq -> Prism' PABResp a -> Contract w s e a
pabReq (ChainIndexQuery -> PABReq
ChainIndexQueryReq (ChainIndexQuery -> PABReq) -> ChainIndexQuery -> PABReq
forall a b. (a -> b) -> a -> b
$ StakeValidatorHash -> ChainIndexQuery
E.StakeValidatorFromHash StakeValidatorHash
h) Prism' PABResp ChainIndexResponse
E._ChainIndexQueryResp
case ChainIndexResponse
cir of
E.StakeValidatorHashResponse Maybe (Versioned StakeValidator)
r -> Maybe (Versioned StakeValidator)
-> Contract w s e (Maybe (Versioned StakeValidator))
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe (Versioned StakeValidator)
r
ChainIndexResponse
r -> e -> Contract w s e (Maybe (Versioned StakeValidator))
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (e -> Contract w s e (Maybe (Versioned StakeValidator)))
-> e -> Contract w s e (Maybe (Versioned StakeValidator))
forall a b. (a -> b) -> a -> b
$ AReview e (Text, ChainIndexResponse)
-> (Text, ChainIndexResponse) -> e
forall b (m :: * -> *) t. MonadReader b m => AReview t b -> m t
review AReview e (Text, ChainIndexResponse)
forall r. AsContractError r => Prism' r (Text, ChainIndexResponse)
_ChainIndexContractError (Text
"StakeValidatorHashResponse", ChainIndexResponse
r)
redeemerFromHash ::
forall w s e.
( AsContractError e
)
=> RedeemerHash
-> Contract w s e (Maybe Redeemer)
redeemerFromHash :: RedeemerHash -> Contract w s e (Maybe Redeemer)
redeemerFromHash RedeemerHash
h = do
ChainIndexResponse
cir <- PABReq
-> Prism' PABResp ChainIndexResponse
-> Contract w s e ChainIndexResponse
forall w (s :: Row *) e a.
AsContractError e =>
PABReq -> Prism' PABResp a -> Contract w s e a
pabReq (ChainIndexQuery -> PABReq
ChainIndexQueryReq (ChainIndexQuery -> PABReq) -> ChainIndexQuery -> PABReq
forall a b. (a -> b) -> a -> b
$ RedeemerHash -> ChainIndexQuery
E.RedeemerFromHash RedeemerHash
h) Prism' PABResp ChainIndexResponse
E._ChainIndexQueryResp
case ChainIndexResponse
cir of
E.RedeemerHashResponse Maybe Redeemer
r -> Maybe Redeemer -> Contract w s e (Maybe Redeemer)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe Redeemer
r
ChainIndexResponse
r -> e -> Contract w s e (Maybe Redeemer)
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (e -> Contract w s e (Maybe Redeemer))
-> e -> Contract w s e (Maybe Redeemer)
forall a b. (a -> b) -> a -> b
$ AReview e (Text, ChainIndexResponse)
-> (Text, ChainIndexResponse) -> e
forall b (m :: * -> *) t. MonadReader b m => AReview t b -> m t
review AReview e (Text, ChainIndexResponse)
forall r. AsContractError r => Prism' r (Text, ChainIndexResponse)
_ChainIndexContractError (Text
"RedeemerHashResponse", ChainIndexResponse
r)
txOutFromRef ::
forall w s e.
( AsContractError e
)
=> TxOutRef
-> Contract w s e (Maybe DecoratedTxOut)
txOutFromRef :: TxOutRef -> Contract w s e (Maybe DecoratedTxOut)
txOutFromRef TxOutRef
ref = do
ChainIndexResponse
cir <- PABReq
-> Prism' PABResp ChainIndexResponse
-> Contract w s e ChainIndexResponse
forall w (s :: Row *) e a.
AsContractError e =>
PABReq -> Prism' PABResp a -> Contract w s e a
pabReq (ChainIndexQuery -> PABReq
ChainIndexQueryReq (ChainIndexQuery -> PABReq) -> ChainIndexQuery -> PABReq
forall a b. (a -> b) -> a -> b
$ TxOutRef -> ChainIndexQuery
E.TxOutFromRef TxOutRef
ref) Prism' PABResp ChainIndexResponse
E._ChainIndexQueryResp
case ChainIndexResponse
cir of
E.TxOutRefResponse Maybe DecoratedTxOut
r -> Maybe DecoratedTxOut -> Contract w s e (Maybe DecoratedTxOut)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe DecoratedTxOut
r
ChainIndexResponse
r -> e -> Contract w s e (Maybe DecoratedTxOut)
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (e -> Contract w s e (Maybe DecoratedTxOut))
-> e -> Contract w s e (Maybe DecoratedTxOut)
forall a b. (a -> b) -> a -> b
$ AReview e (Text, ChainIndexResponse)
-> (Text, ChainIndexResponse) -> e
forall b (m :: * -> *) t. MonadReader b m => AReview t b -> m t
review AReview e (Text, ChainIndexResponse)
forall r. AsContractError r => Prism' r (Text, ChainIndexResponse)
_ChainIndexContractError (Text
"TxOutRefResponse", ChainIndexResponse
r)
unspentTxOutFromRef ::
forall w s e.
( AsContractError e
)
=> TxOutRef
-> Contract w s e (Maybe DecoratedTxOut)
unspentTxOutFromRef :: TxOutRef -> Contract w s e (Maybe DecoratedTxOut)
unspentTxOutFromRef TxOutRef
ref = do
ChainIndexResponse
cir <- PABReq
-> Prism' PABResp ChainIndexResponse
-> Contract w s e ChainIndexResponse
forall w (s :: Row *) e a.
AsContractError e =>
PABReq -> Prism' PABResp a -> Contract w s e a
pabReq (ChainIndexQuery -> PABReq
ChainIndexQueryReq (ChainIndexQuery -> PABReq) -> ChainIndexQuery -> PABReq
forall a b. (a -> b) -> a -> b
$ TxOutRef -> ChainIndexQuery
E.UnspentTxOutFromRef TxOutRef
ref) Prism' PABResp ChainIndexResponse
E._ChainIndexQueryResp
case ChainIndexResponse
cir of
E.UnspentTxOutResponse Maybe DecoratedTxOut
r -> Maybe DecoratedTxOut -> Contract w s e (Maybe DecoratedTxOut)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe DecoratedTxOut
r
ChainIndexResponse
r -> e -> Contract w s e (Maybe DecoratedTxOut)
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (e -> Contract w s e (Maybe DecoratedTxOut))
-> e -> Contract w s e (Maybe DecoratedTxOut)
forall a b. (a -> b) -> a -> b
$ AReview e (Text, ChainIndexResponse)
-> (Text, ChainIndexResponse) -> e
forall b (m :: * -> *) t. MonadReader b m => AReview t b -> m t
review AReview e (Text, ChainIndexResponse)
forall r. AsContractError r => Prism' r (Text, ChainIndexResponse)
_ChainIndexContractError (Text
"UnspentTxOutResponse", ChainIndexResponse
r)
txFromTxId ::
forall w s e.
( AsContractError e
)
=> TxId
-> Contract w s e (Maybe ChainIndexTx)
txFromTxId :: TxId -> Contract w s e (Maybe ChainIndexTx)
txFromTxId TxId
txid = do
ChainIndexResponse
cir <- PABReq
-> Prism' PABResp ChainIndexResponse
-> Contract w s e ChainIndexResponse
forall w (s :: Row *) e a.
AsContractError e =>
PABReq -> Prism' PABResp a -> Contract w s e a
pabReq (ChainIndexQuery -> PABReq
ChainIndexQueryReq (ChainIndexQuery -> PABReq) -> ChainIndexQuery -> PABReq
forall a b. (a -> b) -> a -> b
$ TxId -> ChainIndexQuery
E.TxFromTxId TxId
txid) Prism' PABResp ChainIndexResponse
E._ChainIndexQueryResp
case ChainIndexResponse
cir of
E.TxIdResponse Maybe ChainIndexTx
r -> Maybe ChainIndexTx -> Contract w s e (Maybe ChainIndexTx)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe ChainIndexTx
r
ChainIndexResponse
r -> e -> Contract w s e (Maybe ChainIndexTx)
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (e -> Contract w s e (Maybe ChainIndexTx))
-> e -> Contract w s e (Maybe ChainIndexTx)
forall a b. (a -> b) -> a -> b
$ AReview e (Text, ChainIndexResponse)
-> (Text, ChainIndexResponse) -> e
forall b (m :: * -> *) t. MonadReader b m => AReview t b -> m t
review AReview e (Text, ChainIndexResponse)
forall r. AsContractError r => Prism' r (Text, ChainIndexResponse)
_ChainIndexContractError (Text
"TxIdResponse", ChainIndexResponse
r)
utxoRefMembership ::
forall w s e.
( AsContractError e
)
=> TxOutRef
-> Contract w s e IsUtxoResponse
utxoRefMembership :: TxOutRef -> Contract w s e IsUtxoResponse
utxoRefMembership TxOutRef
ref = do
ChainIndexResponse
cir <- PABReq
-> Prism' PABResp ChainIndexResponse
-> Contract w s e ChainIndexResponse
forall w (s :: Row *) e a.
AsContractError e =>
PABReq -> Prism' PABResp a -> Contract w s e a
pabReq (ChainIndexQuery -> PABReq
ChainIndexQueryReq (ChainIndexQuery -> PABReq) -> ChainIndexQuery -> PABReq
forall a b. (a -> b) -> a -> b
$ TxOutRef -> ChainIndexQuery
E.UtxoSetMembership TxOutRef
ref) Prism' PABResp ChainIndexResponse
E._ChainIndexQueryResp
case ChainIndexResponse
cir of
E.UtxoSetMembershipResponse IsUtxoResponse
r -> IsUtxoResponse -> Contract w s e IsUtxoResponse
forall (f :: * -> *) a. Applicative f => a -> f a
pure IsUtxoResponse
r
ChainIndexResponse
r -> e -> Contract w s e IsUtxoResponse
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (e -> Contract w s e IsUtxoResponse)
-> e -> Contract w s e IsUtxoResponse
forall a b. (a -> b) -> a -> b
$ AReview e (Text, ChainIndexResponse)
-> (Text, ChainIndexResponse) -> e
forall b (m :: * -> *) t. MonadReader b m => AReview t b -> m t
review AReview e (Text, ChainIndexResponse)
forall r. AsContractError r => Prism' r (Text, ChainIndexResponse)
_ChainIndexContractError (Text
"UtxoSetMembershipResponse", ChainIndexResponse
r)
utxoRefsAt ::
forall w s e.
( AsContractError e
)
=> PageQuery TxOutRef
-> CardanoAddress
-> Contract w s e UtxosResponse
utxoRefsAt :: PageQuery TxOutRef
-> CardanoAddress -> Contract w s e UtxosResponse
utxoRefsAt PageQuery TxOutRef
pq CardanoAddress
addr = do
ChainIndexResponse
cir <- PABReq
-> Prism' PABResp ChainIndexResponse
-> Contract w s e ChainIndexResponse
forall w (s :: Row *) e a.
AsContractError e =>
PABReq -> Prism' PABResp a -> Contract w s e a
pabReq (ChainIndexQuery -> PABReq
ChainIndexQueryReq (ChainIndexQuery -> PABReq) -> ChainIndexQuery -> PABReq
forall a b. (a -> b) -> a -> b
$ PageQuery TxOutRef -> CardanoAddress -> ChainIndexQuery
E.UtxoSetAtAddress PageQuery TxOutRef
pq CardanoAddress
addr) Prism' PABResp ChainIndexResponse
E._ChainIndexQueryResp
case ChainIndexResponse
cir of
E.UtxoSetAtResponse UtxosResponse
r -> UtxosResponse -> Contract w s e UtxosResponse
forall (f :: * -> *) a. Applicative f => a -> f a
pure UtxosResponse
r
ChainIndexResponse
r -> e -> Contract w s e UtxosResponse
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (e -> Contract w s e UtxosResponse)
-> e -> Contract w s e UtxosResponse
forall a b. (a -> b) -> a -> b
$ AReview e (Text, ChainIndexResponse)
-> (Text, ChainIndexResponse) -> e
forall b (m :: * -> *) t. MonadReader b m => AReview t b -> m t
review AReview e (Text, ChainIndexResponse)
forall r. AsContractError r => Prism' r (Text, ChainIndexResponse)
_ChainIndexContractError (Text
"UtxoSetAtResponse", ChainIndexResponse
r)
utxoRefsWithCurrency ::
forall w s e.
( AsContractError e
)
=> PageQuery TxOutRef
-> AssetClass
-> Contract w s e UtxosResponse
utxoRefsWithCurrency :: PageQuery TxOutRef -> AssetClass -> Contract w s e UtxosResponse
utxoRefsWithCurrency PageQuery TxOutRef
pq AssetClass
assetClass = do
ChainIndexResponse
cir <- PABReq
-> Prism' PABResp ChainIndexResponse
-> Contract w s e ChainIndexResponse
forall w (s :: Row *) e a.
AsContractError e =>
PABReq -> Prism' PABResp a -> Contract w s e a
pabReq (ChainIndexQuery -> PABReq
ChainIndexQueryReq (ChainIndexQuery -> PABReq) -> ChainIndexQuery -> PABReq
forall a b. (a -> b) -> a -> b
$ PageQuery TxOutRef -> AssetClass -> ChainIndexQuery
E.UtxoSetWithCurrency PageQuery TxOutRef
pq AssetClass
assetClass) Prism' PABResp ChainIndexResponse
E._ChainIndexQueryResp
case ChainIndexResponse
cir of
E.UtxoSetWithCurrencyResponse UtxosResponse
r -> UtxosResponse -> Contract w s e UtxosResponse
forall (f :: * -> *) a. Applicative f => a -> f a
pure UtxosResponse
r
ChainIndexResponse
r -> e -> Contract w s e UtxosResponse
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (e -> Contract w s e UtxosResponse)
-> e -> Contract w s e UtxosResponse
forall a b. (a -> b) -> a -> b
$ AReview e (Text, ChainIndexResponse)
-> (Text, ChainIndexResponse) -> e
forall b (m :: * -> *) t. MonadReader b m => AReview t b -> m t
review AReview e (Text, ChainIndexResponse)
forall r. AsContractError r => Prism' r (Text, ChainIndexResponse)
_ChainIndexContractError (Text
"UtxoSetWithCurrencyResponse", ChainIndexResponse
r)
ownUtxos :: forall w s e. (AsContractError e) => Contract w s e (Map TxOutRef DecoratedTxOut)
ownUtxos :: Contract w s e (Map TxOutRef DecoratedTxOut)
ownUtxos = do
NonEmpty CardanoAddress
addrs <- Contract w s e (NonEmpty CardanoAddress)
forall w (s :: Row *) e.
AsContractError e =>
Contract w s e (NonEmpty CardanoAddress)
ownAddresses
[Map TxOutRef DecoratedTxOut] -> Map TxOutRef DecoratedTxOut
forall (t :: * -> *) m. (Foldable t, Monoid m) => t m -> m
fold ([Map TxOutRef DecoratedTxOut] -> Map TxOutRef DecoratedTxOut)
-> Contract w s e [Map TxOutRef DecoratedTxOut]
-> Contract w s e (Map TxOutRef DecoratedTxOut)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (CardanoAddress -> Contract w s e (Map TxOutRef DecoratedTxOut))
-> [CardanoAddress] -> Contract w s e [Map TxOutRef DecoratedTxOut]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM CardanoAddress -> Contract w s e (Map TxOutRef DecoratedTxOut)
forall w (s :: Row *) e.
AsContractError e =>
CardanoAddress -> Contract w s e (Map TxOutRef DecoratedTxOut)
utxosAt (NonEmpty CardanoAddress -> [CardanoAddress]
forall a. NonEmpty a -> [a]
NonEmpty.toList NonEmpty CardanoAddress
addrs)
getUnspentOutput :: AsContractError e => Contract w s e TxOutRef
getUnspentOutput :: Contract w s e TxOutRef
getUnspentOutput = do
Map TxOutRef DecoratedTxOut
utxos <- Contract w s e (Map TxOutRef DecoratedTxOut)
forall w (s :: Row *) e.
AsContractError e =>
Contract w s e (Map TxOutRef DecoratedTxOut)
ownUtxos
case Map TxOutRef DecoratedTxOut -> [TxOutRef]
forall k a. Map k a -> [k]
Map.keys Map TxOutRef DecoratedTxOut
utxos of
TxOutRef
inp : [TxOutRef]
_ -> TxOutRef -> Contract w s e TxOutRef
forall (f :: * -> *) a. Applicative f => a -> f a
pure TxOutRef
inp
[] -> e -> Contract w s e TxOutRef
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (e -> Contract w s e TxOutRef) -> e -> Contract w s e TxOutRef
forall a b. (a -> b) -> a -> b
$ AReview e Text -> Text -> e
forall b (m :: * -> *) t. MonadReader b m => AReview t b -> m t
review AReview e Text
forall r. AsContractError r => Prism' r Text
_OtherContractError Text
"Balanced transaction has no inputs"
queryUnspentTxOutsAt ::
forall w s e.
( AsContractError e
)
=> CardanoAddress
-> PageQuery TxOutRef
-> Contract w s e (QueryResponse [(TxOutRef, DecoratedTxOut)])
queryUnspentTxOutsAt :: CardanoAddress
-> PageQuery TxOutRef
-> Contract w s e (QueryResponse [(TxOutRef, DecoratedTxOut)])
queryUnspentTxOutsAt CardanoAddress
addr PageQuery TxOutRef
pq = do
ChainIndexResponse
cir <- PABReq
-> Prism' PABResp ChainIndexResponse
-> Contract w s e ChainIndexResponse
forall w (s :: Row *) e a.
AsContractError e =>
PABReq -> Prism' PABResp a -> Contract w s e a
pabReq (ChainIndexQuery -> PABReq
ChainIndexQueryReq (ChainIndexQuery -> PABReq) -> ChainIndexQuery -> PABReq
forall a b. (a -> b) -> a -> b
$ PageQuery TxOutRef -> CardanoAddress -> ChainIndexQuery
E.UnspentTxOutSetAtAddress PageQuery TxOutRef
pq CardanoAddress
addr) Prism' PABResp ChainIndexResponse
E._ChainIndexQueryResp
case ChainIndexResponse
cir of
E.UnspentTxOutsAtResponse QueryResponse [(TxOutRef, DecoratedTxOut)]
r -> QueryResponse [(TxOutRef, DecoratedTxOut)]
-> Contract w s e (QueryResponse [(TxOutRef, DecoratedTxOut)])
forall (f :: * -> *) a. Applicative f => a -> f a
pure QueryResponse [(TxOutRef, DecoratedTxOut)]
r
ChainIndexResponse
r -> e -> Contract w s e (QueryResponse [(TxOutRef, DecoratedTxOut)])
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (e -> Contract w s e (QueryResponse [(TxOutRef, DecoratedTxOut)]))
-> e -> Contract w s e (QueryResponse [(TxOutRef, DecoratedTxOut)])
forall a b. (a -> b) -> a -> b
$ AReview e (Text, ChainIndexResponse)
-> (Text, ChainIndexResponse) -> e
forall b (m :: * -> *) t. MonadReader b m => AReview t b -> m t
review AReview e (Text, ChainIndexResponse)
forall r. AsContractError r => Prism' r (Text, ChainIndexResponse)
_ChainIndexContractError (Text
"UnspentTxOutAtResponse", ChainIndexResponse
r)
findReferenceValidatorScripByHash ::
forall w s e.
( AsContractError e
)
=> ValidatorHash
-> CardanoAddress
-> Contract w s e TxOutRef
findReferenceValidatorScripByHash :: ValidatorHash -> CardanoAddress -> Contract w s e TxOutRef
findReferenceValidatorScripByHash ValidatorHash
hash CardanoAddress
address = do
Map TxOutRef DecoratedTxOut
utxos <- CardanoAddress -> Contract w s e (Map TxOutRef DecoratedTxOut)
forall w (s :: Row *) e.
AsContractError e =>
CardanoAddress -> Contract w s e (Map TxOutRef DecoratedTxOut)
utxosAt CardanoAddress
address
Contract w s e TxOutRef
-> (TxOutRef -> Contract w s e TxOutRef)
-> Maybe TxOutRef
-> Contract w s e TxOutRef
forall b a. b -> (a -> b) -> Maybe a -> b
maybe
(e -> Contract w s e TxOutRef
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (e -> Contract w s e TxOutRef) -> e -> Contract w s e TxOutRef
forall a b. (a -> b) -> a -> b
$ AReview e ContractError -> ContractError -> e
forall b (m :: * -> *) t. MonadReader b m => AReview t b -> m t
review AReview e ContractError
forall r. AsContractError r => Prism' r ContractError
_ContractError (ContractError -> e) -> ContractError -> e
forall a b. (a -> b) -> a -> b
$ Text -> ContractError
OtherContractError Text
"Enable to find the referenc script")
TxOutRef -> Contract w s e TxOutRef
forall (f :: * -> *) a. Applicative f => a -> f a
pure
(Maybe TxOutRef -> Contract w s e TxOutRef)
-> Maybe TxOutRef -> Contract w s e TxOutRef
forall a b. (a -> b) -> a -> b
$ ValidatorHash -> Map TxOutRef DecoratedTxOut -> Maybe TxOutRef
searchReferenceScript ValidatorHash
hash Map TxOutRef DecoratedTxOut
utxos
where
searchReferenceScript :: ValidatorHash -> Map TxOutRef DecoratedTxOut -> Maybe TxOutRef
searchReferenceScript :: ValidatorHash -> Map TxOutRef DecoratedTxOut -> Maybe TxOutRef
searchReferenceScript (ValidatorHash BuiltinByteString
h) = let
getReferenceScriptHash :: (() -> Const (First ()) ())
-> (TxOutRef, DecoratedTxOut)
-> Const (First ()) (TxOutRef, DecoratedTxOut)
getReferenceScriptHash = (DecoratedTxOut -> Const (First ()) DecoratedTxOut)
-> (TxOutRef, DecoratedTxOut)
-> Const (First ()) (TxOutRef, DecoratedTxOut)
forall s t a b. Field2 s t a b => Lens s t a b
_2 ((DecoratedTxOut -> Const (First ()) DecoratedTxOut)
-> (TxOutRef, DecoratedTxOut)
-> Const (First ()) (TxOutRef, DecoratedTxOut))
-> ((() -> Const (First ()) ())
-> DecoratedTxOut -> Const (First ()) DecoratedTxOut)
-> (() -> Const (First ()) ())
-> (TxOutRef, DecoratedTxOut)
-> Const (First ()) (TxOutRef, DecoratedTxOut)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Maybe (Versioned Script)
-> Const (First ()) (Maybe (Versioned Script)))
-> DecoratedTxOut -> Const (First ()) DecoratedTxOut
Lens' DecoratedTxOut (Maybe (Versioned Script))
decoratedTxOutReferenceScript
((Maybe (Versioned Script)
-> Const (First ()) (Maybe (Versioned Script)))
-> DecoratedTxOut -> Const (First ()) DecoratedTxOut)
-> ((() -> Const (First ()) ())
-> Maybe (Versioned Script)
-> Const (First ()) (Maybe (Versioned Script)))
-> (() -> Const (First ()) ())
-> DecoratedTxOut
-> Const (First ()) DecoratedTxOut
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Versioned Script -> Const (First ()) (Versioned Script))
-> Maybe (Versioned Script)
-> Const (First ()) (Maybe (Versioned Script))
forall a b. Prism (Maybe a) (Maybe b) a b
_Just ((Versioned Script -> Const (First ()) (Versioned Script))
-> Maybe (Versioned Script)
-> Const (First ()) (Maybe (Versioned Script)))
-> ((() -> Const (First ()) ())
-> Versioned Script -> Const (First ()) (Versioned Script))
-> (() -> Const (First ()) ())
-> Maybe (Versioned Script)
-> Const (First ()) (Maybe (Versioned Script))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Versioned Script -> BuiltinByteString)
-> Optic'
(->) (Const (First ())) (Versioned Script) BuiltinByteString
forall (p :: * -> * -> *) (f :: * -> *) s a.
(Profunctor p, Contravariant f) =>
(s -> a) -> Optic' p f s a
to (ScriptHash -> BuiltinByteString
getScriptHash (ScriptHash -> BuiltinByteString)
-> (Versioned Script -> ScriptHash)
-> Versioned Script
-> BuiltinByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Versioned Script -> ScriptHash
scriptHash)
Optic' (->) (Const (First ())) (Versioned Script) BuiltinByteString
-> ((() -> Const (First ()) ())
-> BuiltinByteString -> Const (First ()) BuiltinByteString)
-> (() -> Const (First ()) ())
-> Versioned Script
-> Const (First ()) (Versioned Script)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BuiltinByteString -> Prism' BuiltinByteString ()
forall a. Eq a => a -> Prism' a ()
only BuiltinByteString
h
in ((TxOutRef, DecoratedTxOut) -> TxOutRef)
-> Maybe (TxOutRef, DecoratedTxOut) -> Maybe TxOutRef
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (TxOutRef, DecoratedTxOut) -> TxOutRef
forall a b. (a, b) -> a
fst
(Maybe (TxOutRef, DecoratedTxOut) -> Maybe TxOutRef)
-> (Map TxOutRef DecoratedTxOut
-> Maybe (TxOutRef, DecoratedTxOut))
-> Map TxOutRef DecoratedTxOut
-> Maybe TxOutRef
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((TxOutRef, DecoratedTxOut) -> Bool)
-> [(TxOutRef, DecoratedTxOut)] -> Maybe (TxOutRef, DecoratedTxOut)
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
find (Maybe () -> Bool
forall a. Maybe a -> Bool
isJust (Maybe () -> Bool)
-> ((TxOutRef, DecoratedTxOut) -> Maybe ())
-> (TxOutRef, DecoratedTxOut)
-> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> Const (First ()) ())
-> (TxOutRef, DecoratedTxOut)
-> Const (First ()) (TxOutRef, DecoratedTxOut))
-> (TxOutRef, DecoratedTxOut) -> Maybe ()
forall s (m :: * -> *) a.
MonadReader s m =>
Getting (First a) s a -> m (Maybe a)
preview (() -> Const (First ()) ())
-> (TxOutRef, DecoratedTxOut)
-> Const (First ()) (TxOutRef, DecoratedTxOut)
getReferenceScriptHash)
([(TxOutRef, DecoratedTxOut)] -> Maybe (TxOutRef, DecoratedTxOut))
-> (Map TxOutRef DecoratedTxOut -> [(TxOutRef, DecoratedTxOut)])
-> Map TxOutRef DecoratedTxOut
-> Maybe (TxOutRef, DecoratedTxOut)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Map TxOutRef DecoratedTxOut -> [(TxOutRef, DecoratedTxOut)]
forall k a. Map k a -> [(k, a)]
Map.toList
utxosAt ::
forall w s e.
( AsContractError e
)
=> CardanoAddress
-> Contract w s e (Map TxOutRef DecoratedTxOut)
utxosAt :: CardanoAddress -> Contract w s e (Map TxOutRef DecoratedTxOut)
utxosAt CardanoAddress
addr =
[(TxOutRef, DecoratedTxOut)] -> Map TxOutRef DecoratedTxOut
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList ([(TxOutRef, DecoratedTxOut)] -> Map TxOutRef DecoratedTxOut)
-> ([[(TxOutRef, DecoratedTxOut)]] -> [(TxOutRef, DecoratedTxOut)])
-> [[(TxOutRef, DecoratedTxOut)]]
-> Map TxOutRef DecoratedTxOut
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[(TxOutRef, DecoratedTxOut)]] -> [(TxOutRef, DecoratedTxOut)]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([[(TxOutRef, DecoratedTxOut)]] -> Map TxOutRef DecoratedTxOut)
-> Contract w s e [[(TxOutRef, DecoratedTxOut)]]
-> Contract w s e (Map TxOutRef DecoratedTxOut)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (PageQuery TxOutRef
-> Contract w s e (QueryResponse [(TxOutRef, DecoratedTxOut)]))
-> Contract w s e [[(TxOutRef, DecoratedTxOut)]]
forall (m :: * -> *) a.
Monad m =>
(PageQuery TxOutRef -> m (QueryResponse a)) -> m [a]
collectQueryResponse (CardanoAddress
-> PageQuery TxOutRef
-> Contract w s e (QueryResponse [(TxOutRef, DecoratedTxOut)])
forall w (s :: Row *) e.
AsContractError e =>
CardanoAddress
-> PageQuery TxOutRef
-> Contract w s e (QueryResponse [(TxOutRef, DecoratedTxOut)])
queryUnspentTxOutsAt CardanoAddress
addr)
utxosTxOutTxAt ::
forall w s e.
( AsContractError e
)
=> CardanoAddress
-> Contract w s e (Map TxOutRef (DecoratedTxOut, ChainIndexTx))
utxosTxOutTxAt :: CardanoAddress
-> Contract w s e (Map TxOutRef (DecoratedTxOut, ChainIndexTx))
utxosTxOutTxAt CardanoAddress
addr = do
Map TxOutRef DecoratedTxOut
utxos <- CardanoAddress -> Contract w s e (Map TxOutRef DecoratedTxOut)
forall w (s :: Row *) e.
AsContractError e =>
CardanoAddress -> Contract w s e (Map TxOutRef DecoratedTxOut)
utxosAt CardanoAddress
addr
StateT
(Map TxId ChainIndexTx)
(Contract w s e)
(Map TxOutRef (DecoratedTxOut, ChainIndexTx))
-> Map TxId ChainIndexTx
-> Contract w s e (Map TxOutRef (DecoratedTxOut, ChainIndexTx))
forall (m :: * -> *) s a. Monad m => StateT s m a -> s -> m a
evalStateT ((TxOutRef
-> DecoratedTxOut
-> StateT
(Map TxId ChainIndexTx)
(Contract w s e)
(Maybe (DecoratedTxOut, ChainIndexTx)))
-> Map TxOutRef DecoratedTxOut
-> StateT
(Map TxId ChainIndexTx)
(Contract w s e)
(Map TxOutRef (DecoratedTxOut, ChainIndexTx))
forall (f :: * -> *) k a b.
Applicative f =>
(k -> a -> f (Maybe b)) -> Map k a -> f (Map k b)
Map.traverseMaybeWithKey TxOutRef
-> DecoratedTxOut
-> StateT
(Map TxId ChainIndexTx)
(Contract w s e)
(Maybe (DecoratedTxOut, ChainIndexTx))
go Map TxOutRef DecoratedTxOut
utxos) Map TxId ChainIndexTx
forall a. Monoid a => a
mempty
where
go :: TxOutRef
-> DecoratedTxOut
-> StateT (Map TxId ChainIndexTx) (Contract w s e) (Maybe (DecoratedTxOut, ChainIndexTx))
go :: TxOutRef
-> DecoratedTxOut
-> StateT
(Map TxId ChainIndexTx)
(Contract w s e)
(Maybe (DecoratedTxOut, ChainIndexTx))
go TxOutRef
ref DecoratedTxOut
out = (Map TxId ChainIndexTx
-> Contract
w
s
e
(Maybe (DecoratedTxOut, ChainIndexTx), Map TxId ChainIndexTx))
-> StateT
(Map TxId ChainIndexTx)
(Contract w s e)
(Maybe (DecoratedTxOut, ChainIndexTx))
forall s (m :: * -> *) a. (s -> m (a, s)) -> StateT s m a
StateT ((Map TxId ChainIndexTx
-> Contract
w
s
e
(Maybe (DecoratedTxOut, ChainIndexTx), Map TxId ChainIndexTx))
-> StateT
(Map TxId ChainIndexTx)
(Contract w s e)
(Maybe (DecoratedTxOut, ChainIndexTx)))
-> (Map TxId ChainIndexTx
-> Contract
w
s
e
(Maybe (DecoratedTxOut, ChainIndexTx), Map TxId ChainIndexTx))
-> StateT
(Map TxId ChainIndexTx)
(Contract w s e)
(Maybe (DecoratedTxOut, ChainIndexTx))
forall a b. (a -> b) -> a -> b
$ \Map TxId ChainIndexTx
lookupTx -> do
let txid :: TxId
txid = TxOutRef -> TxId
txOutRefId TxOutRef
ref
case TxId -> Map TxId ChainIndexTx -> Maybe ChainIndexTx
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup TxId
txid Map TxId ChainIndexTx
lookupTx of
Just ChainIndexTx
tx ->
(Maybe (DecoratedTxOut, ChainIndexTx), Map TxId ChainIndexTx)
-> Contract
w s e (Maybe (DecoratedTxOut, ChainIndexTx), Map TxId ChainIndexTx)
forall (f :: * -> *) a. Applicative f => a -> f a
pure ((DecoratedTxOut, ChainIndexTx)
-> Maybe (DecoratedTxOut, ChainIndexTx)
forall a. a -> Maybe a
Just (DecoratedTxOut
out, ChainIndexTx
tx), Map TxId ChainIndexTx
lookupTx)
Maybe ChainIndexTx
Nothing -> do
Maybe ChainIndexTx
txM <- TxId -> Contract w s e (Maybe ChainIndexTx)
forall w (s :: Row *) e.
AsContractError e =>
TxId -> Contract w s e (Maybe ChainIndexTx)
txFromTxId TxId
txid
case Maybe ChainIndexTx
txM of
Just ChainIndexTx
tx ->
(Maybe (DecoratedTxOut, ChainIndexTx), Map TxId ChainIndexTx)
-> Contract
w s e (Maybe (DecoratedTxOut, ChainIndexTx), Map TxId ChainIndexTx)
forall (f :: * -> *) a. Applicative f => a -> f a
pure ((DecoratedTxOut, ChainIndexTx)
-> Maybe (DecoratedTxOut, ChainIndexTx)
forall a. a -> Maybe a
Just (DecoratedTxOut
out, ChainIndexTx
tx), TxId
-> ChainIndexTx -> Map TxId ChainIndexTx -> Map TxId ChainIndexTx
forall k a. Ord k => k -> a -> Map k a -> Map k a
Map.insert TxId
txid ChainIndexTx
tx Map TxId ChainIndexTx
lookupTx)
Maybe ChainIndexTx
Nothing ->
(Maybe (DecoratedTxOut, ChainIndexTx), Map TxId ChainIndexTx)
-> Contract
w s e (Maybe (DecoratedTxOut, ChainIndexTx), Map TxId ChainIndexTx)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Maybe (DecoratedTxOut, ChainIndexTx)
forall a. Maybe a
Nothing, Map TxId ChainIndexTx
lookupTx)
utxosTxOutTxFromTx ::
AsContractError e
=> ChainIndexTx
-> Contract w s e [(TxOutRef, (DecoratedTxOut, ChainIndexTx))]
utxosTxOutTxFromTx :: ChainIndexTx
-> Contract w s e [(TxOutRef, (DecoratedTxOut, ChainIndexTx))]
utxosTxOutTxFromTx ChainIndexTx
tx =
[Maybe (TxOutRef, (DecoratedTxOut, ChainIndexTx))]
-> [(TxOutRef, (DecoratedTxOut, ChainIndexTx))]
forall a. [Maybe a] -> [a]
catMaybes ([Maybe (TxOutRef, (DecoratedTxOut, ChainIndexTx))]
-> [(TxOutRef, (DecoratedTxOut, ChainIndexTx))])
-> Contract
w s e [Maybe (TxOutRef, (DecoratedTxOut, ChainIndexTx))]
-> Contract w s e [(TxOutRef, (DecoratedTxOut, ChainIndexTx))]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (TxOutRef
-> Contract
w s e (Maybe (TxOutRef, (DecoratedTxOut, ChainIndexTx))))
-> [TxOutRef]
-> Contract
w s e [Maybe (TxOutRef, (DecoratedTxOut, ChainIndexTx))]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM TxOutRef
-> Contract
w s e (Maybe (TxOutRef, (DecoratedTxOut, ChainIndexTx)))
mkOutRef (ChainIndexTx -> [TxOutRef]
txOutRefs ChainIndexTx
tx)
where
mkOutRef :: TxOutRef
-> Contract
w s e (Maybe (TxOutRef, (DecoratedTxOut, ChainIndexTx)))
mkOutRef TxOutRef
txOutRef = do
Maybe DecoratedTxOut
decoratedTxOutM <- TxOutRef -> Contract w s e (Maybe DecoratedTxOut)
forall w (s :: Row *) e.
AsContractError e =>
TxOutRef -> Contract w s e (Maybe DecoratedTxOut)
unspentTxOutFromRef TxOutRef
txOutRef
Maybe (TxOutRef, (DecoratedTxOut, ChainIndexTx))
-> Contract
w s e (Maybe (TxOutRef, (DecoratedTxOut, ChainIndexTx)))
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Maybe (TxOutRef, (DecoratedTxOut, ChainIndexTx))
-> Contract
w s e (Maybe (TxOutRef, (DecoratedTxOut, ChainIndexTx))))
-> Maybe (TxOutRef, (DecoratedTxOut, ChainIndexTx))
-> Contract
w s e (Maybe (TxOutRef, (DecoratedTxOut, ChainIndexTx)))
forall a b. (a -> b) -> a -> b
$ Maybe DecoratedTxOut
decoratedTxOutM Maybe DecoratedTxOut
-> (DecoratedTxOut
-> Maybe (TxOutRef, (DecoratedTxOut, ChainIndexTx)))
-> Maybe (TxOutRef, (DecoratedTxOut, ChainIndexTx))
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \DecoratedTxOut
decoratedTxOut -> (TxOutRef, (DecoratedTxOut, ChainIndexTx))
-> Maybe (TxOutRef, (DecoratedTxOut, ChainIndexTx))
forall (f :: * -> *) a. Applicative f => a -> f a
pure (TxOutRef
txOutRef, (DecoratedTxOut
decoratedTxOut, ChainIndexTx
tx))
foldTxoRefsAt ::
forall w s e a.
( AsContractError e
)
=> (a -> Page TxOutRef -> Contract w s e a)
-> a
-> CardanoAddress
-> Contract w s e a
foldTxoRefsAt :: (a -> Page TxOutRef -> Contract w s e a)
-> a -> CardanoAddress -> Contract w s e a
foldTxoRefsAt a -> Page TxOutRef -> Contract w s e a
f a
ini CardanoAddress
addr = a -> Maybe (PageQuery TxOutRef) -> Contract w s e a
go a
ini (PageQuery TxOutRef -> Maybe (PageQuery TxOutRef)
forall a. a -> Maybe a
Just PageQuery TxOutRef
forall a. Default a => a
def)
where
go :: a -> Maybe (PageQuery TxOutRef) -> Contract w s e a
go a
acc Maybe (PageQuery TxOutRef)
Nothing = a -> Contract w s e a
forall (f :: * -> *) a. Applicative f => a -> f a
pure a
acc
go a
acc (Just PageQuery TxOutRef
pq) = do
Page TxOutRef
page <- TxosResponse -> Page TxOutRef
paget (TxosResponse -> Page TxOutRef)
-> Contract w s e TxosResponse -> Contract w s e (Page TxOutRef)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> PageQuery TxOutRef -> CardanoAddress -> Contract w s e TxosResponse
forall w (s :: Row *) e.
AsContractError e =>
PageQuery TxOutRef -> CardanoAddress -> Contract w s e TxosResponse
txoRefsAt PageQuery TxOutRef
pq CardanoAddress
addr
a
newAcc <- a -> Page TxOutRef -> Contract w s e a
f a
acc Page TxOutRef
page
a -> Maybe (PageQuery TxOutRef) -> Contract w s e a
go a
newAcc (Page TxOutRef -> Maybe (PageQuery TxOutRef)
forall a. Page a -> Maybe (PageQuery a)
nextPageQuery Page TxOutRef
page)
txsAt ::
forall w s e.
( AsContractError e
)
=> CardanoAddress
-> Contract w s e [ChainIndexTx]
txsAt :: CardanoAddress -> Contract w s e [ChainIndexTx]
txsAt CardanoAddress
addr = do
([ChainIndexTx] -> Page TxOutRef -> Contract w s e [ChainIndexTx])
-> [ChainIndexTx]
-> CardanoAddress
-> Contract w s e [ChainIndexTx]
forall w (s :: Row *) e a.
AsContractError e =>
(a -> Page TxOutRef -> Contract w s e a)
-> a -> CardanoAddress -> Contract w s e a
foldTxoRefsAt [ChainIndexTx] -> Page TxOutRef -> Contract w s e [ChainIndexTx]
forall e w (s :: Row *).
AsContractError e =>
[ChainIndexTx] -> Page TxOutRef -> Contract w s e [ChainIndexTx]
f [] CardanoAddress
addr
where
f :: [ChainIndexTx] -> Page TxOutRef -> Contract w s e [ChainIndexTx]
f [ChainIndexTx]
acc Page TxOutRef
page = do
let txoRefs :: [TxOutRef]
txoRefs = Page TxOutRef -> [TxOutRef]
forall a. Page a -> [a]
pageItems Page TxOutRef
page
let txIds :: [TxId]
txIds = TxOutRef -> TxId
txOutRefId (TxOutRef -> TxId) -> [TxOutRef] -> [TxId]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [TxOutRef]
txoRefs
[ChainIndexTx]
txs <- [TxId] -> Contract w s e [ChainIndexTx]
forall w (s :: Row *) e.
AsContractError e =>
[TxId] -> Contract w s e [ChainIndexTx]
txsFromTxIds [TxId]
txIds
[ChainIndexTx] -> Contract w s e [ChainIndexTx]
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([ChainIndexTx] -> Contract w s e [ChainIndexTx])
-> [ChainIndexTx] -> Contract w s e [ChainIndexTx]
forall a b. (a -> b) -> a -> b
$ [ChainIndexTx]
acc [ChainIndexTx] -> [ChainIndexTx] -> [ChainIndexTx]
forall a. Semigroup a => a -> a -> a
<> [ChainIndexTx]
txs
txoRefsAt ::
forall w s e.
( AsContractError e
)
=> PageQuery TxOutRef
-> CardanoAddress
-> Contract w s e TxosResponse
txoRefsAt :: PageQuery TxOutRef -> CardanoAddress -> Contract w s e TxosResponse
txoRefsAt PageQuery TxOutRef
pq CardanoAddress
addr = do
ChainIndexResponse
cir <- PABReq
-> Prism' PABResp ChainIndexResponse
-> Contract w s e ChainIndexResponse
forall w (s :: Row *) e a.
AsContractError e =>
PABReq -> Prism' PABResp a -> Contract w s e a
pabReq (ChainIndexQuery -> PABReq
ChainIndexQueryReq (ChainIndexQuery -> PABReq) -> ChainIndexQuery -> PABReq
forall a b. (a -> b) -> a -> b
$ PageQuery TxOutRef -> CardanoAddress -> ChainIndexQuery
E.TxoSetAtAddress PageQuery TxOutRef
pq CardanoAddress
addr) Prism' PABResp ChainIndexResponse
E._ChainIndexQueryResp
case ChainIndexResponse
cir of
E.TxoSetAtResponse TxosResponse
r -> TxosResponse -> Contract w s e TxosResponse
forall (f :: * -> *) a. Applicative f => a -> f a
pure TxosResponse
r
ChainIndexResponse
r -> e -> Contract w s e TxosResponse
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (e -> Contract w s e TxosResponse)
-> e -> Contract w s e TxosResponse
forall a b. (a -> b) -> a -> b
$ AReview e (Text, ChainIndexResponse)
-> (Text, ChainIndexResponse) -> e
forall b (m :: * -> *) t. MonadReader b m => AReview t b -> m t
review AReview e (Text, ChainIndexResponse)
forall r. AsContractError r => Prism' r (Text, ChainIndexResponse)
_ChainIndexContractError (Text
"TxoSetAtAddress", ChainIndexResponse
r)
txsFromTxIds ::
forall w s e.
( AsContractError e
)
=> [TxId]
-> Contract w s e [ChainIndexTx]
txsFromTxIds :: [TxId] -> Contract w s e [ChainIndexTx]
txsFromTxIds [TxId]
txid = do
ChainIndexResponse
cir <- PABReq
-> Prism' PABResp ChainIndexResponse
-> Contract w s e ChainIndexResponse
forall w (s :: Row *) e a.
AsContractError e =>
PABReq -> Prism' PABResp a -> Contract w s e a
pabReq (ChainIndexQuery -> PABReq
ChainIndexQueryReq (ChainIndexQuery -> PABReq) -> ChainIndexQuery -> PABReq
forall a b. (a -> b) -> a -> b
$ [TxId] -> ChainIndexQuery
E.TxsFromTxIds [TxId]
txid) Prism' PABResp ChainIndexResponse
E._ChainIndexQueryResp
case ChainIndexResponse
cir of
E.TxIdsResponse [ChainIndexTx]
r -> [ChainIndexTx] -> Contract w s e [ChainIndexTx]
forall (f :: * -> *) a. Applicative f => a -> f a
pure [ChainIndexTx]
r
ChainIndexResponse
r -> e -> Contract w s e [ChainIndexTx]
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (e -> Contract w s e [ChainIndexTx])
-> e -> Contract w s e [ChainIndexTx]
forall a b. (a -> b) -> a -> b
$ AReview e (Text, ChainIndexResponse)
-> (Text, ChainIndexResponse) -> e
forall b (m :: * -> *) t. MonadReader b m => AReview t b -> m t
review AReview e (Text, ChainIndexResponse)
forall r. AsContractError r => Prism' r (Text, ChainIndexResponse)
_ChainIndexContractError (Text
"TxIdsResponse", ChainIndexResponse
r)
getTip ::
forall w s e.
( AsContractError e
)
=> Contract w s e Tip
getTip :: Contract w s e Tip
getTip = do
ChainIndexResponse
cir <- PABReq
-> Prism' PABResp ChainIndexResponse
-> Contract w s e ChainIndexResponse
forall w (s :: Row *) e a.
AsContractError e =>
PABReq -> Prism' PABResp a -> Contract w s e a
pabReq (ChainIndexQuery -> PABReq
ChainIndexQueryReq ChainIndexQuery
E.GetTip) Prism' PABResp ChainIndexResponse
E._ChainIndexQueryResp
case ChainIndexResponse
cir of
E.GetTipResponse Tip
r -> Tip -> Contract w s e Tip
forall (f :: * -> *) a. Applicative f => a -> f a
pure Tip
r
ChainIndexResponse
r -> e -> Contract w s e Tip
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (e -> Contract w s e Tip) -> e -> Contract w s e Tip
forall a b. (a -> b) -> a -> b
$ AReview e (Text, ChainIndexResponse)
-> (Text, ChainIndexResponse) -> e
forall b (m :: * -> *) t. MonadReader b m => AReview t b -> m t
review AReview e (Text, ChainIndexResponse)
forall r. AsContractError r => Prism' r (Text, ChainIndexResponse)
_ChainIndexContractError (Text
"GetTipResponse", ChainIndexResponse
r)
watchAddressUntilSlot ::
forall w s e.
( AsContractError e
)
=> CardanoAddress
-> Slot
-> Contract w s e (Map TxOutRef DecoratedTxOut)
watchAddressUntilSlot :: CardanoAddress
-> Slot -> Contract w s e (Map TxOutRef DecoratedTxOut)
watchAddressUntilSlot CardanoAddress
a Slot
slot = Slot -> Contract w s e Slot
forall w (s :: Row *) e.
AsContractError e =>
Slot -> Contract w s e Slot
awaitSlot Slot
slot Contract w s e Slot
-> Contract w s e (Map TxOutRef DecoratedTxOut)
-> Contract w s e (Map TxOutRef DecoratedTxOut)
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> CardanoAddress -> Contract w s e (Map TxOutRef DecoratedTxOut)
forall w (s :: Row *) e.
AsContractError e =>
CardanoAddress -> Contract w s e (Map TxOutRef DecoratedTxOut)
utxosAt CardanoAddress
a
watchAddressUntilTime ::
forall w s e.
( AsContractError e
)
=> CardanoAddress
-> POSIXTime
-> Contract w s e (Map TxOutRef DecoratedTxOut)
watchAddressUntilTime :: CardanoAddress
-> POSIXTime -> Contract w s e (Map TxOutRef DecoratedTxOut)
watchAddressUntilTime CardanoAddress
a POSIXTime
time = POSIXTime -> Contract w s e POSIXTime
forall w (s :: Row *) e.
AsContractError e =>
POSIXTime -> Contract w s e POSIXTime
awaitTime POSIXTime
time Contract w s e POSIXTime
-> Contract w s e (Map TxOutRef DecoratedTxOut)
-> Contract w s e (Map TxOutRef DecoratedTxOut)
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> CardanoAddress -> Contract w s e (Map TxOutRef DecoratedTxOut)
forall w (s :: Row *) e.
AsContractError e =>
CardanoAddress -> Contract w s e (Map TxOutRef DecoratedTxOut)
utxosAt CardanoAddress
a
awaitUtxoSpent ::
forall w s e.
( AsContractError e
)
=> TxOutRef
-> Contract w s e ChainIndexTx
awaitUtxoSpent :: TxOutRef -> Contract w s e ChainIndexTx
awaitUtxoSpent TxOutRef
ref = do
TxIn
txIn <- (ToCardanoError -> Contract w s e TxIn)
-> (TxIn -> Contract w s e TxIn)
-> Either ToCardanoError TxIn
-> Contract w s e TxIn
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (e -> Contract w s e TxIn
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (e -> Contract w s e TxIn)
-> (ToCardanoError -> e) -> ToCardanoError -> Contract w s e TxIn
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AReview e ToCardanoError -> ToCardanoError -> e
forall b (m :: * -> *) t. MonadReader b m => AReview t b -> m t
review AReview e ToCardanoError
forall r. AsContractError r => Prism' r ToCardanoError
_ToCardanoConvertContractError) TxIn -> Contract w s e TxIn
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either ToCardanoError TxIn -> Contract w s e TxIn)
-> Either ToCardanoError TxIn -> Contract w s e TxIn
forall a b. (a -> b) -> a -> b
$ TxOutRef -> Either ToCardanoError TxIn
toCardanoTxIn TxOutRef
ref
PABReq
-> Prism' PABResp ChainIndexTx -> Contract w s e ChainIndexTx
forall w (s :: Row *) e a.
AsContractError e =>
PABReq -> Prism' PABResp a -> Contract w s e a
pabReq (TxIn -> PABReq
AwaitUtxoSpentReq TxIn
txIn) Prism' PABResp ChainIndexTx
E._AwaitUtxoSpentResp
utxoIsSpent ::
forall w s e.
( AsContractError e
)
=> TxOutRef
-> Promise w s e ChainIndexTx
utxoIsSpent :: TxOutRef -> Promise w s e ChainIndexTx
utxoIsSpent = Contract w s e ChainIndexTx -> Promise w s e ChainIndexTx
forall w (s :: Row *) e a. Contract w s e a -> Promise w s e a
Promise (Contract w s e ChainIndexTx -> Promise w s e ChainIndexTx)
-> (TxOutRef -> Contract w s e ChainIndexTx)
-> TxOutRef
-> Promise w s e ChainIndexTx
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TxOutRef -> Contract w s e ChainIndexTx
forall w (s :: Row *) e.
AsContractError e =>
TxOutRef -> Contract w s e ChainIndexTx
awaitUtxoSpent
awaitUtxoProduced ::
forall w s e .
( AsContractError e
)
=> CardanoAddress
-> Contract w s e (NonEmpty ChainIndexTx)
awaitUtxoProduced :: CardanoAddress -> Contract w s e (NonEmpty ChainIndexTx)
awaitUtxoProduced CardanoAddress
address =
PABReq
-> Prism' PABResp (NonEmpty ChainIndexTx)
-> Contract w s e (NonEmpty ChainIndexTx)
forall w (s :: Row *) e a.
AsContractError e =>
PABReq -> Prism' PABResp a -> Contract w s e a
pabReq (CardanoAddress -> PABReq
AwaitUtxoProducedReq CardanoAddress
address) Prism' PABResp (NonEmpty ChainIndexTx)
E._AwaitUtxoProducedResp
utxoIsProduced ::
forall w s e .
( AsContractError e
)
=> CardanoAddress
-> Promise w s e (NonEmpty ChainIndexTx)
utxoIsProduced :: CardanoAddress -> Promise w s e (NonEmpty ChainIndexTx)
utxoIsProduced = Contract w s e (NonEmpty ChainIndexTx)
-> Promise w s e (NonEmpty ChainIndexTx)
forall w (s :: Row *) e a. Contract w s e a -> Promise w s e a
Promise (Contract w s e (NonEmpty ChainIndexTx)
-> Promise w s e (NonEmpty ChainIndexTx))
-> (CardanoAddress -> Contract w s e (NonEmpty ChainIndexTx))
-> CardanoAddress
-> Promise w s e (NonEmpty ChainIndexTx)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CardanoAddress -> Contract w s e (NonEmpty ChainIndexTx)
forall w (s :: Row *) e.
AsContractError e =>
CardanoAddress -> Contract w s e (NonEmpty ChainIndexTx)
awaitUtxoProduced
fundsAtAddressGt
:: forall w s e.
( AsContractError e
)
=> CardanoAddress
-> C.Value
-> Contract w s e (Map TxOutRef DecoratedTxOut)
fundsAtAddressGt :: CardanoAddress
-> Value -> Contract w s e (Map TxOutRef DecoratedTxOut)
fundsAtAddressGt CardanoAddress
addr Value
vl =
(Value -> Bool)
-> CardanoAddress -> Contract w s e (Map TxOutRef DecoratedTxOut)
forall w (s :: Row *) e.
AsContractError e =>
(Value -> Bool)
-> CardanoAddress -> Contract w s e (Map TxOutRef DecoratedTxOut)
fundsAtAddressCondition (\Value
presentVal -> Bool -> Bool
not (Value
presentVal Value -> Value -> Bool
`valueLeq` Value
vl)) CardanoAddress
addr
fundsAtAddressCondition
:: forall w s e.
( AsContractError e
)
=> (C.Value -> Bool)
-> CardanoAddress
-> Contract w s e (Map TxOutRef DecoratedTxOut)
fundsAtAddressCondition :: (Value -> Bool)
-> CardanoAddress -> Contract w s e (Map TxOutRef DecoratedTxOut)
fundsAtAddressCondition Value -> Bool
condition CardanoAddress
addr = (() -> Contract w s e (Either () (Map TxOutRef DecoratedTxOut)))
-> () -> Contract w s e (Map TxOutRef DecoratedTxOut)
forall (m :: * -> *) a b.
Monad m =>
(a -> m (Either a b)) -> a -> m b
loopM () -> Contract w s e (Either () (Map TxOutRef DecoratedTxOut))
go () where
go :: () -> Contract w s e (Either () (Map TxOutRef DecoratedTxOut))
go () = do
Map TxOutRef DecoratedTxOut
cur <- CardanoAddress -> Contract w s e (Map TxOutRef DecoratedTxOut)
forall w (s :: Row *) e.
AsContractError e =>
CardanoAddress -> Contract w s e (Map TxOutRef DecoratedTxOut)
utxosAt CardanoAddress
addr
let presentVal :: Value
presentVal = (DecoratedTxOut -> Value) -> Map TxOutRef DecoratedTxOut -> Value
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap (Getting Value DecoratedTxOut Value -> DecoratedTxOut -> Value
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting Value DecoratedTxOut Value
Lens' DecoratedTxOut Value
decoratedTxOutValue) Map TxOutRef DecoratedTxOut
cur
if Value -> Bool
condition Value
presentVal
then Either () (Map TxOutRef DecoratedTxOut)
-> Contract w s e (Either () (Map TxOutRef DecoratedTxOut))
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Map TxOutRef DecoratedTxOut
-> Either () (Map TxOutRef DecoratedTxOut)
forall a b. b -> Either a b
Right Map TxOutRef DecoratedTxOut
cur)
else CardanoAddress -> Contract w s e (NonEmpty ChainIndexTx)
forall w (s :: Row *) e.
AsContractError e =>
CardanoAddress -> Contract w s e (NonEmpty ChainIndexTx)
awaitUtxoProduced CardanoAddress
addr Contract w s e (NonEmpty ChainIndexTx)
-> Contract w s e (Either () (Map TxOutRef DecoratedTxOut))
-> Contract w s e (Either () (Map TxOutRef DecoratedTxOut))
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Either () (Map TxOutRef DecoratedTxOut)
-> Contract w s e (Either () (Map TxOutRef DecoratedTxOut))
forall (f :: * -> *) a. Applicative f => a -> f a
pure (() -> Either () (Map TxOutRef DecoratedTxOut)
forall a b. a -> Either a b
Left ())
fundsAtAddressGeq
:: forall w s e.
( AsContractError e
)
=> CardanoAddress
-> C.Value
-> Contract w s e (Map TxOutRef DecoratedTxOut)
fundsAtAddressGeq :: CardanoAddress
-> Value -> Contract w s e (Map TxOutRef DecoratedTxOut)
fundsAtAddressGeq CardanoAddress
addr Value
vl =
(Value -> Bool)
-> CardanoAddress -> Contract w s e (Map TxOutRef DecoratedTxOut)
forall w (s :: Row *) e.
AsContractError e =>
(Value -> Bool)
-> CardanoAddress -> Contract w s e (Map TxOutRef DecoratedTxOut)
fundsAtAddressCondition (\Value
presentVal -> Value
presentVal Value -> Value -> Bool
`valueGeq` Value
vl) CardanoAddress
addr
awaitTxStatusChange :: forall w s e. AsContractError e => C.TxId -> Contract w s e TxStatus
awaitTxStatusChange :: TxId -> Contract w s e TxStatus
awaitTxStatusChange TxId
i = PABReq -> Prism' PABResp TxStatus -> Contract w s e TxStatus
forall w (s :: Row *) e a.
AsContractError e =>
PABReq -> Prism' PABResp a -> Contract w s e a
pabReq (TxId -> PABReq
AwaitTxStatusChangeReq TxId
i) (TxId -> Prism' PABResp TxStatus
E._AwaitTxStatusChangeResp' TxId
i)
awaitTxConfirmed :: forall w s e. (AsContractError e) => C.TxId -> Contract w s e ()
awaitTxConfirmed :: TxId -> Contract w s e ()
awaitTxConfirmed TxId
i = Contract w s e ()
go where
go :: Contract w s e ()
go = do
TxStatus
newStatus <- TxId -> Contract w s e TxStatus
forall w (s :: Row *) e.
AsContractError e =>
TxId -> Contract w s e TxStatus
awaitTxStatusChange TxId
i
case TxStatus
newStatus of
TxStatus
Unknown -> Contract w s e ()
go
TxStatus
_ -> () -> Contract w s e ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
isTxConfirmed :: forall w s e. (AsContractError e) => C.TxId -> Promise w s e ()
isTxConfirmed :: TxId -> Promise w s e ()
isTxConfirmed = Contract w s e () -> Promise w s e ()
forall w (s :: Row *) e a. Contract w s e a -> Promise w s e a
Promise (Contract w s e () -> Promise w s e ())
-> (TxId -> Contract w s e ()) -> TxId -> Promise w s e ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TxId -> Contract w s e ()
forall w (s :: Row *) e.
AsContractError e =>
TxId -> Contract w s e ()
awaitTxConfirmed
awaitTxOutStatusChange :: forall w s e. AsContractError e => TxOutRef -> Contract w s e TxOutStatus
awaitTxOutStatusChange :: TxOutRef -> Contract w s e TxOutStatus
awaitTxOutStatusChange TxOutRef
ref = do
TxIn
txIn <- (ToCardanoError -> Contract w s e TxIn)
-> (TxIn -> Contract w s e TxIn)
-> Either ToCardanoError TxIn
-> Contract w s e TxIn
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (e -> Contract w s e TxIn
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (e -> Contract w s e TxIn)
-> (ToCardanoError -> e) -> ToCardanoError -> Contract w s e TxIn
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AReview e ToCardanoError -> ToCardanoError -> e
forall b (m :: * -> *) t. MonadReader b m => AReview t b -> m t
review AReview e ToCardanoError
forall r. AsContractError r => Prism' r ToCardanoError
_ToCardanoConvertContractError) TxIn -> Contract w s e TxIn
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either ToCardanoError TxIn -> Contract w s e TxIn)
-> Either ToCardanoError TxIn -> Contract w s e TxIn
forall a b. (a -> b) -> a -> b
$ TxOutRef -> Either ToCardanoError TxIn
toCardanoTxIn TxOutRef
ref
(TxIn, TxOutStatus) -> TxOutStatus
forall a b. (a, b) -> b
snd ((TxIn, TxOutStatus) -> TxOutStatus)
-> Contract w s e (TxIn, TxOutStatus) -> Contract w s e TxOutStatus
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> PABReq
-> Prism' PABResp (TxIn, TxOutStatus)
-> Contract w s e (TxIn, TxOutStatus)
forall w (s :: Row *) e a.
AsContractError e =>
PABReq -> Prism' PABResp a -> Contract w s e a
pabReq (TxIn -> PABReq
AwaitTxOutStatusChangeReq TxIn
txIn) Prism' PABResp (TxIn, TxOutStatus)
E._AwaitTxOutStatusChangeResp
ownInstanceId :: forall w s e. (AsContractError e) => Contract w s e ContractInstanceId
ownInstanceId :: Contract w s e ContractInstanceId
ownInstanceId = PABReq
-> Prism' PABResp ContractInstanceId
-> Contract w s e ContractInstanceId
forall w (s :: Row *) e a.
AsContractError e =>
PABReq -> Prism' PABResp a -> Contract w s e a
pabReq PABReq
OwnContractInstanceIdReq Prism' PABResp ContractInstanceId
E._OwnContractInstanceIdResp
type HasEndpoint l a s =
( HasType l (EndpointValue a) (Input s)
, HasType l ActiveEndpoint (Output s)
, KnownSymbol l
, ContractRow s
)
type Endpoint l a = l .== (EndpointValue a, ActiveEndpoint)
endpointReq :: forall l a s.
( HasEndpoint l a s )
=> ActiveEndpoint
endpointReq :: ActiveEndpoint
endpointReq =
ActiveEndpoint :: EndpointDescription -> Maybe Value -> ActiveEndpoint
ActiveEndpoint
{ aeDescription :: EndpointDescription
aeDescription = String -> EndpointDescription
EndpointDescription (String -> EndpointDescription) -> String -> EndpointDescription
forall a b. (a -> b) -> a -> b
$ Proxy l -> String
forall (n :: Symbol) (proxy :: Symbol -> *).
KnownSymbol n =>
proxy n -> String
symbolVal (Proxy l
forall k (t :: k). Proxy t
Proxy @l)
, aeMetadata :: Maybe Value
aeMetadata = Maybe Value
forall a. Maybe a
Nothing
}
endpointDesc :: forall (l :: Symbol). KnownSymbol l => EndpointDescription
endpointDesc :: EndpointDescription
endpointDesc = String -> EndpointDescription
EndpointDescription (String -> EndpointDescription) -> String -> EndpointDescription
forall a b. (a -> b) -> a -> b
$ Proxy l -> String
forall (n :: Symbol) (proxy :: Symbol -> *).
KnownSymbol n =>
proxy n -> String
symbolVal (Proxy l
forall k (t :: k). Proxy t
Proxy @l)
endpointResp :: forall l a s. (HasEndpoint l a s, ToJSON a) => a -> PABResp
endpointResp :: a -> PABResp
endpointResp = EndpointDescription -> EndpointValue Value -> PABResp
ExposeEndpointResp (KnownSymbol l => EndpointDescription
forall (l :: Symbol). KnownSymbol l => EndpointDescription
endpointDesc @l) (EndpointValue Value -> PABResp)
-> (a -> EndpointValue Value) -> a -> PABResp
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Value -> EndpointValue Value
forall a. a -> EndpointValue a
EndpointValue (Value -> EndpointValue Value)
-> (a -> Value) -> a -> EndpointValue Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Value
forall a. ToJSON a => a -> Value
JSON.toJSON
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
endpoint :: (a -> Contract w s e b) -> Promise w s e b
endpoint a -> Contract w s e b
f = Contract w s e b -> Promise w s e b
forall w (s :: Row *) e a. Contract w s e a -> Promise w s e a
Promise (Contract w s e b -> Promise w s e b)
-> Contract w s e b -> Promise w s e b
forall a b. (a -> b) -> a -> b
$ do
(EndpointDescription
ed, EndpointValue Value
ev) <- PABReq
-> Prism' PABResp (EndpointDescription, EndpointValue Value)
-> Contract w s e (EndpointDescription, EndpointValue Value)
forall w (s :: Row *) e a.
AsContractError e =>
PABReq -> Prism' PABResp a -> Contract w s e a
pabReq (ActiveEndpoint -> PABReq
ExposeEndpointReq (ActiveEndpoint -> PABReq) -> ActiveEndpoint -> PABReq
forall a b. (a -> b) -> a -> b
$ HasEndpoint l a s => ActiveEndpoint
forall (l :: Symbol) a (s :: Row *).
HasEndpoint l a s =>
ActiveEndpoint
endpointReq @l @a @s) Prism' PABResp (EndpointDescription, EndpointValue Value)
E._ExposeEndpointResp
a
a <- EndpointDescription -> EndpointValue Value -> Contract w s e a
forall a w (s :: Row *) e.
(FromJSON a, AsContractError e) =>
EndpointDescription -> EndpointValue Value -> Contract w s e a
decode EndpointDescription
ed EndpointValue Value
ev
a -> Contract w s e b
f a
a
decode
:: forall a w s e.
( FromJSON a
, AsContractError e
)
=> EndpointDescription
-> EndpointValue JSON.Value
-> Contract w s e a
decode :: EndpointDescription -> EndpointValue Value -> Contract w s e a
decode EndpointDescription
ed ev :: EndpointValue Value
ev@EndpointValue{Value
unEndpointValue :: Value
unEndpointValue :: forall a. EndpointValue a -> a
unEndpointValue} =
(String -> Contract w s e a)
-> (a -> Contract w s e a) -> Either String a -> Contract w s e a
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either
(\String
e -> e -> Contract w s e a
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (e -> Contract w s e a) -> e -> Contract w s e a
forall a b. (a -> b) -> a -> b
$ AReview e (EndpointDescription, EndpointValue Value, Text)
-> (EndpointDescription, EndpointValue Value, Text) -> e
forall b (m :: * -> *) t. MonadReader b m => AReview t b -> m t
review AReview e (EndpointDescription, EndpointValue Value, Text)
forall r.
AsContractError r =>
Prism' r (EndpointDescription, EndpointValue Value, Text)
_EndpointDecodeContractError (EndpointDescription
ed, EndpointValue Value
ev, String -> Text
Text.pack String
e))
a -> Contract w s e a
forall (f :: * -> *) a. Applicative f => a -> f a
pure
(Either String a -> Contract w s e a)
-> Either String a -> Contract w s e a
forall a b. (a -> b) -> a -> b
$ (Value -> Parser a) -> Value -> Either String a
forall a b. (a -> Parser b) -> a -> Either String b
JSON.parseEither Value -> Parser a
forall a. FromJSON a => Value -> Parser a
JSON.parseJSON Value
unEndpointValue
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
handleEndpoint :: (Either e1 a -> Contract w s e2 b) -> Promise w s e2 b
handleEndpoint Either e1 a -> Contract w s e2 b
f = Contract w s e2 b -> Promise w s e2 b
forall w (s :: Row *) e a. Contract w s e a -> Promise w s e a
Promise (Contract w s e2 b -> Promise w s e2 b)
-> Contract w s e2 b -> Promise w s e2 b
forall a b. (a -> b) -> a -> b
$ do
Either e1 a
a <- Contract w s e1 a -> Contract w s e2 (Either e1 a)
forall w (s :: Row *) e e0 a.
Contract w s e a -> Contract w s e0 (Either e a)
runError (Contract w s e1 a -> Contract w s e2 (Either e1 a))
-> Contract w s e1 a -> Contract w s e2 (Either e1 a)
forall a b. (a -> b) -> a -> b
$ do
(EndpointDescription
ed, EndpointValue Value
ev) <- PABReq
-> Prism' PABResp (EndpointDescription, EndpointValue Value)
-> Contract w s e1 (EndpointDescription, EndpointValue Value)
forall w (s :: Row *) e a.
AsContractError e =>
PABReq -> Prism' PABResp a -> Contract w s e a
pabReq (ActiveEndpoint -> PABReq
ExposeEndpointReq (ActiveEndpoint -> PABReq) -> ActiveEndpoint -> PABReq
forall a b. (a -> b) -> a -> b
$ HasEndpoint l a s => ActiveEndpoint
forall (l :: Symbol) a (s :: Row *).
HasEndpoint l a s =>
ActiveEndpoint
endpointReq @l @a @s) Prism' PABResp (EndpointDescription, EndpointValue Value)
E._ExposeEndpointResp
EndpointDescription -> EndpointValue Value -> Contract w s e1 a
forall a w (s :: Row *) e.
(FromJSON a, AsContractError e) =>
EndpointDescription -> EndpointValue Value -> Contract w s e a
decode EndpointDescription
ed EndpointValue Value
ev
Either e1 a -> Contract w s e2 b
f Either e1 a
a
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
endpointWithMeta :: meta -> (a -> Contract w s e b) -> Promise w s e b
endpointWithMeta meta
meta a -> Contract w s e b
f = Contract w s e b -> Promise w s e b
forall w (s :: Row *) e a. Contract w s e a -> Promise w s e a
Promise (Contract w s e b -> Promise w s e b)
-> Contract w s e b -> Promise w s e b
forall a b. (a -> b) -> a -> b
$ do
(EndpointDescription
ed, EndpointValue Value
ev) <- PABReq
-> Prism' PABResp (EndpointDescription, EndpointValue Value)
-> Contract w s e (EndpointDescription, EndpointValue Value)
forall w (s :: Row *) e a.
AsContractError e =>
PABReq -> Prism' PABResp a -> Contract w s e a
pabReq (ActiveEndpoint -> PABReq
ExposeEndpointReq ActiveEndpoint
s) Prism' PABResp (EndpointDescription, EndpointValue Value)
E._ExposeEndpointResp
a
a <- EndpointDescription -> EndpointValue Value -> Contract w s e a
forall a w (s :: Row *) e.
(FromJSON a, AsContractError e) =>
EndpointDescription -> EndpointValue Value -> Contract w s e a
decode EndpointDescription
ed EndpointValue Value
ev
a -> Contract w s e b
f a
a
where
s :: ActiveEndpoint
s = ActiveEndpoint :: EndpointDescription -> Maybe Value -> ActiveEndpoint
ActiveEndpoint
{ aeDescription :: EndpointDescription
aeDescription = KnownSymbol l => EndpointDescription
forall (l :: Symbol). KnownSymbol l => EndpointDescription
endpointDesc @l
, aeMetadata :: Maybe Value
aeMetadata = Value -> Maybe Value
forall a. a -> Maybe a
Just (Value -> Maybe Value) -> Value -> Maybe Value
forall a b. (a -> b) -> a -> b
$ meta -> Value
forall a. ToJSON a => a -> Value
JSON.toJSON meta
meta
}
endpointDescription :: forall l. KnownSymbol l => Proxy l -> EndpointDescription
endpointDescription :: Proxy l -> EndpointDescription
endpointDescription = String -> EndpointDescription
EndpointDescription (String -> EndpointDescription)
-> (Proxy l -> String) -> Proxy l -> EndpointDescription
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Proxy l -> String
forall (n :: Symbol) (proxy :: Symbol -> *).
KnownSymbol n =>
proxy n -> String
symbolVal
{-# DEPRECATED ownPaymentPubKeyHash "Use ownFirstPaymentPubKeyHash, ownPaymentPubKeyHashes or ownAddresses instead" #-}
ownPaymentPubKeyHash :: forall w s e. (AsContractError e) => Contract w s e PaymentPubKeyHash
ownPaymentPubKeyHash :: Contract w s e PaymentPubKeyHash
ownPaymentPubKeyHash = Contract w s e PaymentPubKeyHash
forall w (s :: Row *) e.
AsContractError e =>
Contract w s e PaymentPubKeyHash
ownFirstPaymentPubKeyHash
ownAddresses :: forall w s e. (AsContractError e) => Contract w s e (NonEmpty CardanoAddress)
ownAddresses :: Contract w s e (NonEmpty CardanoAddress)
ownAddresses = PABReq
-> Prism' PABResp (NonEmpty CardanoAddress)
-> Contract w s e (NonEmpty CardanoAddress)
forall w (s :: Row *) e a.
AsContractError e =>
PABReq -> Prism' PABResp a -> Contract w s e a
pabReq PABReq
OwnAddressesReq Prism' PABResp (NonEmpty CardanoAddress)
E._OwnAddressesResp
ownAddress :: forall w s e. (AsContractError e) => Contract w s e CardanoAddress
ownAddress :: Contract w s e CardanoAddress
ownAddress = NonEmpty CardanoAddress -> CardanoAddress
forall a. NonEmpty a -> a
NonEmpty.head (NonEmpty CardanoAddress -> CardanoAddress)
-> Contract w s e (NonEmpty CardanoAddress)
-> Contract w s e CardanoAddress
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Contract w s e (NonEmpty CardanoAddress)
forall w (s :: Row *) e.
AsContractError e =>
Contract w s e (NonEmpty CardanoAddress)
ownAddresses
ownPaymentPubKeyHashes :: forall w s e. (AsContractError e) => Contract w s e [PaymentPubKeyHash]
ownPaymentPubKeyHashes :: Contract w s e [PaymentPubKeyHash]
ownPaymentPubKeyHashes = do
NonEmpty CardanoAddress
addrs <- Contract w s e (NonEmpty CardanoAddress)
forall w (s :: Row *) e.
AsContractError e =>
Contract w s e (NonEmpty CardanoAddress)
ownAddresses
[PaymentPubKeyHash] -> Contract w s e [PaymentPubKeyHash]
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([PaymentPubKeyHash] -> Contract w s e [PaymentPubKeyHash])
-> [PaymentPubKeyHash] -> Contract w s e [PaymentPubKeyHash]
forall a b. (a -> b) -> a -> b
$ (PubKeyHash -> PaymentPubKeyHash)
-> [PubKeyHash] -> [PaymentPubKeyHash]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap PubKeyHash -> PaymentPubKeyHash
PaymentPubKeyHash ([PubKeyHash] -> [PaymentPubKeyHash])
-> [PubKeyHash] -> [PaymentPubKeyHash]
forall a b. (a -> b) -> a -> b
$ (CardanoAddress -> Maybe PubKeyHash)
-> [CardanoAddress] -> [PubKeyHash]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe CardanoAddress -> Maybe PubKeyHash
forall era. AddressInEra era -> Maybe PubKeyHash
cardanoPubKeyHash ([CardanoAddress] -> [PubKeyHash])
-> [CardanoAddress] -> [PubKeyHash]
forall a b. (a -> b) -> a -> b
$ NonEmpty CardanoAddress -> [CardanoAddress]
forall a. NonEmpty a -> [a]
NonEmpty.toList (NonEmpty CardanoAddress -> [CardanoAddress])
-> NonEmpty CardanoAddress -> [CardanoAddress]
forall a b. (a -> b) -> a -> b
$ NonEmpty CardanoAddress
addrs
ownFirstPaymentPubKeyHash :: forall w s e. (AsContractError e) => Contract w s e PaymentPubKeyHash
ownFirstPaymentPubKeyHash :: Contract w s e PaymentPubKeyHash
ownFirstPaymentPubKeyHash = do
[PaymentPubKeyHash]
pkhs <- Contract w s e [PaymentPubKeyHash]
forall w (s :: Row *) e.
AsContractError e =>
Contract w s e [PaymentPubKeyHash]
ownPaymentPubKeyHashes
case [PaymentPubKeyHash]
pkhs of
[] -> e -> Contract w s e PaymentPubKeyHash
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (e -> Contract w s e PaymentPubKeyHash)
-> e -> Contract w s e PaymentPubKeyHash
forall a b. (a -> b) -> a -> b
$ AReview e WalletAPIError -> WalletAPIError -> e
forall b (m :: * -> *) t. MonadReader b m => AReview t b -> m t
review AReview e WalletAPIError
forall r. AsContractError r => Prism' r WalletAPIError
_WalletContractError WalletAPIError
NoPaymentPubKeyHashError
(PaymentPubKeyHash
pkh:[PaymentPubKeyHash]
_) -> PaymentPubKeyHash -> Contract w s e PaymentPubKeyHash
forall (f :: * -> *) a. Applicative f => a -> f a
pure PaymentPubKeyHash
pkh
submitUnbalancedTx :: forall w s e. (AsContractError e) => UnbalancedTx -> Contract w s e CardanoTx
submitUnbalancedTx :: UnbalancedTx -> Contract w s e CardanoTx
submitUnbalancedTx UnbalancedTx
utx = do
CardanoTx
tx <- UnbalancedTx -> Contract w s e CardanoTx
forall w (s :: Row *) e.
AsContractError e =>
UnbalancedTx -> Contract w s e CardanoTx
balanceTx UnbalancedTx
utx
CardanoTx -> Contract w s e CardanoTx
forall w (s :: Row *) e.
AsContractError e =>
CardanoTx -> Contract w s e CardanoTx
submitBalancedTx CardanoTx
tx
balanceTx :: forall w s e. (AsContractError e) => UnbalancedTx -> Contract w s e CardanoTx
balanceTx :: UnbalancedTx -> Contract w s e CardanoTx
balanceTx UnbalancedTx
t =
let req :: Contract w s e BalanceTxResponse
req = PABReq
-> Prism' PABResp BalanceTxResponse
-> Contract w s e BalanceTxResponse
forall w (s :: Row *) e a.
AsContractError e =>
PABReq -> Prism' PABResp a -> Contract w s e a
pabReq (UnbalancedTx -> PABReq
BalanceTxReq UnbalancedTx
t) Prism' PABResp BalanceTxResponse
E._BalanceTxResp in
Contract w s e BalanceTxResponse
req Contract w s e BalanceTxResponse
-> (BalanceTxResponse -> Contract w s e CardanoTx)
-> Contract w s e CardanoTx
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (WalletAPIError -> Contract w s e CardanoTx)
-> (CardanoTx -> Contract w s e CardanoTx)
-> Either WalletAPIError CardanoTx
-> Contract w s e CardanoTx
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (e -> Contract w s e CardanoTx
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (e -> Contract w s e CardanoTx)
-> (WalletAPIError -> e)
-> WalletAPIError
-> Contract w s e CardanoTx
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AReview e WalletAPIError -> WalletAPIError -> e
forall b (m :: * -> *) t. MonadReader b m => AReview t b -> m t
review AReview e WalletAPIError
forall r. AsContractError r => Prism' r WalletAPIError
_WalletContractError) CardanoTx -> Contract w s e CardanoTx
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either WalletAPIError CardanoTx -> Contract w s e CardanoTx)
-> (BalanceTxResponse -> Either WalletAPIError CardanoTx)
-> BalanceTxResponse
-> Contract w s e CardanoTx
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Getting
(Either WalletAPIError CardanoTx)
BalanceTxResponse
(Either WalletAPIError CardanoTx)
-> BalanceTxResponse -> Either WalletAPIError CardanoTx
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting
(Either WalletAPIError CardanoTx)
BalanceTxResponse
(Either WalletAPIError CardanoTx)
Iso' BalanceTxResponse (Either WalletAPIError CardanoTx)
E.balanceTxResponse
submitBalancedTx :: forall w s e. (AsContractError e) => CardanoTx -> Contract w s e CardanoTx
submitBalancedTx :: CardanoTx -> Contract w s e CardanoTx
submitBalancedTx CardanoTx
t =
let req :: Contract w s e WriteBalancedTxResponse
req = PABReq
-> Prism' PABResp WriteBalancedTxResponse
-> Contract w s e WriteBalancedTxResponse
forall w (s :: Row *) e a.
AsContractError e =>
PABReq -> Prism' PABResp a -> Contract w s e a
pabReq (CardanoTx -> PABReq
WriteBalancedTxReq CardanoTx
t) Prism' PABResp WriteBalancedTxResponse
E._WriteBalancedTxResp in
Contract w s e WriteBalancedTxResponse
req Contract w s e WriteBalancedTxResponse
-> (WriteBalancedTxResponse -> Contract w s e CardanoTx)
-> Contract w s e CardanoTx
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (WalletAPIError -> Contract w s e CardanoTx)
-> (CardanoTx -> Contract w s e CardanoTx)
-> Either WalletAPIError CardanoTx
-> Contract w s e CardanoTx
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (e -> Contract w s e CardanoTx
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (e -> Contract w s e CardanoTx)
-> (WalletAPIError -> e)
-> WalletAPIError
-> Contract w s e CardanoTx
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AReview e WalletAPIError -> WalletAPIError -> e
forall b (m :: * -> *) t. MonadReader b m => AReview t b -> m t
review AReview e WalletAPIError
forall r. AsContractError r => Prism' r WalletAPIError
_WalletContractError) CardanoTx -> Contract w s e CardanoTx
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either WalletAPIError CardanoTx -> Contract w s e CardanoTx)
-> (WriteBalancedTxResponse -> Either WalletAPIError CardanoTx)
-> WriteBalancedTxResponse
-> Contract w s e CardanoTx
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Getting
(Either WalletAPIError CardanoTx)
WriteBalancedTxResponse
(Either WalletAPIError CardanoTx)
-> WriteBalancedTxResponse -> Either WalletAPIError CardanoTx
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting
(Either WalletAPIError CardanoTx)
WriteBalancedTxResponse
(Either WalletAPIError CardanoTx)
Iso' WriteBalancedTxResponse (Either WalletAPIError CardanoTx)
E.writeBalancedTxResponse
submitTx :: forall w s e.
( AsContractError e
)
=> TxConstraints Void Void
-> Contract w s e CardanoTx
submitTx :: TxConstraints Void Void -> Contract w s e CardanoTx
submitTx = ScriptLookups Void
-> TxConstraints (RedeemerType Void) (DatumType Void)
-> Contract w s e CardanoTx
forall a w (s :: Row *) e.
(ToData (RedeemerType a), FromData (DatumType a),
ToData (DatumType a), AsContractError e) =>
ScriptLookups a
-> TxConstraints (RedeemerType a) (DatumType a)
-> Contract w s e CardanoTx
submitTxConstraintsWith @Void ScriptLookups Void
forall a. Monoid a => a
mempty
submitTxConstraints
:: forall a w s e.
( PlutusTx.ToData (RedeemerType a)
, PlutusTx.FromData (DatumType a)
, PlutusTx.ToData (DatumType a)
, AsContractError e
)
=> TypedValidator a
-> TxConstraints (RedeemerType a) (DatumType a)
-> Contract w s e CardanoTx
submitTxConstraints :: TypedValidator a
-> TxConstraints (RedeemerType a) (DatumType a)
-> Contract w s e CardanoTx
submitTxConstraints TypedValidator a
inst = ScriptLookups a
-> TxConstraints (RedeemerType a) (DatumType a)
-> Contract w s e CardanoTx
forall a w (s :: Row *) e.
(ToData (RedeemerType a), FromData (DatumType a),
ToData (DatumType a), AsContractError e) =>
ScriptLookups a
-> TxConstraints (RedeemerType a) (DatumType a)
-> Contract w s e CardanoTx
submitTxConstraintsWith (TypedValidator a -> ScriptLookups a
forall a. TypedValidator a -> ScriptLookups a
Constraints.typedValidatorLookups TypedValidator a
inst)
submitTxConstraintsSpending
:: forall a w s e.
( PlutusTx.ToData (RedeemerType a)
, PlutusTx.FromData (DatumType a)
, PlutusTx.ToData (DatumType a)
, AsContractError e
)
=> TypedValidator a
-> Map TxOutRef DecoratedTxOut
-> TxConstraints (RedeemerType a) (DatumType a)
-> Contract w s e CardanoTx
submitTxConstraintsSpending :: TypedValidator a
-> Map TxOutRef DecoratedTxOut
-> TxConstraints (RedeemerType a) (DatumType a)
-> Contract w s e CardanoTx
submitTxConstraintsSpending TypedValidator a
inst Map TxOutRef DecoratedTxOut
utxo =
let lookups :: ScriptLookups a
lookups = TypedValidator a -> ScriptLookups a
forall a. TypedValidator a -> ScriptLookups a
Constraints.typedValidatorLookups TypedValidator a
inst ScriptLookups a -> ScriptLookups a -> ScriptLookups a
forall a. Semigroup a => a -> a -> a
<> Map TxOutRef DecoratedTxOut -> ScriptLookups a
forall a. Map TxOutRef DecoratedTxOut -> ScriptLookups a
Constraints.unspentOutputs Map TxOutRef DecoratedTxOut
utxo
in ScriptLookups a
-> TxConstraints (RedeemerType a) (DatumType a)
-> Contract w s e CardanoTx
forall a w (s :: Row *) e.
(ToData (RedeemerType a), FromData (DatumType a),
ToData (DatumType a), AsContractError e) =>
ScriptLookups a
-> TxConstraints (RedeemerType a) (DatumType a)
-> Contract w s e CardanoTx
submitTxConstraintsWith ScriptLookups a
lookups
mkTxConstraints :: forall a w s e.
( PlutusTx.ToData (RedeemerType a)
, PlutusTx.FromData (DatumType a)
, PlutusTx.ToData (DatumType a)
, AsContractError e
)
=> ScriptLookups a
-> TxConstraints (RedeemerType a) (DatumType a)
-> Contract w s e UnbalancedTx
mkTxConstraints :: ScriptLookups a
-> TxConstraints (RedeemerType a) (DatumType a)
-> Contract w s e UnbalancedTx
mkTxConstraints ScriptLookups a
lookups TxConstraints (RedeemerType a) (DatumType a)
constraints = do
Params
params <- Contract w s e Params
forall w (s :: Row *) e. AsContractError e => Contract w s e Params
getParams
let result :: Either MkTxError UnbalancedTx
result = Params
-> ScriptLookups a
-> TxConstraints (RedeemerType a) (DatumType a)
-> Either MkTxError UnbalancedTx
forall a.
(FromData (DatumType a), ToData (DatumType a),
ToData (RedeemerType a)) =>
Params
-> ScriptLookups a
-> TxConstraints (RedeemerType a) (DatumType a)
-> Either MkTxError UnbalancedTx
Constraints.mkTx Params
params ScriptLookups a
lookups TxConstraints (RedeemerType a) (DatumType a)
constraints
logData :: MkTxLog
logData = MkTxLog :: ScriptLookups Any
-> TxConstraints BuiltinData BuiltinData
-> Either MkTxError UnbalancedTx
-> MkTxLog
MkTxLog
{ mkTxLogLookups :: ScriptLookups Any
mkTxLogLookups = ScriptLookups a -> ScriptLookups Any
forall a. ScriptLookups a -> ScriptLookups Any
Constraints.generalise ScriptLookups a
lookups
, mkTxLogTxConstraints :: TxConstraints BuiltinData BuiltinData
mkTxLogTxConstraints = (RedeemerType a -> BuiltinData)
-> (DatumType a -> BuiltinData)
-> TxConstraints (RedeemerType a) (DatumType a)
-> TxConstraints BuiltinData BuiltinData
forall (p :: * -> * -> *) a b c d.
Bifunctor p =>
(a -> b) -> (c -> d) -> p a c -> p b d
bimap RedeemerType a -> BuiltinData
forall a. ToData a => a -> BuiltinData
PlutusTx.toBuiltinData DatumType a -> BuiltinData
forall a. ToData a => a -> BuiltinData
PlutusTx.toBuiltinData TxConstraints (RedeemerType a) (DatumType a)
constraints
, mkTxLogResult :: Either MkTxError UnbalancedTx
mkTxLogResult = Either MkTxError UnbalancedTx
result
}
MkTxLog -> Contract w s e ()
forall a w (s :: Row *) e. ToJSON a => a -> Contract w s e ()
logDebug MkTxLog
logData
(MkTxError -> e)
-> Contract w s MkTxError UnbalancedTx
-> Contract w s e UnbalancedTx
forall w (s :: Row *) e e' a.
(e -> e') -> Contract w s e a -> Contract w s e' a
mapError (AReview e MkTxError -> MkTxError -> e
forall b (m :: * -> *) t. MonadReader b m => AReview t b -> m t
review AReview e MkTxError
forall r. AsContractError r => Prism' r MkTxError
_ConstraintResolutionContractError) (Contract w s MkTxError UnbalancedTx
-> Contract w s e UnbalancedTx)
-> Contract w s MkTxError UnbalancedTx
-> Contract w s e UnbalancedTx
forall a b. (a -> b) -> a -> b
$ (MkTxError -> Contract w s MkTxError UnbalancedTx)
-> (UnbalancedTx -> Contract w s MkTxError UnbalancedTx)
-> Either MkTxError UnbalancedTx
-> Contract w s MkTxError UnbalancedTx
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either MkTxError -> Contract w s MkTxError UnbalancedTx
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError UnbalancedTx -> Contract w s MkTxError UnbalancedTx
forall (f :: * -> *) a. Applicative f => a -> f a
pure Either MkTxError UnbalancedTx
result
data MkTxLog =
MkTxLog
{ MkTxLog -> ScriptLookups Any
mkTxLogLookups :: ScriptLookups Any
, MkTxLog -> TxConstraints BuiltinData BuiltinData
mkTxLogTxConstraints :: TxConstraints PlutusTx.BuiltinData PlutusTx.BuiltinData
, MkTxLog -> Either MkTxError UnbalancedTx
mkTxLogResult :: Either Constraints.MkTxError UnbalancedTx
}
deriving stock (Int -> MkTxLog -> ShowS
[MkTxLog] -> ShowS
MkTxLog -> String
(Int -> MkTxLog -> ShowS)
-> (MkTxLog -> String) -> ([MkTxLog] -> ShowS) -> Show MkTxLog
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MkTxLog] -> ShowS
$cshowList :: [MkTxLog] -> ShowS
show :: MkTxLog -> String
$cshow :: MkTxLog -> String
showsPrec :: Int -> MkTxLog -> ShowS
$cshowsPrec :: Int -> MkTxLog -> ShowS
Show, (forall x. MkTxLog -> Rep MkTxLog x)
-> (forall x. Rep MkTxLog x -> MkTxLog) -> Generic MkTxLog
forall x. Rep MkTxLog x -> MkTxLog
forall x. MkTxLog -> Rep MkTxLog x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep MkTxLog x -> MkTxLog
$cfrom :: forall x. MkTxLog -> Rep MkTxLog x
Generic)
deriving anyclass ([MkTxLog] -> Encoding
[MkTxLog] -> Value
MkTxLog -> Encoding
MkTxLog -> Value
(MkTxLog -> Value)
-> (MkTxLog -> Encoding)
-> ([MkTxLog] -> Value)
-> ([MkTxLog] -> Encoding)
-> ToJSON MkTxLog
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [MkTxLog] -> Encoding
$ctoEncodingList :: [MkTxLog] -> Encoding
toJSONList :: [MkTxLog] -> Value
$ctoJSONList :: [MkTxLog] -> Value
toEncoding :: MkTxLog -> Encoding
$ctoEncoding :: MkTxLog -> Encoding
toJSON :: MkTxLog -> Value
$ctoJSON :: MkTxLog -> Value
ToJSON, Value -> Parser [MkTxLog]
Value -> Parser MkTxLog
(Value -> Parser MkTxLog)
-> (Value -> Parser [MkTxLog]) -> FromJSON MkTxLog
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [MkTxLog]
$cparseJSONList :: Value -> Parser [MkTxLog]
parseJSON :: Value -> Parser MkTxLog
$cparseJSON :: Value -> Parser MkTxLog
FromJSON)
submitTxConstraintsWith
:: forall a w s e.
( PlutusTx.ToData (RedeemerType a)
, PlutusTx.FromData (DatumType a)
, PlutusTx.ToData (DatumType a)
, AsContractError e
)
=> ScriptLookups a
-> TxConstraints (RedeemerType a) (DatumType a)
-> Contract w s e CardanoTx
submitTxConstraintsWith :: ScriptLookups a
-> TxConstraints (RedeemerType a) (DatumType a)
-> Contract w s e CardanoTx
submitTxConstraintsWith ScriptLookups a
sl TxConstraints (RedeemerType a) (DatumType a)
constraints =
ScriptLookups a
-> TxConstraints (RedeemerType a) (DatumType a)
-> Contract w s e UnbalancedTx
forall a w (s :: Row *) e.
(ToData (RedeemerType a), FromData (DatumType a),
ToData (DatumType a), AsContractError e) =>
ScriptLookups a
-> TxConstraints (RedeemerType a) (DatumType a)
-> Contract w s e UnbalancedTx
mkTxConstraints ScriptLookups a
sl TxConstraints (RedeemerType a) (DatumType a)
constraints Contract w s e UnbalancedTx
-> (UnbalancedTx -> Contract w s e CardanoTx)
-> Contract w s e CardanoTx
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= UnbalancedTx -> Contract w s e CardanoTx
forall w (s :: Row *) e.
AsContractError e =>
UnbalancedTx -> Contract w s e CardanoTx
submitUnbalancedTx
submitTxConfirmed :: forall w s e. (AsContractError e) => UnbalancedTx -> Contract w s e ()
submitTxConfirmed :: UnbalancedTx -> Contract w s e ()
submitTxConfirmed UnbalancedTx
t = UnbalancedTx -> Contract w s e CardanoTx
forall w (s :: Row *) e.
AsContractError e =>
UnbalancedTx -> Contract w s e CardanoTx
submitUnbalancedTx UnbalancedTx
t Contract w s e CardanoTx
-> (CardanoTx -> Contract w s e ()) -> Contract w s e ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= TxId -> Contract w s e ()
forall w (s :: Row *) e.
AsContractError e =>
TxId -> Contract w s e ()
awaitTxConfirmed (TxId -> Contract w s e ())
-> (CardanoTx -> TxId) -> CardanoTx -> Contract w s e ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CardanoTx -> TxId
getCardanoTxId
yieldUnbalancedTx
:: forall w s e. (AsContractError e)
=> UnbalancedTx
-> Contract w s e ()
yieldUnbalancedTx :: UnbalancedTx -> Contract w s e ()
yieldUnbalancedTx UnbalancedTx
utx = PABReq -> Prism' PABResp () -> Contract w s e ()
forall w (s :: Row *) e a.
AsContractError e =>
PABReq -> Prism' PABResp a -> Contract w s e a
pabReq (UnbalancedTx -> PABReq
YieldUnbalancedTxReq UnbalancedTx
utx) Prism' PABResp ()
E._YieldUnbalancedTxResp