|
| 1 | +{-# LANGUAGE AllowAmbiguousTypes #-} |
| 2 | + |
| 3 | +{- | Module provides the way of building ".raw" transactions with execution budget |
| 4 | + estimated with `Cardano.Api` tools. |
| 5 | +-} |
| 6 | +module BotPlutusInterface.BodyBuilder (buildAndEstimateBudget) where |
| 7 | + |
| 8 | +import BotPlutusInterface.CardanoCLI qualified as CardanoCLI |
| 9 | +import BotPlutusInterface.Effects (PABEffect, estimateBudget) |
| 10 | + |
| 11 | +import BotPlutusInterface.Files ( |
| 12 | + DummyPrivKey, |
| 13 | + txFilePath, |
| 14 | + ) |
| 15 | +import BotPlutusInterface.Types (PABConfig, TxFile (Raw)) |
| 16 | +import Control.Monad.Freer (Eff, Member) |
| 17 | +import Control.Monad.Trans.Either (firstEitherT, newEitherT, runEitherT) |
| 18 | +import Data.Kind (Type) |
| 19 | +import Data.Map (Map) |
| 20 | +import Data.Text (Text) |
| 21 | +import Data.Text qualified as Text |
| 22 | +import Ledger (ExBudget, Tx, txId) |
| 23 | +import Ledger.Crypto (PubKeyHash) |
| 24 | +import Prelude |
| 25 | + |
| 26 | +{- | Build and save raw transaction (transaction body) with estimated execution budgets using `CardanoCLI`. |
| 27 | + It builds first transaction body with 0 budget for all spending inputs and minting policies, |
| 28 | + then uses body of this transaction to estimate execution budget |
| 29 | + and build final body with budget set. |
| 30 | +-} |
| 31 | +buildAndEstimateBudget :: |
| 32 | + forall (w :: Type) (effs :: [Type -> Type]). |
| 33 | + Member (PABEffect w) effs => |
| 34 | + PABConfig -> |
| 35 | + Map PubKeyHash DummyPrivKey -> |
| 36 | + Tx -> |
| 37 | + Eff effs (Either Text ExBudget) |
| 38 | +buildAndEstimateBudget pabConf privKeys tx = runEitherT $ do |
| 39 | + buildDraftTxBody |
| 40 | + >> estimateBudgetByDraftBody (Text.unpack $ txFilePath pabConf "raw" (txId tx)) |
| 41 | + >>= buildBodyUsingEstimatedBudget |
| 42 | + where |
| 43 | + buildDraftTxBody = newEitherT $ CardanoCLI.buildTx @w pabConf privKeys mempty tx |
| 44 | + |
| 45 | + estimateBudgetByDraftBody path = |
| 46 | + firstEitherT toText . newEitherT $ estimateBudget @w (Raw path) |
| 47 | + |
| 48 | + buildBodyUsingEstimatedBudget exBudget = |
| 49 | + newEitherT $ |
| 50 | + CardanoCLI.buildTx @w |
| 51 | + pabConf |
| 52 | + privKeys |
| 53 | + exBudget |
| 54 | + tx |
| 55 | + |
| 56 | + toText = Text.pack . show |
0 commit comments