Skip to content

Commit

Permalink
Use HTTP version of evaluateTx
Browse files Browse the repository at this point in the history
  • Loading branch information
marcusbfs committed Feb 5, 2025
1 parent 12896f5 commit 219f497
Show file tree
Hide file tree
Showing 4 changed files with 30 additions and 93 deletions.
8 changes: 4 additions & 4 deletions src/Internal/Contract/Provider.purs
Original file line number Diff line number Diff line change
Expand Up @@ -16,7 +16,6 @@ import Ctl.Internal.Contract.LogParams (LogParams)
import Ctl.Internal.Contract.ProviderBackend (BlockfrostBackend, CtlBackend)
import Ctl.Internal.Helpers (logWithLevel)
import Ctl.Internal.QueryM (QueryM)
import Ctl.Internal.QueryM (evaluateTxOgmios) as QueryM
import Ctl.Internal.QueryM.CurrentEpoch (getCurrentEpoch) as OgmiosHttp
import Ctl.Internal.QueryM.EraSummaries (getEraSummaries) as OgmiosHttp
import Ctl.Internal.QueryM.Kupo
Expand All @@ -30,7 +29,8 @@ import Ctl.Internal.QueryM.Kupo
) as Kupo
import Ctl.Internal.QueryM.Ogmios (SubmitTxR(SubmitFail, SubmitTxSuccess))
import Ctl.Internal.QueryM.OgmiosHttp
( getChainTip
( evaluateTxOgmios
, getChainTip
, submitTxOgmios
) as OgmiosHttp
import Ctl.Internal.QueryM.Pools
Expand Down Expand Up @@ -78,10 +78,10 @@ providerForCtlBackend runQueryM params backend =
"Computed TransactionHash is not equal to the one returned by Ogmios, please report as bug!"
)
SubmitFail err -> Left $ ClientOtherError $ show err
, evaluateTx: \tx additionalUtxos -> unwrap <$>
, evaluateTx: \tx additionalUtxos ->
runQueryM' do
let txBytes = encodeCbor tx
QueryM.evaluateTxOgmios txBytes (wrap additionalUtxos)
OgmiosHttp.evaluateTxOgmios txBytes (wrap additionalUtxos)
, getEraSummaries: Right <$> runQueryM' OgmiosHttp.getEraSummaries
, getPoolIds: Right <$> runQueryM' OgmiosHttp.getPoolIds
, getPubKeyHashDelegationsAndRewards: \_ pubKeyHash ->
Expand Down
30 changes: 0 additions & 30 deletions src/Internal/QueryM.purs
Original file line number Diff line number Diff line change
Expand Up @@ -6,7 +6,6 @@ module Ctl.Internal.QueryM
( QueryM
, ParQueryM
, QueryMT(QueryMT)
, evaluateTxOgmios
, handleAffjaxResponse
) where

Expand All @@ -19,7 +18,6 @@ import Cardano.Provider.Error
( ClientError(ClientHttpError, ClientHttpResponseError, ClientDecodeJsonError)
, ServiceError(ServiceOtherError)
)
import Cardano.Types.CborBytes (CborBytes)
import Control.Alt (class Alt)
import Control.Alternative (class Alternative)
import Control.Monad.Error.Class (class MonadError, class MonadThrow)
Expand All @@ -30,20 +28,11 @@ import Control.Monad.Rec.Class (class MonadRec)
import Control.Parallel (class Parallel, parallel, sequential)
import Control.Plus (class Plus)
import Ctl.Internal.Helpers (logWithLevel)
import Ctl.Internal.Logging (mkLogger)
import Ctl.Internal.QueryM.Ogmios (AdditionalUtxoSet, OgmiosTxEvaluationR)
import Ctl.Internal.QueryM.Ogmios as Ogmios
import Ctl.Internal.QueryM.OgmiosWebsocket.Mempool
( listeners
, mkRequestAff
, underlyingWebSocket
)
import Ctl.Internal.QueryM.OgmiosWebsocket.Queries (QueryEnv)
import Data.Bifunctor (lmap)
import Data.Either (Either(Left, Right))
import Data.Maybe (fromMaybe)
import Data.Newtype (class Newtype, unwrap, wrap)
import Data.Tuple.Nested ((/\))
import Effect.Aff (Aff, ParAff)
import Effect.Aff.Class (class MonadAff, liftAff)
import Effect.Class (class MonadEffect)
Expand Down Expand Up @@ -101,25 +90,6 @@ instance Parallel (QueryMT ParAff) (QueryMT Aff) where
sequential :: QueryMT ParAff ~> QueryMT Aff
sequential = wrap <<< sequential <<< unwrap

--------------------------------------------------------------------------------
-- Ogmios Local Tx Submission Protocol
--------------------------------------------------------------------------------

evaluateTxOgmios
:: CborBytes -> AdditionalUtxoSet -> QueryM OgmiosTxEvaluationR
evaluateTxOgmios cbor additionalUtxos = do
ws <- asks $ underlyingWebSocket <<< _.ogmiosWs <<< _.runtime
listeners' <- asks $ listeners <<< _.ogmiosWs <<< _.runtime
cfg <- asks _.config
liftAff $ mkRequestAff listeners' ws (mkLogger cfg.logLevel cfg.customLogger)
Ogmios.evaluateTxCall
_.evaluate
(cbor /\ additionalUtxos)

--------------------------------------------------------------------------------
-- Ogmios Local Tx Monitor Protocol
--------------------------------------------------------------------------------

--------------------------------------------------------------------------------
-- Affjax
--------------------------------------------------------------------------------
Expand Down
35 changes: 0 additions & 35 deletions src/Internal/QueryM/Ogmios.purs
Original file line number Diff line number Diff line change
Expand Up @@ -25,8 +25,6 @@ module Ctl.Internal.QueryM.Ogmios
, MaybeMempoolTransaction(MaybeMempoolTransaction)
, OgmiosTxEvaluationR(OgmiosTxEvaluationR)
, aesonObject
, aesonArray
, evaluateTxCall
, submitSuccessPartialResp
, parseIpv6String
, rationalToSubcoin
Expand Down Expand Up @@ -84,7 +82,6 @@ import Cardano.Types
import Cardano.Types.AssetName (unAssetName)
import Cardano.Types.BigNum (BigNum)
import Cardano.Types.BigNum (fromBigInt, fromString) as BigNum
import Cardano.Types.CborBytes (CborBytes)
import Cardano.Types.Coin (Coin(Coin))
import Cardano.Types.CostModel (CostModel(CostModel))
import Cardano.Types.Ed25519KeyHash (Ed25519KeyHash)
Expand Down Expand Up @@ -131,12 +128,9 @@ import Control.Alternative (guard)
import Ctl.Internal.Helpers (encodeMap, showWithParens)
import Ctl.Internal.QueryM.JsonRpc2
( class DecodeOgmios
, JsonRpc2Call
, JsonRpc2Request
, OgmiosError
, decodeErrorOrResult
, decodeResult
, mkCallType
)
import Ctl.Internal.Types.ProtocolParameters
( ProtocolParameters(ProtocolParameters)
Expand Down Expand Up @@ -178,37 +172,8 @@ import JS.BigInt as BigInt
import Untagged.TypeCheck (class HasRuntimeType)
import Untagged.Union (type (|+|), toEither1)

--------------------------------------------------------------------------------
-- Local Tx Submission Protocol
-- https://ogmios.dev/mini-protocols/local-tx-submission/
--------------------------------------------------------------------------------

-- | Evaluates the execution units of scripts present in a given transaction,
-- | without actually submitting the transaction.
evaluateTxCall
:: JsonRpc2Call (CborBytes /\ AdditionalUtxoSet) OgmiosTxEvaluationR
evaluateTxCall = mkOgmiosCallType
{ method: "evaluateTransaction"
, params: \(cbor /\ utxoqr) ->
{ transaction: { cbor: byteArrayToHex $ unwrap cbor }
, additionalUtxo: utxoqr
}
}

--------------------------------------------------------------------------------
-- Helpers
--------------------------------------------------------------------------------

mkOgmiosCallType
:: forall (a :: Type) (i :: Type) (o :: Type)
. EncodeAeson (JsonRpc2Request a)
=> DecodeOgmios o
=> { method :: String, params :: i -> a }
-> JsonRpc2Call i o
mkOgmiosCallType =
mkCallType { jsonrpc: "2.0" }

--------------------------------------------------------------------------------
-- Local Tx Monitor Query Response & Parsing
--------------------------------------------------------------------------------

Expand Down
50 changes: 26 additions & 24 deletions src/Internal/QueryM/OgmiosHttp.purs
Original file line number Diff line number Diff line change
Expand Up @@ -9,7 +9,7 @@ module Ctl.Internal.QueryM.OgmiosHttp
, delegationsAndRewards
, eraSummaries
, getProtocolParameters
-- , evaluateTxOgmios
, evaluateTxOgmios
) where

import Prelude
Expand Down Expand Up @@ -104,11 +104,13 @@ import Ctl.Internal.QueryM.JsonRpc2
, pprintOgmiosDecodeError
)
import Ctl.Internal.QueryM.Ogmios
( CurrentEpoch
( AdditionalUtxoSet
, CurrentEpoch
, DelegationsAndRewardsR(DelegationsAndRewardsR)
, OgmiosEraSummaries
, OgmiosProtocolParameters
, OgmiosSystemStart
, OgmiosTxEvaluationR
, PoolParametersR
, SubmitTxR
) as Ogmios
Expand Down Expand Up @@ -272,28 +274,28 @@ delegationsAndRewards rewardAccounts = do
}
)

-- evaluateTxOgmios
-- :: CborBytes -> AdditionalUtxoSet -> QueryM Provider.TxEvaluationR
-- evaluateTxOgmios cbor additionalUtxos = ogmiosErrorHandlerWithArg
-- evaluateTx
-- (cbor /\ additionalUtxos)
-- where
-- evaluateTx
-- :: CborBytes /\ AdditionalUtxoSet
-- -> Aff (Either OgmiosDecodeError Provider.TxEvaluationR)
-- evaluateTx (cbor /\ utxoqr) = do
-- handleAffjaxOgmiosResponse <$>
-- ( ogmiosPostRequest
-- $ Aeson.encodeAeson
-- { jsonrpc: "2.0"
-- , id: "evaluateTxOgmios"
-- , method: "evaluateTransaction"
-- , params:
-- { transaction: { cbor: byteArrayToHex $ unwrap cbor }
-- , additionalUtxo: utxoqr
-- }
-- }
-- )
evaluateTxOgmios
:: CborBytes -> Ogmios.AdditionalUtxoSet -> QueryM Provider.TxEvaluationR
evaluateTxOgmios cbor additionalUtxos = unwrap <$> ogmiosErrorHandlerWithArg
evaluateTx
(cbor /\ additionalUtxos)
where
evaluateTx
:: CborBytes /\ Ogmios.AdditionalUtxoSet
-> QueryM (Either OgmiosDecodeError Ogmios.OgmiosTxEvaluationR)
evaluateTx (cbor_ /\ utxoqr) = do
handleAffjaxOgmiosResponse <$>
( ogmiosPostRequest
$ Aeson.encodeAeson
{ jsonrpc: "2.0"
, id: "evaluateTxOgmios"
, method: "evaluateTransaction"
, params:
{ transaction: { cbor: byteArrayToHex $ unwrap cbor_ }
, additionalUtxo: utxoqr
}
}
)

instance DecodeOgmios TxEvaluationR where
decodeOgmios = decodeErrorOrResult
Expand Down

0 comments on commit 219f497

Please sign in to comment.