Skip to content

Commit d0269e1

Browse files
committed
Expanded documentation for classy errors
* Additional documentation describing the use of classy prisms for errors * Added the missing AsExUnitsError (ValidationError era) instance
1 parent 2f61ee7 commit d0269e1

File tree

2 files changed

+38
-8
lines changed

2 files changed

+38
-8
lines changed

src/base/lib/Convex/Class.hs

Lines changed: 24 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -6,6 +6,7 @@
66
{-# LANGUAGE FlexibleInstances #-}
77
{-# LANGUAGE FunctionalDependencies #-}
88
{-# LANGUAGE GADTs #-}
9+
{-# LANGUAGE InstanceSigs #-}
910
{-# LANGUAGE LambdaCase #-}
1011
{-# LANGUAGE OverloadedStrings #-}
1112
{-# LANGUAGE TemplateHaskell #-}
@@ -118,6 +119,7 @@ import Control.Exception (
118119
throwIO,
119120
)
120121
import Control.Lens (
122+
Prism',
121123
at,
122124
set,
123125
to,
@@ -202,8 +204,25 @@ instance AsExUnitsError (ValidationError era) era where
202204
203205
Then functions throwing ExUnitsError throw like this:
204206
@
205-
throwError $ L.review _ExUnitsError $ Phase1Error bla
207+
fun :: (MonadError e m, AsExUnitsError e era) => m ()
208+
fun = do
209+
...
210+
throwError $ L.review _ExUnitsError $ Phase1Error bla
206211
@
212+
and we are not forcing a specific error @e@, but only that @e@ can be created via the prism from an @ExUnitsError@.
213+
214+
It is also possible to have multiple types of errors:
215+
@
216+
fun :: (MonadError e m, AsExUnitsError e era, AsValidationError e era, AsSomeOtherError e) => m ()
217+
fun = do
218+
...
219+
throwError $ L.review _ExUnitsError $ Phase1Error bla
220+
...
221+
throwError $ L.review _PredicateFailures $ []
222+
...
223+
throwError $ L.review _OtherError
224+
@
225+
Note that @OtherError@ is "parallel" to @_ExUnitsError@ and not a descendent, i.e. not related.
207226
208227
The whole tree of exceptions can be mapped in this fashion, which increases the interoperability
209228
between error-throwing functions without the need for explicit 'modifyError' calls.
@@ -229,6 +248,10 @@ instance (C.IsAlonzoBasedEra era) => Show (ValidationError era) where
229248

230249
makeClassyPrisms ''ValidationError
231250

251+
instance AsExUnitsError (ValidationError era) era where
252+
_ExUnitsError :: Prism' (ValidationError era) (ExUnitsError era)
253+
_ExUnitsError = _VExUnits . _ExUnitsError
254+
232255
-- | Send transactions and resolve tx inputs.
233256
class (Monad m) => MonadBlockchain era m | m -> era where
234257
sendTx

src/coin-selection/lib/Convex/CoinSelection.hs

Lines changed: 14 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -227,7 +227,10 @@ bodyError = BodyError . Text.pack . C.docToString . C.prettyError
227227

228228
$(deriveFromJSON defaultOptions{sumEncoding = TaggedObject{tagFieldName = "kind", contentsFieldName = "value"}} ''C.ScriptWitnessIndex)
229229

230-
-- | Balancing errors, including the *special* 'BalancingScriptExecutionErr'.
230+
{- | Balancing errors, including the important 'ScriptExecutionErr'. "Important" in the sense that we
231+
can write prisms such as 'exactScriptExecutionError' that allow for more fine-grained
232+
pattern-matching on the on-chain error.
233+
-}
231234
data BalancingError era
232235
= BalancingError Text
233236
| -- | A single type of balancing error is treated specially: the type with
@@ -243,10 +246,10 @@ data BalancingError era
243246

244247
makeClassyPrisms ''BalancingError
245248

246-
{- | This prism will either match on the exact error using the script witness index and an error
247-
string, or just on being a script execution error. The latter is necessary, since in non-debug
248-
mode, there is no error to match on and the prism should not fail in its purpose in non-debug
249-
mode.
249+
{- | This prism will match on the exact error using the script witness index and an error
250+
string if this information is available. It will behave as a script execution error if no debug logs
251+
are available. The latter is necessary, since in non-debug mode, there is no error to match on and
252+
the prism should not fail in its purpose in non-debug mode.
250253
-}
251254
exactScriptExecutionError :: forall e era. (AsBalancingError e era) => (Int, Text) -> Prism' e [(C.ScriptWitnessIndex, Text, [Text])]
252255
exactScriptExecutionError (i, s) = prism' tobe frombe
@@ -267,8 +270,12 @@ exactScriptExecutionError (i, s) = prism' tobe frombe
267270
-- Not the correct error
268271
| otherwise -> Nothing
269272

270-
{- | Sort *most* balancing errors into 'BalancingError', but script execution errors into their own
271-
data constructor.
273+
{- | This convenience function takes @Left@s of type 'C.TxBodyErrorAutoBalance' and throws
274+
'C.TxBodyScriptErecutionError's as 'ScriptExecutionErr', with extraaction of the error log, if
275+
availalbe. Other @Left@s are thrown as 'BalancingError's.
276+
277+
This is a convenient bridge from cardano-api errors to errors where we can pattern-match on script
278+
execution errors and have an error hierarchy.
272279
-}
273280
balancingError :: (MonadError (BalancingError era) m) => Either (C.TxBodyErrorAutoBalance era) a -> m a
274281
balancingError = \case

0 commit comments

Comments
 (0)