| Copyright | (c) 2023 GYELD GMBH |
|---|---|
| License | Apache 2.0 |
| Maintainer | [email protected] |
| Stability | develop |
| Safe Haskell | None |
| Language | GHC2021 |
GeniusYield.TxBuilder
Description
Synopsis
- module GeniusYield.TxBuilder.Common
- module GeniusYield.TxBuilder.Errors
- module GeniusYield.TxBuilder.IO
- module GeniusYield.TxBuilder.User
- class Monad m => MonadRandom (m :: Type -> Type) where
- getRandomR :: Random a => (a, a) -> m a
- getRandom :: Random a => m a
- getRandomRs :: Random a => (a, a) -> m [a]
- getRandoms :: Random a => m [a]
- class Monad m => MonadError e (m :: Type -> Type) | m -> e where
- throwError :: e -> m a
- catchError :: m a -> (e -> m a) -> m a
- class GYTxQueryMonad m => GYTxSpecialQueryMonad (m :: Type -> Type) where
- systemStart :: m SystemStart
- eraHistory :: m EraHistory
- protocolParams :: m ApiProtocolParameters
- stakePools :: m (Set PoolId)
- class GYTxBuilderMonad m => GYTxMonad (m :: Type -> Type) where
- signTxBody :: GYTxBody -> m GYTx
- signTxBodyWithStake :: GYTxBody -> m GYTx
- submitTx :: GYTx -> m GYTxId
- awaitTxConfirmed' :: GYAwaitTxParameters -> GYTxId -> m ()
- slotToEpoch :: GYTxQueryMonad m => GYSlot -> m GYEpochNo
- class MonadError GYTxMonadException m => GYTxQueryMonad (m :: Type -> Type) where
- networkId :: m GYNetworkId
- lookupDatum :: GYDatumHash -> m (Maybe GYDatum)
- utxoAtTxOutRef :: GYTxOutRef -> m (Maybe GYUTxO)
- utxoAtTxOutRefWithDatum :: GYTxOutRef -> m (Maybe (GYUTxO, Maybe GYDatum))
- utxosAtTxOutRefs :: [GYTxOutRef] -> m GYUTxOs
- utxosAtTxOutRefsWithDatums :: [GYTxOutRef] -> m [(GYUTxO, Maybe GYDatum)]
- utxosAtAddress :: GYAddress -> Maybe GYAssetClass -> m GYUTxOs
- utxosWithAsset :: GYNonAdaToken -> m GYUTxOs
- utxosAtAddressWithDatums :: GYAddress -> Maybe GYAssetClass -> m [(GYUTxO, Maybe GYDatum)]
- utxosAtAddresses :: [GYAddress] -> m GYUTxOs
- utxosAtAddressesWithDatums :: [GYAddress] -> m [(GYUTxO, Maybe GYDatum)]
- utxoRefsAtAddress :: GYAddress -> m [GYTxOutRef]
- utxosAtPaymentCredential :: GYPaymentCredential -> Maybe GYAssetClass -> m GYUTxOs
- utxosAtPaymentCredentialWithDatums :: GYPaymentCredential -> Maybe GYAssetClass -> m [(GYUTxO, Maybe GYDatum)]
- utxosAtPaymentCredentials :: [GYPaymentCredential] -> m GYUTxOs
- utxosAtPaymentCredentialsWithDatums :: [GYPaymentCredential] -> m [(GYUTxO, Maybe GYDatum)]
- stakeAddressInfo :: GYStakeAddress -> m (Maybe GYStakeAddressInfo)
- drepState :: GYCredential 'GYKeyRoleDRep -> m (Maybe GYDRepState)
- drepsState :: Set (GYCredential 'GYKeyRoleDRep) -> m (Map (GYCredential 'GYKeyRoleDRep) (Maybe GYDRepState))
- slotConfig :: m GYSlotConfig
- slotOfCurrentBlock :: m GYSlot
- logMsg :: GYLogNamespace -> GYLogSeverity -> String -> m ()
- waitUntilSlot :: GYSlot -> m GYSlot
- waitForNextBlock :: m GYSlot
- constitution :: m GYConstitution
- proposals :: Set GYGovActionId -> m (Seq GYGovActionState)
- mempoolTxs :: m [GYTx]
- class (GYTxMonad (TxMonadOf m), GYTxSpecialQueryMonad m) => GYTxGameMonad (m :: Type -> Type) where
- class (Default (TxBuilderStrategy m), GYTxSpecialQueryMonad m, GYTxUserQueryMonad m) => GYTxBuilderMonad (m :: Type -> Type) where
- type TxBuilderStrategy (m :: Type -> Type)
- buildTxBodyWithStrategy :: forall (v :: PlutusVersion). TxBuilderStrategy m -> GYTxSkeleton v -> m GYTxBody
- buildTxBodyWithStrategyAndExtraConfiguration :: forall (v :: PlutusVersion). TxBuilderStrategy m -> GYTxExtraConfiguration v -> GYTxSkeleton v -> m GYTxBody
- buildTxBodyParallelWithStrategy :: forall (v :: PlutusVersion). TxBuilderStrategy m -> [GYTxSkeleton v] -> m GYTxBuildResult
- buildTxBodyChainingWithStrategy :: forall (v :: PlutusVersion). TxBuilderStrategy m -> [GYTxSkeleton v] -> m GYTxBuildResult
- class GYTxQueryMonad m => GYTxUserQueryMonad (m :: Type -> Type) where
- ownAddresses :: m [GYAddress]
- ownChangeAddress :: m GYAddress
- ownCollateral :: m (Maybe GYUTxO)
- availableUTxOs :: m GYUTxOs
- someUTxO :: PlutusVersion -> m GYTxOutRef
- buildTxBody :: forall (v :: PlutusVersion) m. GYTxBuilderMonad m => GYTxSkeleton v -> m GYTxBody
- buildTxBodyWithExtraConfiguration :: forall (v :: PlutusVersion) m. GYTxBuilderMonad m => GYTxExtraConfiguration v -> GYTxSkeleton v -> m GYTxBody
- buildTxBodyParallel :: forall (v :: PlutusVersion) m. GYTxBuilderMonad m => [GYTxSkeleton v] -> m GYTxBuildResult
- buildTxBodyChaining :: forall (v :: PlutusVersion) m. GYTxBuilderMonad m => [GYTxSkeleton v] -> m GYTxBuildResult
- waitNSlots :: GYTxQueryMonad m => Word64 -> m GYSlot
- waitNSlots_ :: GYTxQueryMonad m => Word64 -> m ()
- waitUntilSlot_ :: GYTxQueryMonad m => GYSlot -> m ()
- submitTx_ :: GYTxMonad m => GYTx -> m ()
- submitTxConfirmed :: GYTxMonad m => GYTx -> m GYTxId
- submitTxConfirmed_ :: GYTxMonad m => GYTx -> m ()
- submitTxConfirmed' :: GYTxMonad m => GYAwaitTxParameters -> GYTx -> m GYTxId
- submitTxConfirmed'_ :: GYTxMonad m => GYAwaitTxParameters -> GYTx -> m ()
- submitTxBody :: forall a m. (GYTxMonad m, ToShelleyWitnessSigningKey a) => GYTxBody -> [a] -> m GYTxId
- submitTxBody_ :: forall a m. (GYTxMonad m, ToShelleyWitnessSigningKey a) => GYTxBody -> [a] -> m ()
- submitTxBodyConfirmed :: forall a m. (GYTxMonad m, ToShelleyWitnessSigningKey a) => GYTxBody -> [a] -> m GYTxId
- submitTxBodyConfirmed_ :: (GYTxMonad m, ToShelleyWitnessSigningKey a) => GYTxBody -> [a] -> m ()
- signAndSubmitConfirmed :: GYTxMonad m => GYTxBody -> m GYTxId
- signAndSubmitConfirmed_ :: GYTxMonad m => GYTxBody -> m ()
- awaitTxConfirmed :: GYTxMonad m => GYTxId -> m ()
- lookupDatum' :: GYTxQueryMonad m => GYDatumHash -> m GYDatum
- utxoAtTxOutRef' :: GYTxQueryMonad m => GYTxOutRef -> m GYUTxO
- utxoAtTxOutRefWithDatum' :: GYTxQueryMonad m => GYTxOutRef -> m (GYUTxO, Maybe GYDatum)
- someUTxOWithoutRefScript :: GYTxUserQueryMonad m => m GYTxOutRef
- slotToBeginTime :: GYTxQueryMonad f => GYSlot -> f GYTime
- slotToEndTime :: GYTxQueryMonad f => GYSlot -> f GYTime
- enclosingSlotFromTime :: GYTxQueryMonad f => GYTime -> f (Maybe GYSlot)
- enclosingSlotFromTime' :: GYTxQueryMonad m => GYTime -> m GYSlot
- epochToBeginSlot :: GYTxQueryMonad m => GYEpochNo -> m GYSlot
- scriptAddress :: forall m (v :: PlutusVersion). GYTxQueryMonad m => GYScript v -> m GYAddress
- scriptAddress' :: GYTxQueryMonad m => GYScriptHash -> m GYAddress
- addressFromText' :: MonadError GYTxMonadException m => Text -> m GYAddress
- addressFromPlutusM :: GYTxQueryMonad m => Address -> m (Either PlutusToCardanoError GYAddress)
- addressFromPlutusHushedM :: GYTxQueryMonad m => Address -> m (Maybe GYAddress)
- addressFromPlutus' :: GYTxQueryMonad m => Address -> m GYAddress
- addressToPubKeyHash' :: MonadError GYTxMonadException m => GYAddress -> m GYPubKeyHash
- addressToPubKeyHashIO :: GYAddress -> IO GYPubKeyHash
- addressToValidatorHash' :: MonadError GYTxMonadException m => GYAddress -> m GYScriptHash
- addressToValidatorHashIO :: GYAddress -> IO GYScriptHash
- valueFromPlutus' :: MonadError GYTxMonadException m => Value -> m GYValue
- valueFromPlutusIO :: Value -> IO GYValue
- makeAssetClass' :: MonadError GYTxMonadException m => Text -> Text -> m GYAssetClass
- makeAssetClassIO :: Text -> Text -> IO GYAssetClass
- assetClassFromPlutus' :: MonadError GYTxMonadException m => AssetClass -> m GYAssetClass
- tokenNameFromPlutus' :: MonadError GYTxMonadException m => TokenName -> m GYTokenName
- txOutRefFromPlutus' :: MonadError GYTxMonadException m => TxOutRef -> m GYTxOutRef
- datumHashFromPlutus' :: MonadError GYTxMonadException m => DatumHash -> m GYDatumHash
- pubKeyHashFromPlutus' :: MonadError GYTxMonadException m => PubKeyHash -> m GYPubKeyHash
- advanceSlot' :: MonadError GYTxMonadException m => GYSlot -> Natural -> m GYSlot
- utxosDatums :: (GYTxQueryMonad m, FromData a) => GYUTxOs -> m (Map GYTxOutRef (GYAddress, GYValue, a))
- utxosDatumsPure :: FromData a => [(GYUTxO, Maybe GYDatum)] -> Map GYTxOutRef (GYAddress, GYValue, a)
- utxosDatumsPureWithOriginalDatum :: FromData a => [(GYUTxO, Maybe GYDatum)] -> Map GYTxOutRef (GYAddress, GYValue, a, GYDatum)
- utxoDatum :: (GYTxQueryMonad m, FromData a) => GYUTxO -> m (Either GYQueryDatumError (GYAddress, GYValue, a))
- utxoDatumPure :: FromData a => (GYUTxO, Maybe GYDatum) -> Either GYQueryDatumError (GYAddress, GYValue, a)
- utxoDatumPureWithOriginalDatum :: FromData a => (GYUTxO, Maybe GYDatum) -> Either GYQueryDatumError (GYAddress, GYValue, a, GYDatum)
- utxoDatumHushed :: (GYTxQueryMonad m, FromData a) => GYUTxO -> m (Maybe (GYAddress, GYValue, a))
- utxoDatumPureHushed :: FromData a => (GYUTxO, Maybe GYDatum) -> Maybe (GYTxOutRef, (GYAddress, GYValue, a))
- utxoDatumPureHushedWithOriginalDatum :: FromData a => (GYUTxO, Maybe GYDatum) -> Maybe (GYTxOutRef, (GYAddress, GYValue, a, GYDatum))
- utxoDatum' :: (GYTxQueryMonad m, FromData a) => GYUTxO -> m (GYAddress, GYValue, a)
- utxoDatumPure' :: (MonadError GYTxMonadException m, FromData a) => (GYUTxO, Maybe GYDatum) -> m (GYAddress, GYValue, a)
- utxoDatumPureWithOriginalDatum' :: (MonadError GYTxMonadException m, FromData a) => (GYUTxO, Maybe GYDatum) -> m (GYAddress, GYValue, a, GYDatum)
- mustHaveInput :: forall (v :: PlutusVersion). GYTxIn v -> GYTxSkeleton v
- mustHaveRefInput :: forall (v :: PlutusVersion). GYTxOutRef -> GYTxSkeleton v
- mustHaveOutput :: forall (v :: PlutusVersion). GYTxOut v -> GYTxSkeleton v
- mustHaveOptionalOutput :: forall (v :: PlutusVersion). Maybe (GYTxOut v) -> GYTxSkeleton v
- mustHaveTxMetadata :: forall (v :: PlutusVersion). Maybe GYTxMetadata -> GYTxSkeleton v
- mustHaveVotingProcedures :: forall (v :: PlutusVersion). VersionIsGreaterOrEqual v 'PlutusV3 => GYTxVotingProcedures v -> GYTxSkeleton v
- mustHaveProposalProcedure :: forall (v :: PlutusVersion). VersionIsGreaterOrEqual v 'PlutusV3 => GYProposalProcedurePB -> GYTxBuildWitness v -> GYTxSkeleton v
- mustHaveProposalProcedures :: forall (v :: PlutusVersion). VersionIsGreaterOrEqual v 'PlutusV3 => [(GYProposalProcedurePB, GYTxBuildWitness v)] -> GYTxSkeleton v
- mustMint :: forall (v :: PlutusVersion). GYBuildScript v -> GYRedeemer -> GYTokenName -> Integer -> GYTxSkeleton v
- mustHaveWithdrawal :: forall (v :: PlutusVersion). GYTxWdrl v -> GYTxSkeleton v
- mustHaveCertificate :: forall (v :: PlutusVersion). GYTxCert v -> GYTxSkeleton v
- mustBeSignedBy :: forall a (v :: PlutusVersion). CanSignTx a => a -> GYTxSkeleton v
- isInvalidBefore :: forall (v :: PlutusVersion). GYSlot -> GYTxSkeleton v
- isInvalidAfter :: forall (v :: PlutusVersion). GYSlot -> GYTxSkeleton v
- mustHaveDonation :: forall (v :: PlutusVersion). VersionIsGreaterOrEqual v 'PlutusV3 => Natural -> GYTxSkeleton v
- gyLogDebug' :: (GYTxQueryMonad m, HasCallStack) => GYLogNamespace -> String -> m ()
- gyLogInfo' :: (GYTxQueryMonad m, HasCallStack) => GYLogNamespace -> String -> m ()
- gyLogWarning' :: (GYTxQueryMonad m, HasCallStack) => GYLogNamespace -> String -> m ()
- gyLogError' :: (GYTxQueryMonad m, HasCallStack) => GYLogNamespace -> String -> m ()
- skeletonToRefScriptsORefs :: forall (v :: PlutusVersion). GYTxSkeleton v -> [GYTxOutRef]
- wrapReqWithTimeLog :: (GYTxQueryMonad m, MonadIO m) => String -> m a -> m a
- wt :: (GYTxQueryMonad m, MonadIO m) => String -> m a -> m a
- obtainTxBodyContentBuildTx :: GYTxSpecialQueryMonad m => GYTxBody -> m (TxBodyContent BuildTx ApiEra)
- obtainTxBodyContentBuildTx' :: GYTxSpecialQueryMonad m => GYTxBody -> m (TxBodyContent BuildTx ApiEra, GYUTxOs)
- type family TxBuilderStrategy (m :: Type -> Type)
- type family TxMonadOf (m :: Type -> Type) = (r :: Type -> Type) | r -> m
- queryBalance :: GYTxQueryMonad m => GYAddress -> m GYValue
- queryBalances :: GYTxQueryMonad m => [GYAddress] -> m GYValue
- getAdaOnlyUTxO :: GYTxQueryMonad m => GYAddress -> m [(GYTxOutRef, Natural)]
- adaOnlyUTxOPure :: GYUTxOs -> [(GYTxOutRef, Natural)]
- getCollateral' :: GYTxQueryMonad m => GYAddress -> Natural -> m (Maybe (GYTxOutRef, Natural))
- getCollateral :: GYTxQueryMonad m => GYAddress -> Natural -> m (GYTxOutRef, Natural)
- getTxBalance :: GYTxQueryMonad m => GYPubKeyHash -> GYTx -> m GYValue
Documentation
module GeniusYield.TxBuilder.Common
module GeniusYield.TxBuilder.Errors
module GeniusYield.TxBuilder.IO
module GeniusYield.TxBuilder.User
class Monad m => MonadRandom (m :: Type -> Type) where #
With a source of random number supply in hand, the MonadRandom class
allows the programmer to extract random values of a variety of types.
Methods
getRandomR :: Random a => (a, a) -> m a #
Takes a range (lo,hi) and a random number generator g, and returns a computation that returns a random value uniformly distributed in the closed interval [lo,hi], together with a new generator. It is unspecified what happens if lo>hi. For continuous types there is no requirement that the values lo and hi are ever produced, but they may be, depending on the implementation and the interval.
See randomR for details.
getRandom :: Random a => m a #
The same as getRandomR, but using a default range determined by the type:
- For bounded types (instances of
Bounded, such asChar), the range is normally the whole type. - For fractional types, the range is normally the semi-closed interval
[0,1). - For
Integer, the range is (arbitrarily) the range ofInt.
See random for details.
getRandomRs :: Random a => (a, a) -> m [a] #
Plural variant of getRandomR, producing an infinite list of
random values instead of returning a new generator.
See randomRs for details.
getRandoms :: Random a => m [a] #
Instances
class Monad m => MonadError e (m :: Type -> Type) | m -> e where #
The strategy of combining computations that can throw exceptions by bypassing bound functions from the point an exception is thrown to the point that it is handled.
Is parameterized over the type of error information and
the monad type constructor.
It is common to use as the monad type constructor
for an error monad in which error descriptions take the form of strings.
In that case and many other common cases the resulting monad is already defined
as an instance of the Either StringMonadError class.
You can also define your own error type and/or use a monad type constructor
other than or Either String.
In these cases you will have to explicitly define instances of the Either IOErrorMonadError
class.
(If you are using the deprecated Control.Monad.Error or
Control.Monad.Trans.Error, you may also have to define an Error instance.)
Methods
throwError :: e -> m a #
Is used within a monadic computation to begin exception processing.
catchError :: m a -> (e -> m a) -> m a #
A handler function to handle previous errors and return to normal execution. A common idiom is:
do { action1; action2; action3 } `catchError` handlerwhere the action functions can call throwError.
Note that handler and the do-block must have the same return type.
Instances
class GYTxQueryMonad m => GYTxSpecialQueryMonad (m :: Type -> Type) where #
Class of monads for querying special chain data.
Methods
systemStart :: m SystemStart #
eraHistory :: m EraHistory #
protocolParams :: m ApiProtocolParameters #
stakePools :: m (Set PoolId) #
Instances
class GYTxBuilderMonad m => GYTxMonad (m :: Type -> Type) where #
Class of monads for interacting with the blockchain using transactions.
Methods
signTxBody :: GYTxBody -> m GYTx #
Sign a transaction body with the user payment key to produce a transaction with witnesses.
Note: The key is not meant to be exposed to the monad, so it is only held
within the closure that signs a given transaction.
It is recommended to use signGYTxBody and similar to implement this method.
signTxBodyWithStake :: GYTxBody -> m GYTx #
Sign a transaction body with the user payment key AND user stake key to produce
a transaction with witnesses.
If the user wallet does not have a stake key, this function should be equivalent to
signTxBody.
See note on signTxBody
submitTx :: GYTx -> m GYTxId #
Submit a fully built transaction to the chain.
Use buildTxBody to build a transaction body, and signGYTxBody to
sign it before submitting.
Note: Changes made to the chain by the submitted transaction may not be reflected immediately,
see awaitTxConfirmed.
Law: someUTxO calls made after a call to submitTx may return previously returned UTxOs
if they were not affected by the submitted transaction.
awaitTxConfirmed' :: GYAwaitTxParameters -> GYTxId -> m () #
Wait for a _recently_ submitted transaction to be confirmed.
Note: If used on a transaction submitted long ago, the behavior is undefined.
Law: Queries made after a call to awaitTxConfirmed' should reflect changes made to the chain
by the identified transaction.
Instances
slotToEpoch :: GYTxQueryMonad m => GYSlot -> m GYEpochNo #
Get epoch number in which the given slot belongs to.
class MonadError GYTxMonadException m => GYTxQueryMonad (m :: Type -> Type) where #
Class of monads for querying chain data.
Minimal complete definition
networkId, lookupDatum, (utxoAtTxOutRef | utxosAtTxOutRefs), utxosAtAddress, utxosWithAsset, utxosAtPaymentCredential, stakeAddressInfo, slotConfig, slotOfCurrentBlock, logMsg, waitUntilSlot, waitForNextBlock, (drepState | drepsState), constitution, proposals, mempoolTxs
Methods
networkId :: m GYNetworkId #
Get the network id
lookupDatum :: GYDatumHash -> m (Maybe GYDatum) #
Lookup datum by its hash.
utxoAtTxOutRef :: GYTxOutRef -> m (Maybe GYUTxO) #
Lookup GYUTxO at GYTxOutRef.
utxoAtTxOutRefWithDatum :: GYTxOutRef -> m (Maybe (GYUTxO, Maybe GYDatum)) #
Lookup UTxO at GYTxOutRef with an attempt to resolve for datum.
utxosAtTxOutRefs :: [GYTxOutRef] -> m GYUTxOs #
Lookup GYUTxOs at multiple GYTxOutRefs at once
utxosAtTxOutRefsWithDatums :: [GYTxOutRef] -> m [(GYUTxO, Maybe GYDatum)] #
Lookup UTxOs at zero or more GYTxOutRef with their datums. This has a default implementation using utxosAtTxOutRefs and lookupDatum but should be overridden for efficiency if provider provides suitable option.
utxosAtAddress :: GYAddress -> Maybe GYAssetClass -> m GYUTxOs #
utxosWithAsset :: GYNonAdaToken -> m GYUTxOs #
Lookup GYUTxOs with a given GYAssetClass.
utxosAtAddressWithDatums :: GYAddress -> Maybe GYAssetClass -> m [(GYUTxO, Maybe GYDatum)] #
Lookup GYUTxO at given GYAddress with their datums. This has a default implementation using utxosAtAddress and lookupDatum but should be overridden for efficiency if provider provides suitable option.
utxosAtAddresses :: [GYAddress] -> m GYUTxOs #
utxosAtAddressesWithDatums :: [GYAddress] -> m [(GYUTxO, Maybe GYDatum)] #
Lookup UTxOs at zero or more GYAddress with their datums. This has a default implementation using utxosAtAddresses and lookupDatum but should be overridden for efficiency if provider provides suitable option.
utxoRefsAtAddress :: GYAddress -> m [GYTxOutRef] #
Lookup the `[GYTxOutRef]`s at a GYAddress
utxosAtPaymentCredential :: GYPaymentCredential -> Maybe GYAssetClass -> m GYUTxOs #
Lookup GYUTxOs at GYPaymentCredential.
utxosAtPaymentCredentialWithDatums :: GYPaymentCredential -> Maybe GYAssetClass -> m [(GYUTxO, Maybe GYDatum)] #
Lookup UTxOs at given GYPaymentCredential with their datums. This has a default implementation using utxosAtPaymentCredential and lookupDatum but should be overridden for efficiency if provider provides suitable option.
utxosAtPaymentCredentials :: [GYPaymentCredential] -> m GYUTxOs #
Lookup GYUTxOs at zero or more GYPaymentCredential.
utxosAtPaymentCredentialsWithDatums :: [GYPaymentCredential] -> m [(GYUTxO, Maybe GYDatum)] #
Lookup UTxOs at zero or more GYPaymentCredential with their datums. This has a default implementation using utxosAtPaymentCredentials and lookupDatum but should be overridden for efficiency if provider provides suitable option.
stakeAddressInfo :: GYStakeAddress -> m (Maybe GYStakeAddressInfo) #
Obtain delegation information for a stake address. Note that in case stake address is not registered, this function should return Nothing.
drepState :: GYCredential 'GYKeyRoleDRep -> m (Maybe GYDRepState) #
Obtain state of drep.
drepsState :: Set (GYCredential 'GYKeyRoleDRep) -> m (Map (GYCredential 'GYKeyRoleDRep) (Maybe GYDRepState)) #
Obtain state of dreps.
slotConfig :: m GYSlotConfig #
Obtain the slot config for the network.
Implementations using era history to create slot config may raise GYEraSummariesToSlotConfigError.
slotOfCurrentBlock :: m GYSlot #
This is expected to give the slot of the latest block. We say "expected" as we cache the result for 5 seconds, that is to say, suppose slot was cached at time T, now if query for current block's slot comes within time duration (T, T + 5), then we'll return the cached slot but if say, query happened at time (T + 5, T + 21) where 21 was taken as an arbitrary number above 5, then we'll query the chain tip and get the slot of the latest block seen by the provider and then store it in our cache, thus new cached value would be served for requests coming within time interval of (T + 21, T + 26).
NOTE: It's behaviour is slightly different, solely for our plutus simple model provider where it actually returns the value of the currentSlot variable maintained inside plutus simple model library.
logMsg :: GYLogNamespace -> GYLogSeverity -> String -> m () #
Log a message with specified namespace and severity.
waitUntilSlot :: GYSlot -> m GYSlot #
Wait until the chain tip is at least the given slot number, returning it's slot.
waitForNextBlock :: m GYSlot #
Wait until the chain tip is at the next block, return it's slot.
constitution :: m GYConstitution #
Query the current constitution definition.
Arguments
| :: Set GYGovActionId | Specify a set of Governance Action IDs to filter the proposals. When this set is empty, all the proposals considered for ratification will be returned. |
| -> m (Seq GYGovActionState) |
Query proposals that are considered for ratification.
mempoolTxs :: m [GYTx] #
Query the transactions in mempool.
Instances
class (GYTxMonad (TxMonadOf m), GYTxSpecialQueryMonad m) => GYTxGameMonad (m :: Type -> Type) where #
Class of monads that can simulate a "game" between different users interacting with transactions.
Associated Types
type TxMonadOf (m :: Type -> Type) = (r :: Type -> Type) | r -> m #
Type of the supported GYTxMonad instance that can participate within the "game".
Methods
createUser :: m User #
Create a new user within the chain. This does not fund the user. See "GeniusYield.Test.Utils.createUserWithLovelace" or "GeniusYield.Test.Utils.createUserWithAssets".
This _must not_ fund the user. Note: The generated user may be arbitrarily complex. i.e may have zero or more stake keys (and thus one or more addresses).
asUser :: User -> TxMonadOf m a -> m a #
Lift the supported GYTxMonad instance into the game, as a participating user wallet.
Instances
| GYTxGameMonad GYTxMonadClb # | |||||
Defined in GeniusYield.Test.Clb Associated Types
Methods createUser :: GYTxMonadClb User # asUser :: User -> TxMonadOf GYTxMonadClb a -> GYTxMonadClb a # | |||||
| GYTxGameMonad GYTxGameMonadIO # | |||||
Defined in GeniusYield.TxBuilder.IO Associated Types
Methods createUser :: GYTxGameMonadIO User # asUser :: User -> TxMonadOf GYTxGameMonadIO a -> GYTxGameMonadIO a # | |||||
| GYTxGameMonad m => GYTxGameMonad (FeeTrackerGame m) # | |||||
Defined in GeniusYield.Test.FeeTracker Associated Types
Methods createUser :: FeeTrackerGame m User # asUser :: User -> TxMonadOf (FeeTrackerGame m) a -> FeeTrackerGame m a # | |||||
class (Default (TxBuilderStrategy m), GYTxSpecialQueryMonad m, GYTxUserQueryMonad m) => GYTxBuilderMonad (m :: Type -> Type) where #
Class of monads for building transactions. This can be default derived if the requirements are met.
Specifically, set TxBuilderStrategy to GYCoinSelectionStrategy if you wish to use the default in-house
transaction building implementation.
Minimal complete definition
Nothing
Associated Types
type TxBuilderStrategy (m :: Type -> Type) #
type TxBuilderStrategy (m :: Type -> Type) = GYCoinSelectionStrategy
Methods
buildTxBodyWithStrategy :: forall (v :: PlutusVersion). TxBuilderStrategy m -> GYTxSkeleton v -> m GYTxBody #
The most basic version of GYTxSkeleton builder.
NOTE ==
This is not meant to be called multiple times with several GYTxSkeletons before submission.
Because the balancer will end up using the same utxos across the different txs.
Consider using buildTxBodyParallel or buildTxBodyChaining instead.
default buildTxBodyWithStrategy :: forall (v :: PlutusVersion). (MonadRandom m, TxBuilderStrategy m ~ GYCoinSelectionStrategy) => TxBuilderStrategy m -> GYTxSkeleton v -> m GYTxBody #
buildTxBodyWithStrategyAndExtraConfiguration :: forall (v :: PlutusVersion). TxBuilderStrategy m -> GYTxExtraConfiguration v -> GYTxSkeleton v -> m GYTxBody #
default buildTxBodyWithStrategyAndExtraConfiguration :: forall (v :: PlutusVersion). (MonadRandom m, TxBuilderStrategy m ~ GYCoinSelectionStrategy) => TxBuilderStrategy m -> GYTxExtraConfiguration v -> GYTxSkeleton v -> m GYTxBody #
buildTxBodyParallelWithStrategy :: forall (v :: PlutusVersion). TxBuilderStrategy m -> [GYTxSkeleton v] -> m GYTxBuildResult #
A multi GYTxSkeleton builder. The result containing built bodies must be in the same order as the skeletons.
This does not perform chaining, i.e does not use utxos created by one of the given transactions in the next one. However, it does ensure that the balancer does not end up using the same own utxos when building multiple transactions at once.
This supports failure recovery by utilizing GYTxBuildResult.
default buildTxBodyParallelWithStrategy :: forall (v :: PlutusVersion). (MonadRandom m, TxBuilderStrategy m ~ GYCoinSelectionStrategy) => TxBuilderStrategy m -> [GYTxSkeleton v] -> m GYTxBuildResult #
buildTxBodyChainingWithStrategy :: forall (v :: PlutusVersion). TxBuilderStrategy m -> [GYTxSkeleton v] -> m GYTxBuildResult #
A chaining GYTxSkeleton builder. The result containing built bodies must be in the same order as the skeletons.
This will perform chaining, i.e it will use utxos created by one of the given transactions, when building the next one.
This supports failure recovery by utilizing GYTxBuildResult.
default buildTxBodyChainingWithStrategy :: forall (v :: PlutusVersion). (MonadRandom m, TxBuilderStrategy m ~ GYCoinSelectionStrategy) => TxBuilderStrategy m -> [GYTxSkeleton v] -> m GYTxBuildResult #
Instances
class GYTxQueryMonad m => GYTxUserQueryMonad (m :: Type -> Type) where #
Class of monads for querying as a user.
Methods
ownAddresses :: m [GYAddress] #
Get your own address(es).
ownChangeAddress :: m GYAddress #
Get own change address.
ownCollateral :: m (Maybe GYUTxO) #
Get own collateral utxo.
availableUTxOs :: m GYUTxOs #
Get available own UTxOs that can be operated upon.
someUTxO :: PlutusVersion -> m GYTxOutRef #
Return some unspent transaction output translatable to the given language corresponding to the script in question.
Law: Must return the different values.
Instances
| GYTxUserQueryMonad GYTxMonadClb # | |
Defined in GeniusYield.Test.Clb | |
| GYTxUserQueryMonad GYTxMonadIO # | |
Defined in GeniusYield.TxBuilder.IO Methods ownAddresses :: GYTxMonadIO [GYAddress] # ownChangeAddress :: GYTxMonadIO GYAddress # ownCollateral :: GYTxMonadIO (Maybe GYUTxO) # | |
| GYTxUserQueryMonad GYTxBuilderMonadIO # | |
Defined in GeniusYield.TxBuilder.IO.Builder | |
| GYTxUserQueryMonad m => GYTxUserQueryMonad (FeeTracker m) # | |
Defined in GeniusYield.Test.FeeTracker Methods ownAddresses :: FeeTracker m [GYAddress] # ownChangeAddress :: FeeTracker m GYAddress # ownCollateral :: FeeTracker m (Maybe GYUTxO) # availableUTxOs :: FeeTracker m GYUTxOs # someUTxO :: PlutusVersion -> FeeTracker m GYTxOutRef # | |
| GYTxUserQueryMonad m => GYTxUserQueryMonad (RandT g m) # | |
Defined in GeniusYield.TxBuilder.Query.Class Methods ownAddresses :: RandT g m [GYAddress] # ownChangeAddress :: RandT g m GYAddress # ownCollateral :: RandT g m (Maybe GYUTxO) # availableUTxOs :: RandT g m GYUTxOs # someUTxO :: PlutusVersion -> RandT g m GYTxOutRef # | |
| GYTxUserQueryMonad m => GYTxUserQueryMonad (ReaderT env m) # | |
Defined in GeniusYield.TxBuilder.Query.Class Methods ownAddresses :: ReaderT env m [GYAddress] # ownChangeAddress :: ReaderT env m GYAddress # ownCollateral :: ReaderT env m (Maybe GYUTxO) # availableUTxOs :: ReaderT env m GYUTxOs # someUTxO :: PlutusVersion -> ReaderT env m GYTxOutRef # | |
| GYTxUserQueryMonad m => GYTxUserQueryMonad (StateT s m) # | |
Defined in GeniusYield.TxBuilder.Query.Class Methods ownAddresses :: StateT s m [GYAddress] # ownChangeAddress :: StateT s m GYAddress # ownCollateral :: StateT s m (Maybe GYUTxO) # availableUTxOs :: StateT s m GYUTxOs # someUTxO :: PlutusVersion -> StateT s m GYTxOutRef # | |
| GYTxUserQueryMonad m => GYTxUserQueryMonad (StateT s m) # | |
Defined in GeniusYield.TxBuilder.Query.Class Methods ownAddresses :: StateT s m [GYAddress] # ownChangeAddress :: StateT s m GYAddress # ownCollateral :: StateT s m (Maybe GYUTxO) # availableUTxOs :: StateT s m GYUTxOs # someUTxO :: PlutusVersion -> StateT s m GYTxOutRef # | |
| (GYTxUserQueryMonad m, Monoid w) => GYTxUserQueryMonad (WriterT w m) # | |
Defined in GeniusYield.TxBuilder.Query.Class Methods ownAddresses :: WriterT w m [GYAddress] # ownChangeAddress :: WriterT w m GYAddress # ownCollateral :: WriterT w m (Maybe GYUTxO) # availableUTxOs :: WriterT w m GYUTxOs # someUTxO :: PlutusVersion -> WriterT w m GYTxOutRef # | |
| (GYTxUserQueryMonad m, Monoid w) => GYTxUserQueryMonad (WriterT w m) # | |
Defined in GeniusYield.TxBuilder.Query.Class Methods ownAddresses :: WriterT w m [GYAddress] # ownChangeAddress :: WriterT w m GYAddress # ownCollateral :: WriterT w m (Maybe GYUTxO) # availableUTxOs :: WriterT w m GYUTxOs # someUTxO :: PlutusVersion -> WriterT w m GYTxOutRef # | |
| (GYTxUserQueryMonad m, Monoid w) => GYTxUserQueryMonad (WriterT w m) # | |
Defined in GeniusYield.TxBuilder.Query.Class Methods ownAddresses :: WriterT w m [GYAddress] # ownChangeAddress :: WriterT w m GYAddress # ownCollateral :: WriterT w m (Maybe GYUTxO) # availableUTxOs :: WriterT w m GYUTxOs # someUTxO :: PlutusVersion -> WriterT w m GYTxOutRef # | |
buildTxBody :: forall (v :: PlutusVersion) m. GYTxBuilderMonad m => GYTxSkeleton v -> m GYTxBody #
buildTxBodyWithStrategy with the default coin selection strategy.
buildTxBodyWithExtraConfiguration :: forall (v :: PlutusVersion) m. GYTxBuilderMonad m => GYTxExtraConfiguration v -> GYTxSkeleton v -> m GYTxBody #
buildTxBodyWithStrategyAndExtraConfiguration with the default coin selection strategy.
buildTxBodyParallel :: forall (v :: PlutusVersion) m. GYTxBuilderMonad m => [GYTxSkeleton v] -> m GYTxBuildResult #
buildTxBodyParallelWithStrategy with the default coin selection strategy.
buildTxBodyChaining :: forall (v :: PlutusVersion) m. GYTxBuilderMonad m => [GYTxSkeleton v] -> m GYTxBuildResult #
buildTxBodyChainingWithStrategy with the default coin selection strategy.
waitNSlots :: GYTxQueryMonad m => Word64 -> m GYSlot #
Wait until the chain tip has progressed by N slots.
waitNSlots_ :: GYTxQueryMonad m => Word64 -> m () #
waitNSlots_ = void . waitNSlots
waitUntilSlot_ :: GYTxQueryMonad m => GYSlot -> m () #
waitUntilSlot_ = void . waitUntilSlot
submitTxConfirmed :: GYTxMonad m => GYTx -> m GYTxId #
submitTxConfirmed' with default tx waiting parameters.
submitTxConfirmed_ :: GYTxMonad m => GYTx -> m () #
submitTxConfirmed_ = void . submitTxConfirmed
submitTxConfirmed' :: GYTxMonad m => GYAwaitTxParameters -> GYTx -> m GYTxId #
Equivalent to a call to submitTx and then a call to awaitTxConfirmed' with submitted tx id.
submitTxConfirmed'_ :: GYTxMonad m => GYAwaitTxParameters -> GYTx -> m () #
submitTxConfirmed'_ p = void . submitTxConfirmed' p
submitTxBody :: forall a m. (GYTxMonad m, ToShelleyWitnessSigningKey a) => GYTxBody -> [a] -> m GYTxId #
Signs a GYTxBody with the given keys and submits the transaction.
Equivalent to a call to signGYTxBody, followed by a call to submitTx
submitTxBody_ :: forall a m. (GYTxMonad m, ToShelleyWitnessSigningKey a) => GYTxBody -> [a] -> m () #
submitTxBody_ t = void . submitTxBody t
submitTxBodyConfirmed :: forall a m. (GYTxMonad m, ToShelleyWitnessSigningKey a) => GYTxBody -> [a] -> m GYTxId #
Signs a GYTxBody with the given keys, submits the transaction, and waits for its confirmation.
Equivalent to a call to signGYTxBody, followed by a call to submitTxConfirmed.
submitTxBodyConfirmed_ :: (GYTxMonad m, ToShelleyWitnessSigningKey a) => GYTxBody -> [a] -> m () #
submitTxBodyConfirmed_ t = void . submitTxBodyConfirmed t
signAndSubmitConfirmed :: GYTxMonad m => GYTxBody -> m GYTxId #
signAndSubmitConfirmed_ :: GYTxMonad m => GYTxBody -> m () #
awaitTxConfirmed :: GYTxMonad m => GYTxId -> m () #
Wait for a _recently_ submitted transaction to be confirmed, with default waiting parameters.
lookupDatum' :: GYTxQueryMonad m => GYDatumHash -> m GYDatum #
A version of lookupDatum that raises GYNoDatumForHash if the datum is not found.
utxoAtTxOutRef' :: GYTxQueryMonad m => GYTxOutRef -> m GYUTxO #
A version of utxoAtTxOutRef that raises GYNoUtxoAtRef if the utxo is not found.
utxoAtTxOutRefWithDatum' :: GYTxQueryMonad m => GYTxOutRef -> m (GYUTxO, Maybe GYDatum) #
A version of utxoAtTxOutRefWithDatum that raises GYNoUtxoAtRef if the utxo is not found.
someUTxOWithoutRefScript :: GYTxUserQueryMonad m => m GYTxOutRef #
Returns some UTxO present in wallet which doesn't have reference script.
slotToBeginTime :: GYTxQueryMonad f => GYSlot -> f GYTime #
slotToEndTime :: GYTxQueryMonad f => GYSlot -> f GYTime #
enclosingSlotFromTime :: GYTxQueryMonad f => GYTime -> f (Maybe GYSlot) #
enclosingSlotFromTime' :: GYTxQueryMonad m => GYTime -> m GYSlot #
Partial version of enclosingSlotFromTime.
Raises GYTimeUnderflowException if given time is before known system start.
epochToBeginSlot :: GYTxQueryMonad m => GYEpochNo -> m GYSlot #
Get the first slot in the given epoch.
scriptAddress :: forall m (v :: PlutusVersion). GYTxQueryMonad m => GYScript v -> m GYAddress #
Calculate script's address.
scriptAddress' :: GYTxQueryMonad m => GYScriptHash -> m GYAddress #
Calculate script's address.
addressFromText' :: MonadError GYTxMonadException m => Text -> m GYAddress #
Parse the bech32 representation of an address into GYAddress in GYTxMonad.
Throw GYConversionException if parsing fails.
addressFromPlutusM :: GYTxQueryMonad m => Address -> m (Either PlutusToCardanoError GYAddress) #
addressFromPlutusHushedM :: GYTxQueryMonad m => Address -> m (Maybe GYAddress) #
hushed version of addressFromPlutusM.
addressFromPlutus' :: GYTxQueryMonad m => Address -> m GYAddress #
Convert a Address to GYAddress in GYTxMonad.
Throw GYConversionException if conversion fails.
addressToPubKeyHash' :: MonadError GYTxMonadException m => GYAddress -> m GYPubKeyHash #
Convert GYAddress to GYPubKeyHash in GYTxMonad.
Throw GYConversionException if address is not key-hash one.
addressToValidatorHash' :: MonadError GYTxMonadException m => GYAddress -> m GYScriptHash #
Convert GYAddress to GYScriptHash in GYTxMonad.
Throw GYConversionException if address is not script-hash one.
valueFromPlutus' :: MonadError GYTxMonadException m => Value -> m GYValue #
Convert a Value to GYValue in GYTxMonad.
Throw GYConversionException if conversion fails.
valueFromPlutusIO :: Value -> IO GYValue #
Convert a Value to GYValue in IO.
Throw GYConversionException if conversion fails.
makeAssetClass' :: MonadError GYTxMonadException m => Text -> Text -> m GYAssetClass #
Create a GYAssetClass from the textual representation of currency symbol and token name in GYTxMonad.
Throw GYConversionException if conversion fails.
makeAssetClassIO :: Text -> Text -> IO GYAssetClass #
makeAssetClass' in the IO monad.
Throw GYConversionException if conversion fails.
assetClassFromPlutus' :: MonadError GYTxMonadException m => AssetClass -> m GYAssetClass #
Convert a AssetClass to GYAssetClass in GYTxMonad.
Throw GYConversionException if conversion fails.
tokenNameFromPlutus' :: MonadError GYTxMonadException m => TokenName -> m GYTokenName #
Convert a TokenName to GYTokenName in GYTxMonad.
Throw GYConversionException if conversion fails.
txOutRefFromPlutus' :: MonadError GYTxMonadException m => TxOutRef -> m GYTxOutRef #
Convert a TxOutRef to GYTxOutRef in GYTxMonad.
Throw GYConversionException if conversion fails.
datumHashFromPlutus' :: MonadError GYTxMonadException m => DatumHash -> m GYDatumHash #
Convert a DatumHash to GYDatumHash in GYTxMonad.
Throw GYConversionException if conversion fails.
pubKeyHashFromPlutus' :: MonadError GYTxMonadException m => PubKeyHash -> m GYPubKeyHash #
Convert a PubKeyHash to GYPubKeyHash in GYTxMonad.
Throw GYConversionException if conversion fails.
advanceSlot' :: MonadError GYTxMonadException m => GYSlot -> Natural -> m GYSlot #
Advance GYSlot forward in GYTxMonad. If slot value overflows, throw GYSlotOverflowException.
utxosDatums :: (GYTxQueryMonad m, FromData a) => GYUTxOs -> m (Map GYTxOutRef (GYAddress, GYValue, a)) #
utxosDatumsPure :: FromData a => [(GYUTxO, Maybe GYDatum)] -> Map GYTxOutRef (GYAddress, GYValue, a) #
Pure variant of utxosDatums.
utxosDatumsPureWithOriginalDatum :: FromData a => [(GYUTxO, Maybe GYDatum)] -> Map GYTxOutRef (GYAddress, GYValue, a, GYDatum) #
Like utxosDatumsPure but also returns original raw GYDatum.
utxoDatum :: (GYTxQueryMonad m, FromData a) => GYUTxO -> m (Either GYQueryDatumError (GYAddress, GYValue, a)) #
utxoDatumPure :: FromData a => (GYUTxO, Maybe GYDatum) -> Either GYQueryDatumError (GYAddress, GYValue, a) #
Pure variant of utxoDatum.
utxoDatumPureWithOriginalDatum :: FromData a => (GYUTxO, Maybe GYDatum) -> Either GYQueryDatumError (GYAddress, GYValue, a, GYDatum) #
Like utxoDatumPure but also returns original raw datum.
utxoDatumHushed :: (GYTxQueryMonad m, FromData a) => GYUTxO -> m (Maybe (GYAddress, GYValue, a)) #
utxoDatumPureHushed :: FromData a => (GYUTxO, Maybe GYDatum) -> Maybe (GYTxOutRef, (GYAddress, GYValue, a)) #
Obtain original datum representation of an UTxO.
utxoDatumPureHushedWithOriginalDatum :: FromData a => (GYUTxO, Maybe GYDatum) -> Maybe (GYTxOutRef, (GYAddress, GYValue, a, GYDatum)) #
Like utxoDatumPureHushed but also returns original raw GYDatum.
utxoDatum' :: (GYTxQueryMonad m, FromData a) => GYUTxO -> m (GYAddress, GYValue, a) #
Version of utxoDatum that throws GYTxMonadException.
utxoDatumPure' :: (MonadError GYTxMonadException m, FromData a) => (GYUTxO, Maybe GYDatum) -> m (GYAddress, GYValue, a) #
Version of utxoDatumPure that throws GYTxMonadException.
utxoDatumPureWithOriginalDatum' :: (MonadError GYTxMonadException m, FromData a) => (GYUTxO, Maybe GYDatum) -> m (GYAddress, GYValue, a, GYDatum) #
Like utxoDatumPure' but also returns original raw datum.
mustHaveInput :: forall (v :: PlutusVersion). GYTxIn v -> GYTxSkeleton v #
mustHaveRefInput :: forall (v :: PlutusVersion). GYTxOutRef -> GYTxSkeleton v #
mustHaveOutput :: forall (v :: PlutusVersion). GYTxOut v -> GYTxSkeleton v #
mustHaveOptionalOutput :: forall (v :: PlutusVersion). Maybe (GYTxOut v) -> GYTxSkeleton v #
mustHaveTxMetadata :: forall (v :: PlutusVersion). Maybe GYTxMetadata -> GYTxSkeleton v #
mustHaveVotingProcedures :: forall (v :: PlutusVersion). VersionIsGreaterOrEqual v 'PlutusV3 => GYTxVotingProcedures v -> GYTxSkeleton v #
mustHaveProposalProcedure :: forall (v :: PlutusVersion). VersionIsGreaterOrEqual v 'PlutusV3 => GYProposalProcedurePB -> GYTxBuildWitness v -> GYTxSkeleton v #
mustHaveProposalProcedures :: forall (v :: PlutusVersion). VersionIsGreaterOrEqual v 'PlutusV3 => [(GYProposalProcedurePB, GYTxBuildWitness v)] -> GYTxSkeleton v #
mustMint :: forall (v :: PlutusVersion). GYBuildScript v -> GYRedeemer -> GYTokenName -> Integer -> GYTxSkeleton v #
mustHaveWithdrawal :: forall (v :: PlutusVersion). GYTxWdrl v -> GYTxSkeleton v #
mustHaveCertificate :: forall (v :: PlutusVersion). GYTxCert v -> GYTxSkeleton v #
mustBeSignedBy :: forall a (v :: PlutusVersion). CanSignTx a => a -> GYTxSkeleton v #
isInvalidBefore :: forall (v :: PlutusVersion). GYSlot -> GYTxSkeleton v #
isInvalidAfter :: forall (v :: PlutusVersion). GYSlot -> GYTxSkeleton v #
mustHaveDonation :: forall (v :: PlutusVersion). VersionIsGreaterOrEqual v 'PlutusV3 => Natural -> GYTxSkeleton v #
gyLogDebug' :: (GYTxQueryMonad m, HasCallStack) => GYLogNamespace -> String -> m () #
gyLogInfo' :: (GYTxQueryMonad m, HasCallStack) => GYLogNamespace -> String -> m () #
gyLogWarning' :: (GYTxQueryMonad m, HasCallStack) => GYLogNamespace -> String -> m () #
gyLogError' :: (GYTxQueryMonad m, HasCallStack) => GYLogNamespace -> String -> m () #
skeletonToRefScriptsORefs :: forall (v :: PlutusVersion). GYTxSkeleton v -> [GYTxOutRef] #
Given a skeleton, returns a list of reference to reference script UTxOs which are present as witness.
wrapReqWithTimeLog :: (GYTxQueryMonad m, MonadIO m) => String -> m a -> m a #
Log the time a particular monad action took.
wt :: (GYTxQueryMonad m, MonadIO m) => String -> m a -> m a #
Synonym of wrapReqWithTimeLog.
obtainTxBodyContentBuildTx :: GYTxSpecialQueryMonad m => GYTxBody -> m (TxBodyContent BuildTx ApiEra) #
See obtainTxBodyContentBuildTx' for details.
obtainTxBodyContentBuildTx' :: GYTxSpecialQueryMonad m => GYTxBody -> m (TxBodyContent BuildTx ApiEra, GYUTxOs) #
Obtain 'TxBodyContent BuildTx ApiEra' from GYTxBody. Also returns the set of UTxOs used as input in this transaction (reference and spending inputs).
CAUTION: This does not account for voting procedures and proposal procedures present inside the original transaction.
type family TxBuilderStrategy (m :: Type -> Type) #
Instances
| type TxBuilderStrategy GYTxMonadClb # | |
Defined in GeniusYield.Test.Clb | |
| type TxBuilderStrategy GYTxMonadIO # | |
Defined in GeniusYield.TxBuilder.IO | |
| type TxBuilderStrategy GYTxBuilderMonadIO # | |
| type TxBuilderStrategy (FeeTracker m) # | |
Defined in GeniusYield.Test.FeeTracker | |
| type TxBuilderStrategy (RandT g m) # | |
Defined in GeniusYield.TxBuilder.Class | |
| type TxBuilderStrategy (ReaderT env m) # | |
Defined in GeniusYield.TxBuilder.Class | |
| type TxBuilderStrategy (StateT s m) # | |
Defined in GeniusYield.TxBuilder.Class | |
| type TxBuilderStrategy (StateT s m) # | |
Defined in GeniusYield.TxBuilder.Class | |
| type TxBuilderStrategy (WriterT w m) # | |
Defined in GeniusYield.TxBuilder.Class | |
| type TxBuilderStrategy (WriterT w m) # | |
Defined in GeniusYield.TxBuilder.Class | |
| type TxBuilderStrategy (WriterT w m) # | |
Defined in GeniusYield.TxBuilder.Class | |
type family TxMonadOf (m :: Type -> Type) = (r :: Type -> Type) | r -> m #
Type of the supported GYTxMonad instance that can participate within the "game".
Instances
| type TxMonadOf GYTxMonadClb # | |
Defined in GeniusYield.Test.Clb | |
| type TxMonadOf GYTxGameMonadIO # | |
Defined in GeniusYield.TxBuilder.IO | |
| type TxMonadOf (FeeTrackerGame m) # | |
Defined in GeniusYield.Test.FeeTracker | |
queryBalance :: GYTxQueryMonad m => GYAddress -> m GYValue #
Query the balance at given address.
queryBalances :: GYTxQueryMonad m => [GYAddress] -> m GYValue #
Query the balances at given addresses.
getAdaOnlyUTxO :: GYTxQueryMonad m => GYAddress -> m [(GYTxOutRef, Natural)] #
Query the txoutrefs at given address with ADA-only values.
Useful for finding a txoutref to be used as collateral.
adaOnlyUTxOPure :: GYUTxOs -> [(GYTxOutRef, Natural)] #
Arguments
| :: GYTxQueryMonad m | |
| => GYAddress | The address where to look. |
| -> Natural | The minimal amount of lovelace required as collateral. |
| -> m (Maybe (GYTxOutRef, Natural)) | Returns the smallest ada-only UTxO and the contained amount of lovelace at the specified address with the specified minimal value. If no such UTxO exists, |
Get a UTxO suitable for use as collateral.
Arguments
| :: GYTxQueryMonad m | |
| => GYAddress | The address where to look. |
| -> Natural | The minimal amount of lovelace required as collateral. |
| -> m (GYTxOutRef, Natural) | Returns the smallest ada-only UTxO and the contained amount of lovelace at the specified address with the specified minimal value. If no such UTxO exists, an exception is thrown. |
Get an UTxO suitable for use as collateral.
getTxBalance :: GYTxQueryMonad m => GYPubKeyHash -> GYTx -> m GYValue #
Calculate how much balance is the given transaction is moving to given pubkeyhash address(es).