@@ -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 (.. ),
@@ -63,9 +63,6 @@ import Plutus.V1.Ledger.Api (
6363 CurrencySymbol (.. ),
6464 TokenName (.. ),
6565 )
66-
67- import BotPlutusInterface.BodyBuilder qualified as BodyBuilder
68- import Data.Bifunctor (bimap )
6966import Prettyprinter (pretty , viaShow , (<+>) )
7067import Prelude
7168
@@ -103,15 +100,15 @@ balanceTxIO pabConf ownPkh unbalancedTx =
103100 preBalancedTx <- hoistEither $ addTxCollaterals utxoIndex tx >>= addSignatories ownPkh privKeys requiredSigs
104101
105102 -- Balance the tx
106- ( balancedTx, minUtxos) <- loop utxoIndex privKeys [] preBalancedTx
103+ balancedTx <- loop utxoIndex privKeys preBalancedTx
107104
108105 -- Get current Ada change
109106 let adaChange = getAdaChange utxoIndex balancedTx
110107 -- If we have change but no change UTxO, we need to add an output for it
111108 -- We'll add a minimal output, run the loop again so it gets minUTxO, then update change
112109 balancedTxWithChange <-
113110 if adaChange /= 0 && not (hasChangeUTxO changeAddr balancedTx)
114- then fst <$> loop utxoIndex privKeys minUtxos (addOutput changeAddr balancedTx)
111+ then loop utxoIndex privKeys (addOutput changeAddr balancedTx)
115112 else pure balancedTx
116113
117114 -- Get the updated change, add it to the tx
@@ -122,26 +119,18 @@ balanceTxIO pabConf ownPkh unbalancedTx =
122119 hoistEither $ addSignatories ownPkh privKeys requiredSigs fullyBalancedTx
123120 where
124121 changeAddr :: Address
125- changeAddr = Ledger. pubKeyHashAddress (Ledger. PaymentPubKeyHash ownPkh) ( pabConf. pcOwnStakePubKeyHash)
122+ changeAddr = Ledger. pubKeyHashAddress (Ledger. PaymentPubKeyHash ownPkh) pabConf. pcOwnStakePubKeyHash
126123 loop ::
127124 Map TxOutRef TxOut ->
128125 Map PubKeyHash DummyPrivKey ->
129- [(TxOut , Integer )] ->
130126 Tx ->
131- EitherT Text (Eff effs ) ( Tx , [( TxOut , Integer )])
132- loop utxoIndex privKeys prevMinUtxos tx = do
127+ EitherT Text (Eff effs ) Tx
128+ loop utxoIndex privKeys tx = do
133129 void $ lift $ Files. writeAll @ w pabConf tx
134- nextMinUtxos <-
135- newEitherT $
136- calculateMinUtxos @ w pabConf (Tx. txData tx) $ Tx. txOutputs tx \\ map fst prevMinUtxos
137-
138- let minUtxos = prevMinUtxos ++ nextMinUtxos
139-
140- lift $ printBpiLog @ w Debug $ " Min utxos:" <+> pretty minUtxos
141130
142131 -- Calculate fees by pre-balancing the tx, building it, and running the CLI on result
143132 txWithoutFees <-
144- hoistEither $ balanceTxStep minUtxos utxoIndex changeAddr $ tx `withFee` 0
133+ hoistEither $ balanceTxStep utxoIndex changeAddr $ tx `withFee` 0
145134
146135 exBudget <- newEitherT $ BodyBuilder. buildAndEstimateBudget @ w pabConf privKeys txWithoutFees
147136
@@ -152,11 +141,11 @@ balanceTxIO pabConf ownPkh unbalancedTx =
152141 lift $ printBpiLog @ w Debug $ " Fees:" <+> pretty fees
153142
154143 -- Rebalance the initial tx with the above fees
155- balancedTx <- hoistEither $ balanceTxStep minUtxos utxoIndex changeAddr $ tx `withFee` fees
144+ balancedTx <- hoistEither $ balanceTxStep utxoIndex changeAddr $ tx `withFee` fees
156145
157146 if balancedTx == tx
158- then pure ( balancedTx, minUtxos)
159- else loop utxoIndex privKeys minUtxos balancedTx
147+ then pure balancedTx
148+ else loop utxoIndex privKeys balancedTx
160149
161150getExecutionUnitPrices :: PABConfig -> ExecutionUnitPrices
162151getExecutionUnitPrices pabConf =
@@ -176,24 +165,13 @@ multRational (num :% denom) s = (s * num) :% denom
176165withFee :: Tx -> Integer -> Tx
177166withFee tx fee = tx {txFee = Ada. lovelaceValueOf fee}
178167
179- calculateMinUtxos ::
180- forall (w :: Type ) (effs :: [Type -> Type ]).
181- Member (PABEffect w ) effs =>
182- PABConfig ->
183- Map DatumHash Datum ->
184- [TxOut ] ->
185- Eff effs (Either Text [(TxOut , Integer )])
186- calculateMinUtxos pabConf datums txOuts =
187- zipWithM (fmap . (,)) txOuts <$> mapM (CardanoCLI. calculateMinUtxo @ w pabConf datums) txOuts
188-
189168balanceTxStep ::
190- [(TxOut , Integer )] ->
191169 Map TxOutRef TxOut ->
192170 Address ->
193171 Tx ->
194172 Either Text Tx
195- balanceTxStep minUtxos utxos changeAddr tx =
196- Right (addLovelaces minUtxos tx)
173+ balanceTxStep utxos changeAddr tx =
174+ Right tx
197175 >>= balanceTxIns utxos
198176 >>= handleNonAdaChange changeAddr utxos
199177
@@ -256,23 +234,6 @@ txOutToTxIn (txOutRef, txOut) =
256234 PubKeyCredential _ -> Right $ Tx. pubKeyTxIn txOutRef
257235 ScriptCredential _ -> Left " Cannot covert a script output to TxIn"
258236
259- -- | Add min lovelaces to each tx output
260- addLovelaces :: [(TxOut , Integer )] -> Tx -> Tx
261- addLovelaces minLovelaces tx =
262- let lovelacesAdded =
263- map
264- ( \ txOut ->
265- let outValue = txOutValue txOut
266- lovelaces = Ada. getLovelace $ Ada. fromValue outValue
267- minUtxo = fromMaybe 0 $ lookup txOut minLovelaces
268- in txOut
269- { txOutValue =
270- outValue <> Ada. lovelaceValueOf (max 0 (minUtxo - lovelaces))
271- }
272- )
273- $ txOutputs tx
274- in tx {txOutputs = lovelacesAdded}
275-
276237balanceTxIns :: Map TxOutRef TxOut -> Tx -> Either Text Tx
277238balanceTxIns utxos tx = do
278239 let txOuts = Tx. txOutputs tx
0 commit comments