@@ -7,6 +7,7 @@ module BotPlutusInterface.Balance (
77 withFee ,
88) where
99
10+ import BotPlutusInterface.BodyBuilder qualified as BodyBuilder
1011import BotPlutusInterface.CardanoCLI qualified as CardanoCLI
1112import BotPlutusInterface.Effects (
1213 PABEffect ,
@@ -19,14 +20,14 @@ import BotPlutusInterface.Files qualified as Files
1920import BotPlutusInterface.Types (LogLevel (Debug ), PABConfig )
2021import Cardano.Api (ExecutionUnitPrices (ExecutionUnitPrices ))
2122import Cardano.Api.Shelley (ProtocolParameters (protocolParamPrices ))
22- import Control.Monad (foldM , void , zipWithM )
23+ import Control.Monad (foldM , void )
2324import Control.Monad.Freer (Eff , Member )
2425import Control.Monad.Trans.Class (lift )
2526import Control.Monad.Trans.Either (EitherT , hoistEither , newEitherT , runEitherT )
27+ import Data.Bifunctor (bimap )
2628import Data.Coerce (coerce )
2729import Data.Either.Combinators (rightToMaybe )
2830import Data.Kind (Type )
29- import Data.List ((\\) )
3031import Data.Map (Map )
3132import Data.Map qualified as Map
3233import Data.Maybe (fromMaybe , mapMaybe )
@@ -46,7 +47,6 @@ import Ledger.Interval (
4647 LowerBound (LowerBound ),
4748 UpperBound (UpperBound ),
4849 )
49- import Ledger.Scripts (Datum , DatumHash )
5050import Ledger.Time (POSIXTimeRange )
5151import 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 )
7067import Prettyprinter (pretty , viaShow , (<+>) )
7168import 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
162151getExecutionUnitPrices :: PABConfig -> ExecutionUnitPrices
163152getExecutionUnitPrices pabConf =
@@ -177,24 +166,13 @@ multRational (num :% denom) s = (s * num) :% denom
177166withFee :: Tx -> Integer -> Tx
178167withFee 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-
190169balanceTxStep ::
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-
277238balanceTxIns :: Map TxOutRef TxOut -> Tx -> Either Text Tx
278239balanceTxIns utxos tx = do
279240 let txOuts = Tx. txOutputs tx
0 commit comments