@@ -55,7 +55,7 @@ import Data.Text qualified as Text
55
55
import GHC.Real (Ratio ((:%) ))
56
56
import Ledger qualified
57
57
import Ledger.Ada qualified as Ada
58
- import Ledger.Address (Address (.. ))
58
+ import Ledger.Address (Address (.. ), PaymentPubKeyHash ( PaymentPubKeyHash ) )
59
59
import Ledger.Constraints.OffChain (UnbalancedTx (.. ))
60
60
import Ledger.Crypto (PubKeyHash )
61
61
import Ledger.Interval (
@@ -70,7 +70,7 @@ import Ledger.Tx (
70
70
TxIn (.. ),
71
71
TxInType (.. ),
72
72
TxOut (.. ),
73
- TxOutRef (.. ),
73
+ TxOutRef (.. ), ToCardanoError ( InvalidValidityRange )
74
74
)
75
75
import Ledger.Tx qualified as Tx
76
76
import Ledger.Tx.CardanoAPI (CardanoBuildTx )
@@ -84,6 +84,7 @@ import Plutus.V1.Ledger.Api (
84
84
import Ledger.Constraints.OffChain qualified as Constraints
85
85
import Prettyprinter (pretty , viaShow , (<+>) )
86
86
import Prelude
87
+ import qualified Wallet.API as WAPI
87
88
88
89
-- Config for balancing a `Tx`.
89
90
data BalanceConfig = BalanceConfig
@@ -106,7 +107,7 @@ balanceTxIO ::
106
107
PABConfig ->
107
108
PubKeyHash ->
108
109
UnbalancedTx ->
109
- Eff effs (Either Text Tx )
110
+ Eff effs (Either WAPI. WalletAPIError Tx )
110
111
balanceTxIO = balanceTxIO' @ w defaultBalanceConfig
111
112
112
113
-- | `balanceTxIO'` is more flexible version of `balanceTxIO`, this lets us specify custom `BalanceConfig`.
@@ -117,12 +118,12 @@ balanceTxIO' ::
117
118
PABConfig ->
118
119
PubKeyHash ->
119
120
UnbalancedTx ->
120
- Eff effs (Either Text Tx )
121
+ Eff effs (Either WAPI. WalletAPIError Tx )
121
122
balanceTxIO' balanceCfg pabConf ownPkh unbalancedTx' =
122
123
runEitherT $
123
124
do
124
125
updatedOuts <-
125
- firstEitherT ( Text. pack . show ) $
126
+ firstEitherT WAPI. OtherError $
126
127
newEitherT $
127
128
sequence <$> traverse (minUtxo @ w ) (unbalancedTx' ^. Constraints. tx . Tx. outputs)
128
129
@@ -136,7 +137,7 @@ balanceTxIO' balanceCfg pabConf ownPkh unbalancedTx' =
136
137
pabConf
137
138
changeAddr
138
139
139
- privKeys <- newEitherT $ Files. readPrivateKeys @ w pabConf
140
+ privKeys <- firstEitherT WAPI. OtherError $ newEitherT $ Files. readPrivateKeys @ w pabConf
140
141
141
142
let utxoIndex :: Map TxOutRef TxOut
142
143
utxoIndex = fmap Tx. toTxOut utxos <> unBalancedTxUtxoIndex unbalancedTx
@@ -163,14 +164,14 @@ balanceTxIO' balanceCfg pabConf ownPkh unbalancedTx' =
163
164
if bcHasScripts balanceCfg
164
165
then
165
166
maybe
166
- (throwE " Tx uses script but no collateral was provided." )
167
+ (throwE $ WAPI. OtherError " Tx uses script but no collateral was provided." )
167
168
(hoistEither . addSignatories ownPkh privKeys requiredSigs . flip addTxCollaterals tx)
168
169
mcollateral
169
170
else hoistEither $ addSignatories ownPkh privKeys requiredSigs tx
170
171
171
172
-- Balance the tx
172
173
balancedTx <- balanceTxLoop utxoIndex privKeys preBalancedTx
173
- changeTxOutWithMinAmt <- newEitherT $ addOutput @ w changeAddr balancedTx
174
+ changeTxOutWithMinAmt <- firstEitherT WAPI. OtherError $ newEitherT $ addOutput @ w changeAddr balancedTx
174
175
175
176
-- Get current Ada change
176
177
let adaChange = getAdaChange utxoIndex balancedTx
@@ -213,17 +214,17 @@ balanceTxIO' balanceCfg pabConf ownPkh unbalancedTx' =
213
214
Map TxOutRef TxOut ->
214
215
Map PubKeyHash DummyPrivKey ->
215
216
Tx ->
216
- EitherT Text (Eff effs ) Tx
217
+ EitherT WAPI. WalletAPIError (Eff effs ) Tx
217
218
balanceTxLoop utxoIndex privKeys tx = do
218
219
void $ lift $ Files. writeAll @ w pabConf tx
219
220
220
221
-- Calculate fees by pre-balancing the tx, building it, and running the CLI on result
221
222
txWithoutFees <-
222
223
newEitherT $ balanceTxStep @ w balanceCfg utxoIndex changeAddr $ tx `withFee` 0
223
224
224
- exBudget <- newEitherT $ BodyBuilder. buildAndEstimateBudget @ w pabConf privKeys txWithoutFees
225
+ exBudget <- firstEitherT WAPI. OtherError $ newEitherT $ BodyBuilder. buildAndEstimateBudget @ w pabConf privKeys txWithoutFees
225
226
226
- nonBudgettedFees <- newEitherT $ CardanoCLI. calculateMinFee @ w pabConf txWithoutFees
227
+ nonBudgettedFees <- firstEitherT WAPI. OtherError $ newEitherT $ CardanoCLI. calculateMinFee @ w pabConf txWithoutFees
227
228
228
229
let fees = nonBudgettedFees + getBudgetPrice (getExecutionUnitPrices pabConf) exBudget
229
230
@@ -244,7 +245,7 @@ utxosAndCollateralAtAddress ::
244
245
BalanceConfig ->
245
246
PABConfig ->
246
247
Address ->
247
- Eff effs (Either Text (Map TxOutRef Tx. ChainIndexTxOut , Maybe CollateralUtxo ))
248
+ Eff effs (Either WAPI. WalletAPIError (Map TxOutRef Tx. ChainIndexTxOut , Maybe CollateralUtxo ))
248
249
utxosAndCollateralAtAddress balanceCfg _pabConf changeAddr =
249
250
runEitherT $ do
250
251
inMemCollateral <- lift $ getInMemCollateral @ w
@@ -254,14 +255,14 @@ utxosAndCollateralAtAddress balanceCfg _pabConf changeAddr =
254
255
(UtxosAtExcluding changeAddr . Set. singleton . collateralTxOutRef)
255
256
inMemCollateral
256
257
257
- utxos <- firstEitherT (Text. pack . show ) $ newEitherT $ queryNode @ w nodeQuery
258
+ utxos <- firstEitherT (WAPI. OtherError . Text. pack . show ) $ newEitherT $ queryNode @ w nodeQuery
258
259
259
260
-- check if `bcHasScripts` is true, if this is the case then we search of
260
261
-- collateral UTxO in the environment, if such collateral is not present we throw Error.
261
262
if bcHasScripts balanceCfg
262
263
then
263
264
maybe
264
- ( throwE $
265
+ ( throwE $ WAPI. OtherError $
265
266
" The given transaction uses script, but there's no collateral provided."
266
267
<> " This usually means that, we failed to create Tx and update our ContractEnvironment."
267
268
)
@@ -302,7 +303,7 @@ balanceTxStep ::
302
303
Map TxOutRef TxOut ->
303
304
Address ->
304
305
Tx ->
305
- Eff effs (Either Text Tx )
306
+ Eff effs (Either WAPI. WalletAPIError Tx )
306
307
balanceTxStep balanceCfg utxos changeAddr tx =
307
308
runEitherT $
308
309
(newEitherT . balanceTxIns @ w utxos) tx
@@ -339,7 +340,7 @@ balanceTxIns ::
339
340
Member (PABEffect w ) effs =>
340
341
Map TxOutRef TxOut ->
341
342
Tx ->
342
- Eff effs (Either Text Tx )
343
+ Eff effs (Either WAPI. WalletAPIError Tx )
343
344
balanceTxIns utxos tx = do
344
345
runEitherT $ do
345
346
let txOuts = Tx. txOutputs tx
@@ -377,7 +378,7 @@ handleNonAdaChange ::
377
378
Address ->
378
379
Map TxOutRef TxOut ->
379
380
Tx ->
380
- Eff effs (Either Text Tx )
381
+ Eff effs (Either WAPI. WalletAPIError Tx )
381
382
handleNonAdaChange balanceCfg changeAddr utxos tx = runEitherT $ do
382
383
let nonAdaChange :: Value
383
384
nonAdaChange = getNonAdaChange utxos tx
@@ -403,7 +404,7 @@ handleNonAdaChange balanceCfg changeAddr utxos tx = runEitherT $ do
403
404
}
404
405
405
406
newOutputWithMinAmt <-
406
- firstEitherT ( Text. pack . show ) $
407
+ firstEitherT WAPI. OtherError $
407
408
newEitherT $ minUtxo @ w newOutput
408
409
409
410
let outputs :: [TxOut ]
@@ -415,7 +416,7 @@ handleNonAdaChange balanceCfg changeAddr utxos tx = runEitherT $ do
415
416
416
417
if isValueNat nonAdaChange
417
418
then return $ if Value. isZero nonAdaChange then tx else tx {txOutputs = outputs}
418
- else throwE " Not enough inputs to balance tokens."
419
+ else throwE $ WAPI. InsufficientFunds " Not enough inputs to balance tokens."
419
420
420
421
{- | `addAdaChange` checks if `bcSeparateChange` is true,
421
422
if it is then we add the ada change to seperate `TxOut` at changeAddr that contains only ada,
@@ -466,23 +467,21 @@ addOutput changeAddr tx =
466
467
, txOutDatumHash = Nothing
467
468
}
468
469
469
- changeTxOutWithMinAmt <-
470
- firstEitherT (Text. pack . show ) $
471
- newEitherT $
472
- minUtxo @ w changeTxOut
470
+ changeTxOutWithMinAmt <- newEitherT $
471
+ minUtxo @ w changeTxOut
473
472
474
473
return $ tx {txOutputs = txOutputs tx ++ [changeTxOutWithMinAmt]}
475
474
476
475
{- | Add the required signatories to the transaction. Be aware the the signature itself is invalid,
477
476
and will be ignored. Only the pub key hashes are used, mapped to signing key files on disk.
478
477
-}
479
- addSignatories :: PubKeyHash -> Map PubKeyHash DummyPrivKey -> [PubKeyHash ] -> Tx -> Either Text Tx
478
+ addSignatories :: PubKeyHash -> Map PubKeyHash DummyPrivKey -> [PubKeyHash ] -> Tx -> Either WAPI. WalletAPIError Tx
480
479
addSignatories ownPkh privKeys pkhs tx =
481
480
foldM
482
481
( \ tx' pkh ->
483
482
case Map. lookup pkh privKeys of
484
483
Just privKey -> Right $ Tx. addSignature' (unDummyPrivateKey privKey) tx'
485
- Nothing -> Left " Signing key not found. "
484
+ Nothing -> Left $ WAPI. PaymentPrivateKeyNotFound $ PaymentPubKeyHash pkh
486
485
)
487
486
tx
488
487
(ownPkh : pkhs)
@@ -492,14 +491,14 @@ addValidRange ::
492
491
Member (PABEffect w ) effs =>
493
492
POSIXTimeRange ->
494
493
Either CardanoBuildTx Tx ->
495
- Eff effs (Either Text Tx )
496
- addValidRange _ (Left _) = pure $ Left " BPI is not using CardanoBuildTx"
494
+ Eff effs (Either WAPI. WalletAPIError Tx )
495
+ addValidRange _ (Left _) = pure $ Left $ WAPI. OtherError " BPI is not using CardanoBuildTx"
497
496
addValidRange timeRange (Right tx) =
498
497
if validateRange timeRange
499
498
then
500
- bimap (Text. pack . show ) (setRange tx)
499
+ bimap (WAPI. OtherError . Text. pack . show ) (setRange tx)
501
500
<$> posixTimeRangeToContainedSlotRange @ w timeRange
502
- else pure $ Left " Invalid validity interval. "
501
+ else pure $ Left $ WAPI. ToCardanoError InvalidValidityRange
503
502
where
504
503
setRange tx' range = tx' {txValidRange = range}
505
504
0 commit comments