@@ -55,7 +55,7 @@ import Data.Text qualified as Text
5555import GHC.Real (Ratio ((:%) ))
5656import Ledger qualified
5757import Ledger.Ada qualified as Ada
58- import Ledger.Address (Address (.. ))
58+ import Ledger.Address (Address (.. ), PaymentPubKeyHash ( PaymentPubKeyHash ) )
5959import Ledger.Constraints.OffChain (UnbalancedTx (.. ))
6060import Ledger.Crypto (PubKeyHash )
6161import Ledger.Interval (
@@ -70,7 +70,7 @@ import Ledger.Tx (
7070 TxIn (.. ),
7171 TxInType (.. ),
7272 TxOut (.. ),
73- TxOutRef (.. ),
73+ TxOutRef (.. ), ToCardanoError ( InvalidValidityRange )
7474 )
7575import Ledger.Tx qualified as Tx
7676import Ledger.Tx.CardanoAPI (CardanoBuildTx )
@@ -84,6 +84,7 @@ import Plutus.V1.Ledger.Api (
8484import Ledger.Constraints.OffChain qualified as Constraints
8585import Prettyprinter (pretty , viaShow , (<+>) )
8686import Prelude
87+ import qualified Wallet.API as WAPI
8788
8889-- Config for balancing a `Tx`.
8990data BalanceConfig = BalanceConfig
@@ -106,7 +107,7 @@ balanceTxIO ::
106107 PABConfig ->
107108 PubKeyHash ->
108109 UnbalancedTx ->
109- Eff effs (Either Text Tx )
110+ Eff effs (Either WAPI. WalletAPIError Tx )
110111balanceTxIO = balanceTxIO' @ w defaultBalanceConfig
111112
112113-- | `balanceTxIO'` is more flexible version of `balanceTxIO`, this lets us specify custom `BalanceConfig`.
@@ -117,12 +118,12 @@ balanceTxIO' ::
117118 PABConfig ->
118119 PubKeyHash ->
119120 UnbalancedTx ->
120- Eff effs (Either Text Tx )
121+ Eff effs (Either WAPI. WalletAPIError Tx )
121122balanceTxIO' balanceCfg pabConf ownPkh unbalancedTx' =
122123 runEitherT $
123124 do
124125 updatedOuts <-
125- firstEitherT ( Text. pack . show ) $
126+ firstEitherT WAPI. OtherError $
126127 newEitherT $
127128 sequence <$> traverse (minUtxo @ w ) (unbalancedTx' ^. Constraints. tx . Tx. outputs)
128129
@@ -136,7 +137,7 @@ balanceTxIO' balanceCfg pabConf ownPkh unbalancedTx' =
136137 pabConf
137138 changeAddr
138139
139- privKeys <- newEitherT $ Files. readPrivateKeys @ w pabConf
140+ privKeys <- firstEitherT WAPI. OtherError $ newEitherT $ Files. readPrivateKeys @ w pabConf
140141
141142 let utxoIndex :: Map TxOutRef TxOut
142143 utxoIndex = fmap Tx. toTxOut utxos <> unBalancedTxUtxoIndex unbalancedTx
@@ -163,14 +164,14 @@ balanceTxIO' balanceCfg pabConf ownPkh unbalancedTx' =
163164 if bcHasScripts balanceCfg
164165 then
165166 maybe
166- (throwE " Tx uses script but no collateral was provided." )
167+ (throwE $ WAPI. OtherError " Tx uses script but no collateral was provided." )
167168 (hoistEither . addSignatories ownPkh privKeys requiredSigs . flip addTxCollaterals tx)
168169 mcollateral
169170 else hoistEither $ addSignatories ownPkh privKeys requiredSigs tx
170171
171172 -- Balance the tx
172173 balancedTx <- balanceTxLoop utxoIndex privKeys preBalancedTx
173- changeTxOutWithMinAmt <- newEitherT $ addOutput @ w changeAddr balancedTx
174+ changeTxOutWithMinAmt <- firstEitherT WAPI. OtherError $ newEitherT $ addOutput @ w changeAddr balancedTx
174175
175176 -- Get current Ada change
176177 let adaChange = getAdaChange utxoIndex balancedTx
@@ -213,17 +214,17 @@ balanceTxIO' balanceCfg pabConf ownPkh unbalancedTx' =
213214 Map TxOutRef TxOut ->
214215 Map PubKeyHash DummyPrivKey ->
215216 Tx ->
216- EitherT Text (Eff effs ) Tx
217+ EitherT WAPI. WalletAPIError (Eff effs ) Tx
217218 balanceTxLoop utxoIndex privKeys tx = do
218219 void $ lift $ Files. writeAll @ w pabConf tx
219220
220221 -- Calculate fees by pre-balancing the tx, building it, and running the CLI on result
221222 txWithoutFees <-
222223 newEitherT $ balanceTxStep @ w balanceCfg utxoIndex changeAddr $ tx `withFee` 0
223224
224- exBudget <- newEitherT $ BodyBuilder. buildAndEstimateBudget @ w pabConf privKeys txWithoutFees
225+ exBudget <- firstEitherT WAPI. OtherError $ newEitherT $ BodyBuilder. buildAndEstimateBudget @ w pabConf privKeys txWithoutFees
225226
226- nonBudgettedFees <- newEitherT $ CardanoCLI. calculateMinFee @ w pabConf txWithoutFees
227+ nonBudgettedFees <- firstEitherT WAPI. OtherError $ newEitherT $ CardanoCLI. calculateMinFee @ w pabConf txWithoutFees
227228
228229 let fees = nonBudgettedFees + getBudgetPrice (getExecutionUnitPrices pabConf) exBudget
229230
@@ -244,7 +245,7 @@ utxosAndCollateralAtAddress ::
244245 BalanceConfig ->
245246 PABConfig ->
246247 Address ->
247- Eff effs (Either Text (Map TxOutRef Tx. ChainIndexTxOut , Maybe CollateralUtxo ))
248+ Eff effs (Either WAPI. WalletAPIError (Map TxOutRef Tx. ChainIndexTxOut , Maybe CollateralUtxo ))
248249utxosAndCollateralAtAddress balanceCfg _pabConf changeAddr =
249250 runEitherT $ do
250251 inMemCollateral <- lift $ getInMemCollateral @ w
@@ -254,14 +255,14 @@ utxosAndCollateralAtAddress balanceCfg _pabConf changeAddr =
254255 (UtxosAtExcluding changeAddr . Set. singleton . collateralTxOutRef)
255256 inMemCollateral
256257
257- utxos <- firstEitherT (Text. pack . show ) $ newEitherT $ queryNode @ w nodeQuery
258+ utxos <- firstEitherT (WAPI. OtherError . Text. pack . show ) $ newEitherT $ queryNode @ w nodeQuery
258259
259260 -- check if `bcHasScripts` is true, if this is the case then we search of
260261 -- collateral UTxO in the environment, if such collateral is not present we throw Error.
261262 if bcHasScripts balanceCfg
262263 then
263264 maybe
264- ( throwE $
265+ ( throwE $ WAPI. OtherError $
265266 " The given transaction uses script, but there's no collateral provided."
266267 <> " This usually means that, we failed to create Tx and update our ContractEnvironment."
267268 )
@@ -302,7 +303,7 @@ balanceTxStep ::
302303 Map TxOutRef TxOut ->
303304 Address ->
304305 Tx ->
305- Eff effs (Either Text Tx )
306+ Eff effs (Either WAPI. WalletAPIError Tx )
306307balanceTxStep balanceCfg utxos changeAddr tx =
307308 runEitherT $
308309 (newEitherT . balanceTxIns @ w utxos) tx
@@ -339,7 +340,7 @@ balanceTxIns ::
339340 Member (PABEffect w ) effs =>
340341 Map TxOutRef TxOut ->
341342 Tx ->
342- Eff effs (Either Text Tx )
343+ Eff effs (Either WAPI. WalletAPIError Tx )
343344balanceTxIns utxos tx = do
344345 runEitherT $ do
345346 let txOuts = Tx. txOutputs tx
@@ -377,7 +378,7 @@ handleNonAdaChange ::
377378 Address ->
378379 Map TxOutRef TxOut ->
379380 Tx ->
380- Eff effs (Either Text Tx )
381+ Eff effs (Either WAPI. WalletAPIError Tx )
381382handleNonAdaChange balanceCfg changeAddr utxos tx = runEitherT $ do
382383 let nonAdaChange :: Value
383384 nonAdaChange = getNonAdaChange utxos tx
@@ -403,7 +404,7 @@ handleNonAdaChange balanceCfg changeAddr utxos tx = runEitherT $ do
403404 }
404405
405406 newOutputWithMinAmt <-
406- firstEitherT ( Text. pack . show ) $
407+ firstEitherT WAPI. OtherError $
407408 newEitherT $ minUtxo @ w newOutput
408409
409410 let outputs :: [TxOut ]
@@ -415,7 +416,7 @@ handleNonAdaChange balanceCfg changeAddr utxos tx = runEitherT $ do
415416
416417 if isValueNat nonAdaChange
417418 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."
419420
420421{- | `addAdaChange` checks if `bcSeparateChange` is true,
421422 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 =
466467 , txOutDatumHash = Nothing
467468 }
468469
469- changeTxOutWithMinAmt <-
470- firstEitherT (Text. pack . show ) $
471- newEitherT $
472- minUtxo @ w changeTxOut
470+ changeTxOutWithMinAmt <- newEitherT $
471+ minUtxo @ w changeTxOut
473472
474473 return $ tx {txOutputs = txOutputs tx ++ [changeTxOutWithMinAmt]}
475474
476475{- | Add the required signatories to the transaction. Be aware the the signature itself is invalid,
477476 and will be ignored. Only the pub key hashes are used, mapped to signing key files on disk.
478477-}
479- addSignatories :: PubKeyHash -> Map PubKeyHash DummyPrivKey -> [PubKeyHash ] -> Tx -> Either Text Tx
478+ addSignatories :: PubKeyHash -> Map PubKeyHash DummyPrivKey -> [PubKeyHash ] -> Tx -> Either WAPI. WalletAPIError Tx
480479addSignatories ownPkh privKeys pkhs tx =
481480 foldM
482481 ( \ tx' pkh ->
483482 case Map. lookup pkh privKeys of
484483 Just privKey -> Right $ Tx. addSignature' (unDummyPrivateKey privKey) tx'
485- Nothing -> Left " Signing key not found. "
484+ Nothing -> Left $ WAPI. PaymentPrivateKeyNotFound $ PaymentPubKeyHash pkh
486485 )
487486 tx
488487 (ownPkh : pkhs)
@@ -492,14 +491,14 @@ addValidRange ::
492491 Member (PABEffect w ) effs =>
493492 POSIXTimeRange ->
494493 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"
497496addValidRange timeRange (Right tx) =
498497 if validateRange timeRange
499498 then
500- bimap (Text. pack . show ) (setRange tx)
499+ bimap (WAPI. OtherError . Text. pack . show ) (setRange tx)
501500 <$> posixTimeRangeToContainedSlotRange @ w timeRange
502- else pure $ Left " Invalid validity interval. "
501+ else pure $ Left $ WAPI. ToCardanoError InvalidValidityRange
503502 where
504503 setRange tx' range = tx' {txValidRange = range}
505504
0 commit comments