Skip to content

Commit

Permalink
BalancingError with explicit script evaluation errors
Browse files Browse the repository at this point in the history
* Makes script evaluation errors explicit by wrapping those, and only
  those, in 'ScriptExecutionError'
* Should, in turn, allow using classy prisms to extract just the script
  execution errors.
* The errors themselves are, again, shown as strings, since the error
  hierarchy allows json encoding, which is not allowed by the actual
  script execution error.
  • Loading branch information
choener committed Feb 20, 2025
1 parent 4bbd178 commit ea08dd8
Showing 1 changed file with 17 additions and 3 deletions.
20 changes: 17 additions & 3 deletions src/coin-selection/lib/Convex/CoinSelection.hs
Original file line number Diff line number Diff line change
@@ -1,7 +1,7 @@
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE DerivingVia #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE GADTs #-}
Expand Down Expand Up @@ -136,7 +136,7 @@ import Convex.Utxos (
import Convex.Utxos qualified as Utxos
import Convex.Wallet (Wallet)
import Convex.Wallet qualified as Wallet
import Data.Aeson (FromJSON, ToJSON)
import Data.Aeson (FromJSON (..), ToJSON (..))
import Data.Bifunctor (Bifunctor (..))
import Data.Default (Default (..))
import Data.Functor.Identity (Identity)
Expand Down Expand Up @@ -214,8 +214,14 @@ makeClassyPrisms ''CoinSelectionError
bodyError :: C.TxBodyError -> CoinSelectionError
bodyError = BodyError . Text.pack . C.docToString . C.prettyError

-- | Balancing errors, including the *special* 'BalancingScriptExecutionErr'.
data BalancingError era
= BalancingError Text
| -- | A single type of balancing error is treated specially: the type with
-- 'C.ScriptExecutionError's.
-- TODO: I would like to retain the actual error structure, but this collides (quite massively)
-- with the required JSON encoding / decoding.
ScriptExecutionErr Text -- [(C.ScriptWitnessIndex, C.ScriptExecutionError)]
| CheckMinUtxoValueError (C.TxOut C.CtxTx era) C.Quantity
| BalanceCheckError (BalancingError era)
| ComputeBalanceChangeError
Expand All @@ -224,8 +230,16 @@ data BalancingError era

makeClassyPrisms ''BalancingError

{- | Sort *most* balancing errors into 'BalancingError', but script execution errors into their own
data constructor.
-}
balancingError :: (MonadError (BalancingError era) m) => Either (C.TxBodyErrorAutoBalance era) a -> m a
balancingError = either (throwError . BalancingError . Text.pack . C.docToString . C.prettyError) pure
balancingError = \case
Right a -> pure a
Left err@(C.TxBodyScriptExecutionError _es) -> throwError $ ScriptExecutionErr (asText err)
Left err -> throwError . BalancingError $ asText err
where
asText = Text.pack . C.docToString . C.prettyError

-- | Messages that are produced during coin selection and balancing
data TxBalancingMessage
Expand Down

0 comments on commit ea08dd8

Please sign in to comment.