Skip to content

Commit e6e0c4a

Browse files
committed
Merge branch 'gergely/vasil' of github.com:mlabs-haskell/bot-plutus-interface into gergely/vasil-with-latest-wallet
2 parents 2808c5e + 936f093 commit e6e0c4a

File tree

7 files changed

+78
-141
lines changed

7 files changed

+78
-141
lines changed

bot-plutus-interface.cabal

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -217,6 +217,7 @@ test-suite bot-plutus-interface-test
217217
, plutus-script-utils
218218
, plutus-tx
219219
, plutus-tx-plugin
220+
, pretty-diff
220221
, prettyprinter
221222
, QuickCheck
222223
, quickcheck-instances

flake.lock

Lines changed: 3 additions & 3 deletions
Some generated files are not rendered by default. Learn more about customizing how changed files appear on GitHub.

src/BotPlutusInterface/Balance.hs

Lines changed: 14 additions & 53 deletions
Original file line numberDiff line numberDiff line change
@@ -7,6 +7,7 @@ module BotPlutusInterface.Balance (
77
withFee,
88
) where
99

10+
import BotPlutusInterface.BodyBuilder qualified as BodyBuilder
1011
import BotPlutusInterface.CardanoCLI qualified as CardanoCLI
1112
import BotPlutusInterface.Effects (
1213
PABEffect,
@@ -19,14 +20,14 @@ import BotPlutusInterface.Files qualified as Files
1920
import BotPlutusInterface.Types (LogLevel (Debug), PABConfig)
2021
import Cardano.Api (ExecutionUnitPrices (ExecutionUnitPrices))
2122
import Cardano.Api.Shelley (ProtocolParameters (protocolParamPrices))
22-
import Control.Monad (foldM, void, zipWithM)
23+
import Control.Monad (foldM, void)
2324
import Control.Monad.Freer (Eff, Member)
2425
import Control.Monad.Trans.Class (lift)
2526
import Control.Monad.Trans.Either (EitherT, hoistEither, newEitherT, runEitherT)
27+
import Data.Bifunctor (bimap)
2628
import Data.Coerce (coerce)
2729
import Data.Either.Combinators (rightToMaybe)
2830
import Data.Kind (Type)
29-
import Data.List ((\\))
3031
import Data.Map (Map)
3132
import Data.Map qualified as Map
3233
import Data.Maybe (fromMaybe, mapMaybe)
@@ -46,7 +47,6 @@ import Ledger.Interval (
4647
LowerBound (LowerBound),
4748
UpperBound (UpperBound),
4849
)
49-
import Ledger.Scripts (Datum, DatumHash)
5050
import Ledger.Time (POSIXTimeRange)
5151
import Ledger.Tx (
5252
Tx (..),
@@ -64,9 +64,6 @@ import Plutus.V1.Ledger.Api (
6464
CurrencySymbol (..),
6565
TokenName (..),
6666
)
67-
68-
import BotPlutusInterface.BodyBuilder qualified as BodyBuilder
69-
import Data.Bifunctor (bimap)
7067
import Prettyprinter (pretty, viaShow, (<+>))
7168
import Prelude
7269

@@ -104,15 +101,15 @@ balanceTxIO pabConf ownPkh unbalancedTx =
104101
preBalancedTx <- hoistEither $ addTxCollaterals utxoIndex tx >>= addSignatories ownPkh privKeys requiredSigs
105102

106103
-- Balance the tx
107-
(balancedTx, minUtxos) <- loop utxoIndex privKeys [] preBalancedTx
104+
balancedTx <- loop utxoIndex privKeys preBalancedTx
108105

109106
-- Get current Ada change
110107
let adaChange = getAdaChange utxoIndex balancedTx
111108
-- If we have change but no change UTxO, we need to add an output for it
112109
-- We'll add a minimal output, run the loop again so it gets minUTxO, then update change
113110
balancedTxWithChange <-
114111
if adaChange /= 0 && not (hasChangeUTxO changeAddr balancedTx)
115-
then fst <$> loop utxoIndex privKeys minUtxos (addOutput changeAddr balancedTx)
112+
then loop utxoIndex privKeys (addOutput changeAddr balancedTx)
116113
else pure balancedTx
117114

118115
-- Get the updated change, add it to the tx
@@ -123,26 +120,18 @@ balanceTxIO pabConf ownPkh unbalancedTx =
123120
hoistEither $ addSignatories ownPkh privKeys requiredSigs fullyBalancedTx
124121
where
125122
changeAddr :: Address
126-
changeAddr = Ledger.pubKeyHashAddress (Ledger.PaymentPubKeyHash ownPkh) (pabConf.pcOwnStakePubKeyHash)
123+
changeAddr = Ledger.pubKeyHashAddress (Ledger.PaymentPubKeyHash ownPkh) pabConf.pcOwnStakePubKeyHash
127124
loop ::
128125
Map TxOutRef TxOut ->
129126
Map PubKeyHash DummyPrivKey ->
130-
[(TxOut, Integer)] ->
131127
Tx ->
132-
EitherT Text (Eff effs) (Tx, [(TxOut, Integer)])
133-
loop utxoIndex privKeys prevMinUtxos tx = do
128+
EitherT Text (Eff effs) Tx
129+
loop utxoIndex privKeys tx = do
134130
void $ lift $ Files.writeAll @w pabConf tx
135-
nextMinUtxos <-
136-
newEitherT $
137-
calculateMinUtxos @w pabConf (Tx.txData tx) $ Tx.txOutputs tx \\ map fst prevMinUtxos
138-
139-
let minUtxos = prevMinUtxos ++ nextMinUtxos
140-
141-
lift $ printBpiLog @w Debug $ "Min utxos:" <+> pretty minUtxos
142131

143132
-- Calculate fees by pre-balancing the tx, building it, and running the CLI on result
144133
txWithoutFees <-
145-
hoistEither $ balanceTxStep minUtxos utxoIndex changeAddr $ tx `withFee` 0
134+
hoistEither $ balanceTxStep utxoIndex changeAddr $ tx `withFee` 0
146135

147136
exBudget <- newEitherT $ BodyBuilder.buildAndEstimateBudget @w pabConf privKeys txWithoutFees
148137

@@ -153,11 +142,11 @@ balanceTxIO pabConf ownPkh unbalancedTx =
153142
lift $ printBpiLog @w Debug $ "Fees:" <+> pretty fees
154143

155144
-- Rebalance the initial tx with the above fees
156-
balancedTx <- hoistEither $ balanceTxStep minUtxos utxoIndex changeAddr $ tx `withFee` fees
145+
balancedTx <- hoistEither $ balanceTxStep utxoIndex changeAddr $ tx `withFee` fees
157146

158147
if balancedTx == tx
159-
then pure (balancedTx, minUtxos)
160-
else loop utxoIndex privKeys minUtxos balancedTx
148+
then pure balancedTx
149+
else loop utxoIndex privKeys balancedTx
161150

162151
getExecutionUnitPrices :: PABConfig -> ExecutionUnitPrices
163152
getExecutionUnitPrices pabConf =
@@ -177,24 +166,13 @@ multRational (num :% denom) s = (s * num) :% denom
177166
withFee :: Tx -> Integer -> Tx
178167
withFee tx fee = tx {txFee = Ada.lovelaceValueOf fee}
179168

180-
calculateMinUtxos ::
181-
forall (w :: Type) (effs :: [Type -> Type]).
182-
Member (PABEffect w) effs =>
183-
PABConfig ->
184-
Map DatumHash Datum ->
185-
[TxOut] ->
186-
Eff effs (Either Text [(TxOut, Integer)])
187-
calculateMinUtxos pabConf datums txOuts =
188-
zipWithM (fmap . (,)) txOuts <$> mapM (CardanoCLI.calculateMinUtxo @w pabConf datums) txOuts
189-
190169
balanceTxStep ::
191-
[(TxOut, Integer)] ->
192170
Map TxOutRef TxOut ->
193171
Address ->
194172
Tx ->
195173
Either Text Tx
196-
balanceTxStep minUtxos utxos changeAddr tx =
197-
Right (addLovelaces minUtxos tx)
174+
balanceTxStep utxos changeAddr tx =
175+
Right tx
198176
>>= balanceTxIns utxos
199177
>>= handleNonAdaChange changeAddr utxos
200178

@@ -257,23 +235,6 @@ txOutToTxIn (txOutRef, txOut) =
257235
PubKeyCredential _ -> Right $ Tx.pubKeyTxIn txOutRef
258236
ScriptCredential _ -> Left "Cannot covert a script output to TxIn"
259237

260-
-- | Add min lovelaces to each tx output
261-
addLovelaces :: [(TxOut, Integer)] -> Tx -> Tx
262-
addLovelaces minLovelaces tx =
263-
let lovelacesAdded =
264-
map
265-
( \txOut ->
266-
let outValue = txOutValue txOut
267-
lovelaces = Ada.getLovelace $ Ada.fromValue outValue
268-
minUtxo = fromMaybe 0 $ lookup txOut minLovelaces
269-
in txOut
270-
{ txOutValue =
271-
outValue <> Ada.lovelaceValueOf (max 0 (minUtxo - lovelaces))
272-
}
273-
)
274-
$ txOutputs tx
275-
in tx {txOutputs = lovelacesAdded}
276-
277238
balanceTxIns :: Map TxOutRef TxOut -> Tx -> Either Text Tx
278239
balanceTxIns utxos tx = do
279240
let txOuts = Tx.txOutputs tx

src/BotPlutusInterface/CardanoCLI.hs

Lines changed: 0 additions & 22 deletions
Original file line numberDiff line numberDiff line change
@@ -3,7 +3,6 @@
33

44
module BotPlutusInterface.CardanoCLI (
55
submitTx,
6-
calculateMinUtxo,
76
calculateMinFee,
87
buildTx,
98
signTx,
@@ -124,27 +123,6 @@ utxosAt pabConf address =
124123
. Text.pack
125124
}
126125

127-
calculateMinUtxo ::
128-
forall (w :: Type) (effs :: [Type -> Type]).
129-
Member (PABEffect w) effs =>
130-
PABConfig ->
131-
Map DatumHash Datum ->
132-
TxOut ->
133-
Eff effs (Either Text Integer)
134-
calculateMinUtxo pabConf datums txOut =
135-
join
136-
<$> callCommand @w
137-
ShellArgs
138-
{ cmdName = "cardano-cli"
139-
, cmdArgs =
140-
mconcat
141-
[ ["transaction", "calculate-min-required-utxo", "--babbage-era"]
142-
, txOutOpts pabConf datums [txOut]
143-
, ["--protocol-params-file", pabConf.pcProtocolParamsFile]
144-
]
145-
, cmdOutParser = mapLeft Text.pack . parseOnly UtxoParser.feeParser . Text.pack
146-
}
147-
148126
-- | Calculating fee for an unbalanced transaction
149127
calculateMinFee ::
150128
forall (w :: Type) (effs :: [Type -> Type]).

src/BotPlutusInterface/Contract.hs

Lines changed: 22 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -57,8 +57,10 @@ import Data.Vector qualified as V
5757
import Ledger (POSIXTime)
5858
import Ledger qualified
5959
import Ledger.Address (PaymentPubKeyHash (PaymentPubKeyHash))
60-
import Ledger.Constraints.OffChain (UnbalancedTx (..))
60+
import Ledger.Constraints.OffChain (UnbalancedTx (..), adjustUnbalancedTx)
61+
import Ledger.Params (Params (Params))
6162
import Ledger.Slot (Slot (Slot))
63+
import Ledger.TimeSlot (SlotConfig (..))
6264
import Ledger.Tx (CardanoTx (CardanoApiTx, EmulatorTx))
6365
import Ledger.Tx qualified as Tx
6466
import Plutus.ChainIndex.TxIdState (fromTx, transactionStatus)
@@ -195,20 +197,32 @@ handlePABReq contractEnv req = do
195197
either (error . show) (PosixTimeRangeToContainedSlotRangeResp . Right)
196198
<$> posixTimeRangeToContainedSlotRange @w posixTimeRange
197199
AwaitTxStatusChangeReq txId -> AwaitTxStatusChangeResp txId <$> awaitTxStatusChange @w contractEnv txId
200+
AdjustUnbalancedTxReq unbalancedTx -> AdjustUnbalancedTxResp <$> adjustUnbalancedTx' @w contractEnv unbalancedTx
198201
------------------------
199202
-- Unhandled requests --
200203
------------------------
201-
-- AwaitTimeReq t -> pure $ AwaitTimeResp t
202-
-- AwaitUtxoSpentReq txOutRef -> pure $ AwaitUtxoSpentResp ChainIndexTx
203-
-- AwaitUtxoProducedReq Address -> pure $ AwaitUtxoProducedResp (NonEmpty ChainIndexTx)
204-
-- AwaitTxOutStatusChangeReq TxOutRef
205-
-- ExposeEndpointReq ActiveEndpoint -> ExposeEndpointResp EndpointDescription (EndpointValue JSON.Value)
206-
-- YieldUnbalancedTxReq UnbalancedTx
207-
unsupported -> error ("Unsupported PAB effect: " ++ show unsupported)
204+
AwaitUtxoSpentReq _ -> error ("Unsupported PAB effect: " ++ show req)
205+
AwaitUtxoProducedReq _ -> error ("Unsupported PAB effect: " ++ show req)
206+
AwaitTxOutStatusChangeReq _ -> error ("Unsupported PAB effect: " ++ show req)
207+
ExposeEndpointReq _ -> error ("Unsupported PAB effect: " ++ show req)
208+
YieldUnbalancedTxReq _ -> error ("Unsupported PAB effect: " ++ show req)
208209

209210
printBpiLog @w Debug $ pretty resp
210211
pure resp
211212

213+
adjustUnbalancedTx' ::
214+
forall (w :: Type) (effs :: [Type -> Type]).
215+
ContractEnvironment w ->
216+
UnbalancedTx ->
217+
Eff effs (Either Tx.ToCardanoError UnbalancedTx)
218+
adjustUnbalancedTx' contractEnv unbalancedTx = do
219+
let slotConfig = SlotConfig 20000 1654524000
220+
networkId = contractEnv.cePABConfig.pcNetwork
221+
maybeParams = contractEnv.cePABConfig.pcProtocolParams >>= \pparams -> pure $ Params slotConfig pparams networkId
222+
case maybeParams of
223+
Just params -> pure $ snd <$> adjustUnbalancedTx params unbalancedTx
224+
_ -> pure . Left $ Tx.TxBodyError "no protocol params"
225+
212226
{- | Await till transaction status change to something from `Unknown`.
213227
Uses `chain-index` to query transaction by id.
214228
Important notes:

test/Spec/BotPlutusInterface/Balance.hs

Lines changed: 3 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -59,34 +59,31 @@ addUtxosForFees :: Assertion
5959
addUtxosForFees = do
6060
let txout = TxOut addr2 (Ada.lovelaceValueOf 1_000_000) Nothing
6161
tx = mempty {txOutputs = [txout]} `withFee` 500_000
62-
minUtxo = [(txout, 1_000_000)]
6362
utxoIndex = Map.fromList [utxo1, utxo2, utxo3]
6463
ownAddr = addr1
6564
balancedTx =
66-
Balance.balanceTxStep minUtxo utxoIndex ownAddr tx
65+
Balance.balanceTxStep utxoIndex ownAddr tx
6766

6867
txInputs <$> balancedTx @?= Right (Set.fromList [txIn1, txIn2])
6968

7069
addUtxosForNativeTokens :: Assertion
7170
addUtxosForNativeTokens = do
7271
let txout = TxOut addr2 (Value.singleton "11223344" "Token" 123) Nothing
7372
tx = mempty {txOutputs = [txout]} `withFee` 500_000
74-
minUtxo = [(txout, 1_000_000)]
7573
utxoIndex = Map.fromList [utxo1, utxo2, utxo3, utxo4]
7674
ownAddr = addr1
7775
balancedTx =
78-
Balance.balanceTxStep minUtxo utxoIndex ownAddr tx
76+
Balance.balanceTxStep utxoIndex ownAddr tx
7977

8078
txInputs <$> balancedTx @?= Right (Set.fromList [txIn1, txIn2, txIn3, txIn4])
8179

8280
addUtxosForChange :: Assertion
8381
addUtxosForChange = do
8482
let txout = TxOut addr2 (Ada.lovelaceValueOf 1_600_000) Nothing
8583
tx = mempty {txOutputs = [txout]} `withFee` 500_000
86-
minUtxo = [(txout, 1_000_000)]
8784
utxoIndex = Map.fromList [utxo1, utxo2, utxo3]
8885
ownAddr = addr1
8986
balancedTx =
90-
Balance.balanceTxStep minUtxo utxoIndex ownAddr tx
87+
Balance.balanceTxStep utxoIndex ownAddr tx
9188

9289
txInputs <$> balancedTx @?= Right (Set.fromList [txIn1, txIn2])

0 commit comments

Comments
 (0)