@@ -36,7 +36,7 @@ import Cardano.Api.Shelley (ProtocolParameters (protocolParamPrices))
36
36
import Control.Monad (foldM , void , zipWithM )
37
37
import Control.Monad.Freer (Eff , Member )
38
38
import Control.Monad.Trans.Class (lift )
39
- import Control.Monad.Trans.Either (EitherT , firstEitherT , hoistEither , newEitherT , runEitherT )
39
+ import Control.Monad.Trans.Either (EitherT , hoistEither , newEitherT , runEitherT )
40
40
import Control.Monad.Trans.Except (throwE )
41
41
import Data.Bifunctor (bimap )
42
42
import Data.Coerce (coerce )
@@ -52,10 +52,12 @@ import Data.Text qualified as Text
52
52
import GHC.Real (Ratio ((:%) ))
53
53
import Ledger qualified
54
54
import Ledger.Ada qualified as Ada
55
- import Ledger.Address (Address (.. ), PaymentPubKeyHash ( PaymentPubKeyHash ) )
55
+ import Ledger.Address (Address (.. ))
56
56
import Ledger.Constraints.OffChain (UnbalancedTx (.. ))
57
+ import Ledger.Crypto (PubKeyHash )
57
58
import Ledger.Interval (
58
59
Extended (Finite , NegInf , PosInf ),
60
+ Interval (Interval ),
59
61
LowerBound (LowerBound ),
60
62
UpperBound (UpperBound ),
61
63
)
@@ -69,15 +71,13 @@ import Ledger.Tx (
69
71
TxOutRef (.. ),
70
72
)
71
73
import Ledger.Tx qualified as Tx
72
- import Ledger.Tx.CardanoAPI (ToCardanoError (InvalidValidityRange ))
73
74
import Ledger.Value (Value )
74
75
import Ledger.Value qualified as Value
75
76
import Plutus.V1.Ledger.Api (
76
77
CurrencySymbol (.. ),
77
78
TokenName (.. ),
78
79
)
79
80
import Prettyprinter (pretty , viaShow , (<+>) )
80
- import Wallet.API as WAPI
81
81
import Prelude
82
82
83
83
-- Config for balancing a `Tx`.
@@ -101,7 +101,7 @@ balanceTxIO ::
101
101
PABConfig ->
102
102
PubKeyHash ->
103
103
UnbalancedTx ->
104
- Eff effs (Either WAPI. WalletAPIError Tx )
104
+ Eff effs (Either Text Tx )
105
105
balanceTxIO = balanceTxIO' @ w defaultBalanceConfig
106
106
107
107
-- | `balanceTxIO'` is more flexible version of `balanceTxIO`, this let us specify custom `BalanceConfig`.
@@ -112,12 +112,12 @@ balanceTxIO' ::
112
112
PABConfig ->
113
113
PubKeyHash ->
114
114
UnbalancedTx ->
115
- Eff effs (Either WAPI. WalletAPIError Tx )
115
+ Eff effs (Either Text Tx )
116
116
balanceTxIO' balanceCfg pabConf ownPkh unbalancedTx =
117
117
runEitherT $
118
118
do
119
119
(utxos, mcollateral) <- newEitherT $ utxosAndCollateralAtAddress @ w balanceCfg pabConf changeAddr
120
- privKeys <- firstEitherT WAPI. OtherError $ newEitherT $ Files. readPrivateKeys @ w pabConf
120
+ privKeys <- newEitherT $ Files. readPrivateKeys @ w pabConf
121
121
122
122
let utxoIndex :: Map TxOutRef TxOut
123
123
utxoIndex = fmap Tx. toTxOut utxos <> unBalancedTxUtxoIndex unbalancedTx
@@ -142,7 +142,7 @@ balanceTxIO' balanceCfg pabConf ownPkh unbalancedTx =
142
142
if bcHasScripts balanceCfg
143
143
then
144
144
maybe
145
- (throwE $ WAPI. OtherError " Tx uses script but no collateral was provided." )
145
+ (throwE " Tx uses script but no collateral was provided." )
146
146
(hoistEither . addSignatories ownPkh privKeys requiredSigs . flip addTxCollaterals tx)
147
147
mcollateral
148
148
else hoistEither $ addSignatories ownPkh privKeys requiredSigs tx
@@ -189,13 +189,12 @@ balanceTxIO' balanceCfg pabConf ownPkh unbalancedTx =
189
189
Map PubKeyHash DummyPrivKey ->
190
190
[(TxOut , Integer )] ->
191
191
Tx ->
192
- EitherT WAPI. WalletAPIError (Eff effs ) (Tx , [(TxOut , Integer )])
192
+ EitherT Text (Eff effs ) (Tx , [(TxOut , Integer )])
193
193
balanceTxLoop utxoIndex privKeys prevMinUtxos tx = do
194
194
void $ lift $ Files. writeAll @ w pabConf tx
195
195
nextMinUtxos <-
196
- firstEitherT WAPI. OtherError $
197
- newEitherT $
198
- calculateMinUtxos @ w pabConf (Tx. txData tx) $ Tx. txOutputs tx \\ map fst prevMinUtxos
196
+ newEitherT $
197
+ calculateMinUtxos @ w pabConf (Tx. txData tx) $ Tx. txOutputs tx \\ map fst prevMinUtxos
199
198
200
199
let minUtxos = prevMinUtxos ++ nextMinUtxos
201
200
@@ -205,9 +204,9 @@ balanceTxIO' balanceCfg pabConf ownPkh unbalancedTx =
205
204
txWithoutFees <-
206
205
newEitherT $ balanceTxStep @ w balanceCfg minUtxos utxoIndex changeAddr $ tx `withFee` 0
207
206
208
- exBudget <- firstEitherT WAPI. OtherError $ newEitherT $ BodyBuilder. buildAndEstimateBudget @ w pabConf privKeys txWithoutFees
207
+ exBudget <- newEitherT $ BodyBuilder. buildAndEstimateBudget @ w pabConf privKeys txWithoutFees
209
208
210
- nonBudgettedFees <- firstEitherT WAPI. OtherError $ newEitherT $ CardanoCLI. calculateMinFee @ w pabConf txWithoutFees
209
+ nonBudgettedFees <- newEitherT $ CardanoCLI. calculateMinFee @ w pabConf txWithoutFees
211
210
212
211
let fees = nonBudgettedFees + getBudgetPrice (getExecutionUnitPrices pabConf) exBudget
213
212
@@ -228,10 +227,10 @@ utxosAndCollateralAtAddress ::
228
227
BalanceConfig ->
229
228
PABConfig ->
230
229
Address ->
231
- Eff effs (Either WAPI. WalletAPIError (Map TxOutRef Tx. ChainIndexTxOut , Maybe CollateralUtxo ))
230
+ Eff effs (Either Text (Map TxOutRef Tx. ChainIndexTxOut , Maybe CollateralUtxo ))
232
231
utxosAndCollateralAtAddress balanceCfg pabConf changeAddr =
233
232
runEitherT $ do
234
- utxos <- firstEitherT WAPI. OtherError $ newEitherT $ CardanoCLI. utxosAt @ w pabConf changeAddr
233
+ utxos <- newEitherT $ CardanoCLI. utxosAt @ w pabConf changeAddr
235
234
inMemCollateral <- lift $ getInMemCollateral @ w
236
235
237
236
-- check if `bcHasScripts` is true, if this is the case then we search of
@@ -240,9 +239,8 @@ utxosAndCollateralAtAddress balanceCfg pabConf changeAddr =
240
239
then
241
240
maybe
242
241
( throwE $
243
- WAPI. OtherError $
244
- " The given transaction uses script, but there's no collateral provided."
245
- <> " This usually means that, we failed to create Tx and update our ContractEnvironment."
242
+ " The given transaction uses script, but there's no collateral provided."
243
+ <> " This usually means that, we failed to create Tx and update our ContractEnvironment."
246
244
)
247
245
(const $ pure (removeCollateralFromMap inMemCollateral utxos, inMemCollateral))
248
246
inMemCollateral
@@ -290,7 +288,7 @@ balanceTxStep ::
290
288
Map TxOutRef TxOut ->
291
289
Address ->
292
290
Tx ->
293
- Eff effs (Either WAPI. WalletAPIError Tx )
291
+ Eff effs (Either Text Tx )
294
292
balanceTxStep balanceCfg minUtxos utxos changeAddr tx =
295
293
runEitherT $
296
294
(newEitherT . balanceTxIns @ w utxos) (addLovelaces minUtxos tx)
@@ -338,7 +336,7 @@ balanceTxIns ::
338
336
Member (PABEffect w ) effs =>
339
337
Map TxOutRef TxOut ->
340
338
Tx ->
341
- Eff effs (Either WAPI. WalletAPIError Tx )
339
+ Eff effs (Either Text Tx )
342
340
balanceTxIns utxos tx = do
343
341
runEitherT $ do
344
342
let txOuts = Tx. txOutputs tx
@@ -348,7 +346,7 @@ balanceTxIns utxos tx = do
348
346
[ txFee tx
349
347
, nonMintedValue
350
348
]
351
- txIns <- firstEitherT WAPI. OtherError $ newEitherT $ selectTxIns @ w (txInputs tx) utxos minSpending
349
+ txIns <- newEitherT $ selectTxIns @ w (txInputs tx) utxos minSpending
352
350
pure $ tx {txInputs = txIns <> txInputs tx}
353
351
354
352
-- | Set collateral or fail in case it's required but not available
@@ -365,7 +363,7 @@ txUsesScripts Tx {txInputs, txMintScripts} =
365
363
(Set. toList txInputs)
366
364
367
365
-- | Ensures all non ada change goes back to user
368
- handleNonAdaChange :: BalanceConfig -> Address -> Map TxOutRef TxOut -> Tx -> Either WAPI. WalletAPIError Tx
366
+ handleNonAdaChange :: BalanceConfig -> Address -> Map TxOutRef TxOut -> Tx -> Either Text Tx
369
367
handleNonAdaChange balanceCfg changeAddr utxos tx =
370
368
let nonAdaChange = getNonAdaChange utxos tx
371
369
predicate =
@@ -389,7 +387,7 @@ handleNonAdaChange balanceCfg changeAddr utxos tx =
389
387
(txOutputs tx)
390
388
in if isValueNat nonAdaChange
391
389
then Right $ if Value. isZero nonAdaChange then tx else tx {txOutputs = outputs}
392
- else Left $ WAPI. InsufficientFunds " Not enough inputs to balance tokens."
390
+ else Left " Not enough inputs to balance tokens."
393
391
394
392
{- | `addAdaChange` checks if `bcSeparateChange` is true,
395
393
if it is then we add the ada change to seperate `TxOut` at changeAddr that contains only ada,
@@ -433,13 +431,13 @@ addOutput changeAddr tx = tx {txOutputs = txOutputs tx ++ [changeTxOut]}
433
431
{- | Add the required signatories to the transaction. Be aware the the signature itself is invalid,
434
432
and will be ignored. Only the pub key hashes are used, mapped to signing key files on disk.
435
433
-}
436
- addSignatories :: PubKeyHash -> Map PubKeyHash DummyPrivKey -> [PubKeyHash ] -> Tx -> Either WAPI. WalletAPIError Tx
434
+ addSignatories :: PubKeyHash -> Map PubKeyHash DummyPrivKey -> [PubKeyHash ] -> Tx -> Either Text Tx
437
435
addSignatories ownPkh privKeys pkhs tx =
438
436
foldM
439
437
( \ tx' pkh ->
440
438
case Map. lookup pkh privKeys of
441
439
Just privKey -> Right $ Tx. addSignature' (unDummyPrivateKey privKey) tx'
442
- Nothing -> Left $ WAPI. PaymentPrivateKeyNotFound $ PaymentPubKeyHash pkh
440
+ Nothing -> Left " Signing key not found. "
443
441
)
444
442
tx
445
443
(ownPkh : pkhs)
@@ -449,13 +447,13 @@ addValidRange ::
449
447
Member (PABEffect w ) effs =>
450
448
POSIXTimeRange ->
451
449
Tx ->
452
- Eff effs (Either WAPI. WalletAPIError Tx )
450
+ Eff effs (Either Text Tx )
453
451
addValidRange timeRange tx =
454
452
if validateRange timeRange
455
453
then
456
- bimap (WAPI. OtherError . Text. pack . show ) (setRange tx)
454
+ bimap (Text. pack . show ) (setRange tx)
457
455
<$> posixTimeRangeToContainedSlotRange @ w timeRange
458
- else pure $ Left $ WAPI. ToCardanoError InvalidValidityRange
456
+ else pure $ Left " Invalid validity interval. "
459
457
where
460
458
setRange tx' range = tx' {txValidRange = range}
461
459
0 commit comments