Skip to content

Commit e195ddc

Browse files
committed
Change error type to WalletApiError.
1 parent 857ec74 commit e195ddc

File tree

5 files changed

+64
-59
lines changed

5 files changed

+64
-59
lines changed

src/BotPlutusInterface/Balance.hs

Lines changed: 28 additions & 29 deletions
Original file line numberDiff line numberDiff line change
@@ -55,7 +55,7 @@ import Data.Text qualified as Text
5555
import GHC.Real (Ratio ((:%)))
5656
import Ledger qualified
5757
import Ledger.Ada qualified as Ada
58-
import Ledger.Address (Address (..))
58+
import Ledger.Address (Address (..), PaymentPubKeyHash (PaymentPubKeyHash))
5959
import Ledger.Constraints.OffChain (UnbalancedTx (..))
6060
import Ledger.Crypto (PubKeyHash)
6161
import Ledger.Interval (
@@ -70,7 +70,7 @@ import Ledger.Tx (
7070
TxIn (..),
7171
TxInType (..),
7272
TxOut (..),
73-
TxOutRef (..),
73+
TxOutRef (..), ToCardanoError (InvalidValidityRange)
7474
)
7575
import Ledger.Tx qualified as Tx
7676
import Ledger.Tx.CardanoAPI (CardanoBuildTx)
@@ -84,6 +84,7 @@ import Plutus.V1.Ledger.Api (
8484
import Ledger.Constraints.OffChain qualified as Constraints
8585
import Prettyprinter (pretty, viaShow, (<+>))
8686
import Prelude
87+
import qualified Wallet.API as WAPI
8788

8889
-- Config for balancing a `Tx`.
8990
data 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)
110111
balanceTxIO = 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)
121122
balanceTxIO' 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))
248249
utxosAndCollateralAtAddress 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)
306307
balanceTxStep 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)
343344
balanceTxIns 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)
381382
handleNonAdaChange 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
480479
addSignatories 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"
497496
addValidRange 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

src/BotPlutusInterface/CoinSelection.hs

Lines changed: 16 additions & 14 deletions
Original file line numberDiff line numberDiff line change
@@ -28,7 +28,7 @@ import Control.Lens (
2828
import Control.Monad.Except (foldM, throwError, unless)
2929
import Control.Monad.Freer (Eff, Member)
3030
import Control.Monad.Trans.Class (lift)
31-
import Control.Monad.Trans.Either (hoistEither, newEitherT, runEitherT)
31+
import Control.Monad.Trans.Either (hoistEither, newEitherT, runEitherT, firstEitherT)
3232
import Data.Either.Combinators (isRight, maybeToRight)
3333
import Data.Kind (Type)
3434
import Data.List qualified as List
@@ -52,6 +52,7 @@ import Plutus.V1.Ledger.Api (
5252
)
5353
import Prettyprinter (pretty, (<+>))
5454
import Prelude
55+
import qualified Wallet.API as WAPI
5556

5657
{-
5758
@@ -184,7 +185,7 @@ selectTxIns ::
184185
Set TxIn -> -- Inputs `TxIn` of the transaction.
185186
Map TxOutRef TxOut -> -- Map of utxos that can be spent
186187
Value -> -- total output value of the Tx.
187-
Eff effs (Either Text (Set TxIn))
188+
Eff effs (Either WAPI.WalletAPIError (Set TxIn))
188189
selectTxIns originalTxIns utxosIndex outValue =
189190
runEitherT $ do
190191
let -- This represents the input value.
@@ -227,13 +228,14 @@ selectTxIns originalTxIns utxosIndex outValue =
227228
-- we use the default search strategy to get indexes of optimal utxos, these indexes are for the
228229
-- remainingUtxos, as we are sampling utxos from that set.
229230
selectedUtxosIdxs <-
230-
newEitherT $
231-
searchTxIns @w
232-
defaultSearchStrategy
233-
(isSufficient outVec)
234-
outVec
235-
txInsVec
236-
remainingUtxosVec
231+
firstEitherT WAPI.OtherError $
232+
newEitherT $
233+
searchTxIns @w
234+
defaultSearchStrategy
235+
(isSufficient outVec)
236+
outVec
237+
txInsVec
238+
remainingUtxosVec
237239

238240
lift $ printBpiLog @w (Debug [CoinSelectionLog]) $ "" <+> "Selected UTxOs Index: " <+> pretty selectedUtxosIdxs
239241

@@ -244,10 +246,10 @@ selectTxIns originalTxIns utxosIndex outValue =
244246
selectedVectors :: [ValueVector]
245247
selectedVectors = selectedUtxosIdxs ^.. folded . to (\idx -> remainingUtxosVec ^? ix idx) . folded
246248

247-
finalTxInputVector <- hoistEither $ foldM addVec txInsVec selectedVectors
248-
unless (isSufficient outVec finalTxInputVector) $ throwError "Insufficient Funds"
249+
finalTxInputVector <- firstEitherT WAPI.OtherError $ hoistEither $ foldM addVec txInsVec selectedVectors
250+
unless (isSufficient outVec finalTxInputVector) $ throwError (WAPI.InsufficientFunds "Insufficient funds in the final vector.")
249251

250-
selectedTxIns <- hoistEither $ mapM txOutToTxIn selectedUtxos
252+
selectedTxIns <- firstEitherT WAPI.OtherError $ hoistEither $ mapM txOutToTxIn selectedUtxos
251253

252254
lift $ printBpiLog @w (Debug [CoinSelectionLog]) $ "Selected TxIns: " <+> pretty selectedTxIns
253255

@@ -447,9 +449,9 @@ zeroVec :: Int -> Vector Integer
447449
zeroVec n = Vec.replicate n 0
448450

449451
-- | Convert a value to a vector.
450-
valueToVec :: Set AssetClass -> Value -> Either Text ValueVector
452+
valueToVec :: Set AssetClass -> Value -> Either WAPI.WalletAPIError ValueVector
451453
valueToVec allAssetClasses v =
452-
maybeToRight "Error: Not able to uncons from empty vector." $
454+
maybeToRight (WAPI.OtherError "Error: Not able to uncons from empty vector.") $
453455
(over _Just fst . uncons) $ valuesToVecs allAssetClasses [v]
454456

455457
-- | Convert values to a list of vectors.

src/BotPlutusInterface/Contract.hs

Lines changed: 13 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -95,6 +95,8 @@ import Prettyprinter (Pretty (pretty), (<+>))
9595
import Prettyprinter qualified as PP
9696
import Wallet.Emulator.Error (WalletAPIError (..))
9797
import Prelude
98+
import qualified Wallet.API as WAPI
99+
import qualified Data.Text as T
98100

99101
runContract ::
100102
forall (w :: Type) (s :: Row Type) (e :: Type) (a :: Type).
@@ -325,7 +327,7 @@ balanceTx contractEnv unbalancedTx@(UnbalancedTx (Right tx') _ _ _) = do
325327
result <- handleCollateral @w contractEnv
326328

327329
case result of
328-
Left e -> pure $ BalanceTxFailed (OtherError e)
330+
Left e -> pure $ BalanceTxFailed e
329331
_ -> do
330332
uploadDir @w pabConf.pcSigningKeyFileDir
331333
eitherBalancedTx <-
@@ -337,7 +339,7 @@ balanceTx contractEnv unbalancedTx@(UnbalancedTx (Right tx') _ _ _) = do
337339
pabConf.pcOwnPubKeyHash
338340
unbalancedTx
339341

340-
pure $ either (BalanceTxFailed . OtherError) (BalanceTxSuccess . EmulatorTx) eitherBalancedTx
342+
pure $ either BalanceTxFailed (BalanceTxSuccess . EmulatorTx) eitherBalancedTx
341343

342344
fromCardanoTx :: CardanoTx -> Tx.Tx
343345
fromCardanoTx (CardanoApiTx _) = error "Cannot handle cardano api tx"
@@ -499,7 +501,7 @@ handleCollateral ::
499501
forall (w :: Type) (effs :: [Type -> Type]).
500502
Member (PABEffect w) effs =>
501503
ContractEnvironment w ->
502-
Eff effs (Either Text ())
504+
Eff effs (Either WAPI.WalletAPIError ())
503505
handleCollateral cEnv = do
504506
result <- (fmap swapEither . runEitherT) $
505507
do
@@ -525,13 +527,13 @@ handleCollateral cEnv = do
525527
helperLog
526528
("Failed to create collateral UTxO: " <> pretty notCreatedCollateral)
527529

528-
pure ("Failed to create collateral UTxO: " <> notCreatedCollateral)
530+
pure ("Failed to create collateral UTxO: " <> show notCreatedCollateral)
529531

530532
case result of
531533
Right collteralUtxo ->
532534
setInMemCollateral @w collteralUtxo
533535
>> Right <$> printBpiLog @w (Debug [CollateralLog]) "successfully set the collateral utxo in env."
534-
Left err -> pure $ Left $ "Failed to make collateral: " <> err
536+
Left err -> pure $ Left $ WAPI.OtherError $ T.pack $ "Failed to make collateral: " <> show err
535537

536538
{- | Create collateral UTxO by submitting Tx.
537539
Then try to find created UTxO at own PKH address.
@@ -540,13 +542,13 @@ makeCollateral ::
540542
forall (w :: Type) (effs :: [Type -> Type]).
541543
Member (PABEffect w) effs =>
542544
ContractEnvironment w ->
543-
Eff effs (Either Text CollateralUtxo)
545+
Eff effs (Either WAPI.WalletAPIError CollateralUtxo)
544546
makeCollateral cEnv = runEitherT $ do
545547
lift $ printBpiLog @w (Notice [CollateralLog]) "Making collateral"
546548

547549
let pabConf = cEnv.cePABConfig
548550
unbalancedTx <-
549-
firstEitherT (Text.pack . show) $
551+
firstEitherT (WAPI.OtherError . Text.pack . show) $
550552
hoistEither $ Collateral.mkCollateralTx pabConf
551553

552554
balancedTx <-
@@ -558,7 +560,7 @@ makeCollateral cEnv = runEitherT $ do
558560

559561
wbr <- lift $ writeBalancedTx cEnv (EmulatorTx balancedTx)
560562
case wbr of
561-
WriteBalancedTxFailed e -> throwE . Text.pack $ "Failed to create collateral output: " <> show e
563+
WriteBalancedTxFailed e -> throwE . WAPI.OtherError . Text.pack $ "Failed to create collateral output: " <> show e
562564
WriteBalancedTxSuccess cTx -> do
563565
status <- lift $ awaitTxStatusChange cEnv (getCardanoTxId cTx)
564566
lift $ printBpiLog @w (Notice [CollateralLog]) $ "Collateral Tx Status: " <> pretty status
@@ -569,7 +571,7 @@ findCollateralAtOwnPKH ::
569571
forall (w :: Type) (effs :: [Type -> Type]).
570572
Member (PABEffect w) effs =>
571573
ContractEnvironment w ->
572-
Eff effs (Either Text CollateralUtxo)
574+
Eff effs (Either WAPI.WalletAPIError CollateralUtxo)
573575
findCollateralAtOwnPKH cEnv =
574576
runEitherT $
575577
CollateralUtxo <$> do
@@ -580,11 +582,11 @@ findCollateralAtOwnPKH cEnv =
580582
pabConf.pcOwnStakePubKeyHash
581583

582584
r <-
583-
firstEitherT (Text.pack . show) $
585+
firstEitherT (WAPI.OtherError . Text.pack . show) $
584586
newEitherT $ queryNode @w (UtxosAt changeAddr)
585587
let refsAndOuts = Map.toList $ Tx.toTxOut <$> r
586588
hoistEither $ case filter check refsAndOuts of
587-
[] -> Left "Couldn't find collateral UTxO"
589+
[] -> Left $ WAPI.OtherError "Couldn't find collateral UTxO"
588590
((oref, _) : _) -> Right oref
589591
where
590592
check (_, txOut) = Tx.txOutValue txOut == collateralValue (cePABConfig cEnv)

0 commit comments

Comments
 (0)