Skip to content

Commit 3d38fd6

Browse files
committed
[Builtins] Replace 'EvaluationResult' with 'BuiltinResult' (#5926)
This replaces several `Emitter (EvaluationResult a)` occurrences with `BuiltinResult`, something that I missed the last [time](#5728). In addition to that, it also replaces `EvaluationResult` with `BuiltinResult` in general. It doesn't matter performance-wise (modulo a regression that we didn't notice some time ago), but `BuiltinResult`, unlike `EvaluationResult`, allows one to attach an error message to a failure, which we do in this PR as well, meaning we now get better error messages. And we also now respect the operational vs structural evaluation errors distinction. The PR also replaces `Emitter` with `BuiltinResult`. And makes the GHC Core of builtins smaller by making error-throwing functions (not) inline (see `Note [INLINE and OPAQUE on error-related definitions]` for details).
1 parent 8fbfbf4 commit 3d38fd6

File tree

19 files changed

+322
-216
lines changed

19 files changed

+322
-216
lines changed
Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,3 @@
1+
### Changed
2+
3+
- Forbade using `EvaluationResult` in the builtins code in favor of `BuiltinResult` in #5926, so that builtins throw errors with more helpful messages.

plutus-core/cost-model/budgeting-bench/Benchmarks/Nops.hs

Lines changed: 10 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -22,6 +22,7 @@ import PlutusCore.Evaluation.Machine.BuiltinCostModel hiding (BuiltinCostModel)
2222
import PlutusCore.Evaluation.Machine.ExBudgetingDefaults
2323
import PlutusCore.Evaluation.Machine.ExMemoryUsage (ExMemoryUsage)
2424
import PlutusCore.Evaluation.Machine.MachineParameters
25+
import PlutusCore.Evaluation.Result (evaluationFailure)
2526
import PlutusCore.Pretty
2627
import PlutusPrelude
2728
import UntypedPlutusCore.Evaluation.Machine.Cek
@@ -132,12 +133,12 @@ nopCostParameters =
132133
infixr >:
133134
(>:) :: uni ~ DefaultUni
134135
=> SomeConstant uni Integer
135-
-> EvaluationResult Integer
136-
-> EvaluationResult Integer
136+
-> BuiltinResult Integer
137+
-> BuiltinResult Integer
137138
n >: k =
138139
case n of
139140
SomeConstant (Some (ValueOf DefaultUniInteger _)) -> k
140-
_ -> EvaluationFailure
141+
_ -> evaluationFailure
141142

142143
{- | The meanings of the builtins. Each one takes a number of arguments and
143144
returns a result without doing any other work. A builtin can process its
@@ -225,27 +226,27 @@ instance uni ~ DefaultUni => ToBuiltinMeaning uni NopFun where
225226
-- Integers unlifted via SomeConstant
226227
toBuiltinMeaning _semvar Nop1c =
227228
makeBuiltinMeaning
228-
(\c1 -> c1 >: EvaluationSuccess 11)
229+
(\c1 -> c1 >: BuiltinSuccess 11)
229230
(runCostingFunOneArgument . paramNop1)
230231
toBuiltinMeaning _semvar Nop2c =
231232
makeBuiltinMeaning
232-
(\c1 c2 -> c1 >: c2 >: EvaluationSuccess 22)
233+
(\c1 c2 -> c1 >: c2 >: BuiltinSuccess 22)
233234
(runCostingFunTwoArguments . paramNop2)
234235
toBuiltinMeaning _semvar Nop3c =
235236
makeBuiltinMeaning
236-
(\c1 c2 c3 -> c1 >: c2 >: c3 >: EvaluationSuccess 33)
237+
(\c1 c2 c3 -> c1 >: c2 >: c3 >: BuiltinSuccess 33)
237238
(runCostingFunThreeArguments . paramNop3)
238239
toBuiltinMeaning _semvar Nop4c =
239240
makeBuiltinMeaning
240-
(\c1 c2 c3 c4 -> c1 >: c2 >: c3 >: c4 >: EvaluationSuccess 44)
241+
(\c1 c2 c3 c4 -> c1 >: c2 >: c3 >: c4 >: BuiltinSuccess 44)
241242
(runCostingFunFourArguments . paramNop4)
242243
toBuiltinMeaning _semvar Nop5c =
243244
makeBuiltinMeaning
244-
(\c1 c2 c3 c4 c5 -> c1 >: c2 >: c3 >: c4 >: c5 >: EvaluationSuccess 55)
245+
(\c1 c2 c3 c4 c5 -> c1 >: c2 >: c3 >: c4 >: c5 >: BuiltinSuccess 55)
245246
(runCostingFunFiveArguments . paramNop5)
246247
toBuiltinMeaning _semvar Nop6c =
247248
makeBuiltinMeaning
248-
(\c1 c2 c3 c4 c5 c6 -> c1 >: c2 >: c3 >: c4 >: c5 >: c6 >: EvaluationSuccess 66)
249+
(\c1 c2 c3 c4 c5 c6 -> c1 >: c2 >: c3 >: c4 >: c5 >: c6 >: BuiltinSuccess 66)
249250
(runCostingFunSixArguments . paramNop6)
250251
-- Opaque Integers
251252
toBuiltinMeaning _semvar Nop1o =

plutus-core/plutus-core/examples/PlutusCore/Examples/Builtins.hs

Lines changed: 19 additions & 19 deletions
Original file line numberDiff line numberDiff line change
@@ -24,6 +24,7 @@ import PlutusCore.Data
2424
import PlutusCore.Evaluation.Machine.BuiltinCostModel
2525
import PlutusCore.Evaluation.Machine.ExBudget
2626
import PlutusCore.Evaluation.Machine.ExBudgetStream
27+
import PlutusCore.Evaluation.Result (evaluationFailure)
2728
import PlutusCore.Pretty
2829

2930
import PlutusCore.StdLib.Data.ScottList qualified as Plc
@@ -277,31 +278,31 @@ instance uni ~ DefaultUni => ToBuiltinMeaning uni ExtensionFun where
277278
idAssumeCheckBoolPlc
278279
whatever
279280
where
280-
idAssumeCheckBoolPlc :: Opaque val Bool -> EvaluationResult Bool
281+
idAssumeCheckBoolPlc :: Opaque val Bool -> BuiltinResult Bool
281282
idAssumeCheckBoolPlc val =
282283
case asConstant val of
283-
Right (Some (ValueOf DefaultUniBool b)) -> EvaluationSuccess b
284-
_ -> EvaluationFailure
284+
Right (Some (ValueOf DefaultUniBool b)) -> pure b
285+
_ -> evaluationFailure
285286

286287
toBuiltinMeaning _semvar IdSomeConstantBool =
287288
makeBuiltinMeaning
288289
idSomeConstantBoolPlc
289290
whatever
290291
where
291-
idSomeConstantBoolPlc :: SomeConstant uni Bool -> EvaluationResult Bool
292+
idSomeConstantBoolPlc :: SomeConstant uni Bool -> BuiltinResult Bool
292293
idSomeConstantBoolPlc = \case
293-
SomeConstant (Some (ValueOf DefaultUniBool b)) -> EvaluationSuccess b
294-
_ -> EvaluationFailure
294+
SomeConstant (Some (ValueOf DefaultUniBool b)) -> pure b
295+
_ -> evaluationFailure
295296

296297
toBuiltinMeaning _semvar IdIntegerAsBool =
297298
makeBuiltinMeaning
298299
idIntegerAsBool
299300
whatever
300301
where
301-
idIntegerAsBool :: SomeConstant uni Integer -> EvaluationResult (SomeConstant uni Integer)
302+
idIntegerAsBool :: SomeConstant uni Integer -> BuiltinResult (SomeConstant uni Integer)
302303
idIntegerAsBool = \case
303-
con@(SomeConstant (Some (ValueOf DefaultUniBool _))) -> EvaluationSuccess con
304-
_ -> EvaluationFailure
304+
con@(SomeConstant (Some (ValueOf DefaultUniBool _))) -> pure con
305+
_ -> evaluationFailure
305306

306307
toBuiltinMeaning _semvar IdFInteger =
307308
makeBuiltinMeaning
@@ -380,8 +381,7 @@ instance uni ~ DefaultUni => ToBuiltinMeaning uni ExtensionFun where
380381
whatever
381382
where
382383
unsafeCoerceElPlc
383-
:: SomeConstant DefaultUni [a]
384-
-> EvaluationResult (SomeConstant DefaultUni [b])
384+
:: SomeConstant DefaultUni [a] -> BuiltinResult (SomeConstant DefaultUni [b])
385385
unsafeCoerceElPlc (SomeConstant (Some (ValueOf uniList xs))) = do
386386
DefaultUniList _ <- pure uniList
387387
pure $ fromValueOf uniList xs
@@ -398,7 +398,7 @@ instance uni ~ DefaultUni => ToBuiltinMeaning uni ExtensionFun where
398398

399399
toBuiltinMeaning _semvar ErrorPrime =
400400
makeBuiltinMeaning
401-
EvaluationFailure
401+
(evaluationFailure :: forall a. BuiltinResult a)
402402
whatever
403403

404404
toBuiltinMeaning _semvar Comma =
@@ -422,7 +422,7 @@ instance uni ~ DefaultUni => ToBuiltinMeaning uni ExtensionFun where
422422
:: SomeConstant uni a
423423
-> SomeConstant uni b
424424
-> SomeConstant uni (a, b)
425-
-> EvaluationResult (SomeConstant uni (a, b))
425+
-> BuiltinResult (SomeConstant uni (a, b))
426426
biconstPairPlc
427427
(SomeConstant (Some (ValueOf uniA x)))
428428
(SomeConstant (Some (ValueOf uniB y)))
@@ -439,7 +439,7 @@ instance uni ~ DefaultUni => ToBuiltinMeaning uni ExtensionFun where
439439
where
440440
swapPlc
441441
:: SomeConstant uni (a, b)
442-
-> EvaluationResult (SomeConstant uni (b, a))
442+
-> BuiltinResult (SomeConstant uni (b, a))
443443
swapPlc (SomeConstant (Some (ValueOf uniPairAB p))) = do
444444
DefaultUniPair uniA uniB <- pure uniPairAB
445445
pure $ fromValueOf (DefaultUniPair uniB uniA) (snd p, fst p)
@@ -452,7 +452,7 @@ instance uni ~ DefaultUni => ToBuiltinMeaning uni ExtensionFun where
452452
-- The type reads as @[(a, Bool)] -> [(Bool, a)]@.
453453
swapElsPlc
454454
:: SomeConstant uni [SomeConstant uni (a, Bool)]
455-
-> EvaluationResult (SomeConstant uni [SomeConstant uni (Bool, a)])
455+
-> BuiltinResult (SomeConstant uni [SomeConstant uni (Bool, a)])
456456
swapElsPlc (SomeConstant (Some (ValueOf uniList xs))) = do
457457
DefaultUniList (DefaultUniPair uniA DefaultUniBool) <- pure uniList
458458
let uniList' = DefaultUniList $ DefaultUniPair DefaultUniBool uniA
@@ -462,10 +462,10 @@ instance uni ~ DefaultUni => ToBuiltinMeaning uni ExtensionFun where
462462
-- See Note [Builtin semantics variants]
463463
toBuiltinMeaning semvar ExtensionVersion =
464464
makeBuiltinMeaning
465-
@(() -> EvaluationResult Integer)
466-
(\(_ :: ()) -> EvaluationSuccess $ case semvar of
467-
ExtensionFunSemanticsVariantX -> 0
468-
ExtensionFunSemanticsVariantY -> 1)
465+
@(() -> Integer)
466+
(\_ -> case semvar of
467+
ExtensionFunSemanticsVariantX -> 0
468+
ExtensionFunSemanticsVariantY -> 1)
469469
whatever
470470

471471
-- We want to know if the CEK machine releases individual budgets after accounting for them and

plutus-core/plutus-core/src/PlutusCore/Builtin/KnownType.hs

Lines changed: 25 additions & 17 deletions
Original file line numberDiff line numberDiff line change
@@ -248,9 +248,8 @@ typeMismatchError uniExp uniAct =
248248
, "expected: " ++ displayBy botRenderContext (SomeTypeIn uniExp)
249249
, "; actual: " ++ displayBy botRenderContext (SomeTypeIn uniAct)
250250
]
251-
-- Just for tidier Core to get generated, we don't care about performance here, since it's just a
252-
-- failure message and evaluation is about to be shut anyway.
253-
{-# NOINLINE typeMismatchError #-}
251+
-- See Note [INLINE and OPAQUE on error-related definitions].
252+
{-# OPAQUE typeMismatchError #-}
254253

255254
-- Normally it's a good idea for an exported abstraction not to be a type synonym, since a @newtype@
256255
-- is cheap, looks good in error messages and clearly emphasize an abstraction barrier. However we
@@ -322,11 +321,6 @@ readKnownSelf
322321
readKnownSelf val = fromRightM (throwBuiltinErrorWithCause val) $ readKnown val
323322
{-# INLINE readKnownSelf #-}
324323

325-
instance MakeKnownIn uni val a => MakeKnownIn uni val (EvaluationResult a) where
326-
makeKnown EvaluationFailure = evaluationFailure
327-
makeKnown (EvaluationSuccess x) = makeKnown x
328-
{-# INLINE makeKnown #-}
329-
330324
instance MakeKnownIn uni val a => MakeKnownIn uni val (BuiltinResult a) where
331325
makeKnown res = res >>= makeKnown
332326
{-# INLINE makeKnown #-}
@@ -338,24 +332,38 @@ instance MakeKnownIn uni val a => MakeKnownIn uni val (BuiltinResult a) where
338332
-- I.e. it would essentially allow us to catch errors and handle them in a programmable way.
339333
-- We forbid this, because it complicates code and isn't supported by evaluation engines anyway.
340334
instance
341-
( TypeError ('Text "‘EvaluationResult’ cannot appear in the type of an argument")
335+
( TypeError ('Text "‘BuiltinResult’ cannot appear in the type of an argument")
336+
, uni ~ UniOf val
337+
) => ReadKnownIn uni val (BuiltinResult a) where
338+
readKnown _ = throwUnderTypeError
339+
{-# INLINE readKnown #-}
340+
341+
instance
342+
( TypeError ('Text "Use ‘BuiltinResult’ instead of ‘EvaluationResult’")
343+
, uni ~ UniOf val
344+
) => MakeKnownIn uni val (EvaluationResult a) where
345+
makeKnown _ = throwUnderTypeError
346+
{-# INLINE makeKnown #-}
347+
348+
instance
349+
( TypeError ('Text "Use ‘BuiltinResult’ instead of ‘EvaluationResult’")
342350
, uni ~ UniOf val
343351
) => ReadKnownIn uni val (EvaluationResult a) where
344-
readKnown _ = throwing _StructuralUnliftingError "Panic: 'TypeError' was bypassed"
345-
-- Just for 'readKnown' not to appear in the generated Core.
352+
readKnown _ = throwUnderTypeError
346353
{-# INLINE readKnown #-}
347354

348-
instance MakeKnownIn uni val a => MakeKnownIn uni val (Emitter a) where
349-
makeKnown a = case runEmitter a of
350-
(x, logs) -> withLogs logs $ makeKnown x
355+
instance
356+
( TypeError ('Text "Use ‘BuiltinResult’ instead of ‘Emitter’")
357+
, uni ~ UniOf val
358+
) => MakeKnownIn uni val (Emitter a) where
359+
makeKnown _ = throwUnderTypeError
351360
{-# INLINE makeKnown #-}
352361

353362
instance
354-
( TypeError ('Text "‘Emitter’ cannot appear in the type of an argument")
363+
( TypeError ('Text "Use ‘BuiltinResult’ instead of ‘Emitter’")
355364
, uni ~ UniOf val
356365
) => ReadKnownIn uni val (Emitter a) where
357-
readKnown _ = throwing _StructuralUnliftingError "Panic: 'TypeError' was bypassed"
358-
-- Just for 'readKnown' not to appear in the generated Core.
366+
readKnown _ = throwUnderTypeError
359367
{-# INLINE readKnown #-}
360368

361369
instance HasConstantIn uni val => MakeKnownIn uni val (SomeConstant uni rep) where

plutus-core/plutus-core/src/PlutusCore/Builtin/Meaning.hs

Lines changed: 1 addition & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -30,7 +30,6 @@ import PlutusCore.Evaluation.Machine.ExBudgetStream
3030
import PlutusCore.Evaluation.Machine.ExMemoryUsage
3131
import PlutusCore.Name.Unique
3232

33-
import Control.Monad.Except (throwError)
3433
import Data.Array
3534
import Data.Kind qualified as GHC
3635
import Data.Proxy
@@ -244,7 +243,7 @@ instance (Typeable res, KnownTypeAst TyName (UniOf val) res, MakeKnown val res)
244243
-- either a budgeting failure or a budgeting success with a cost and a 'BuiltinResult'
245244
-- computation inside, but that would slow things down a bit and the current strategy is
246245
-- reasonable enough.
247-
(BuiltinCostedResult (ExBudgetLast mempty) . throwError)
246+
builtinRuntimeFailure
248247
(\(x, cost) -> BuiltinCostedResult cost $ makeKnown x)
249248
{-# INLINE toMonoF #-}
250249

plutus-core/plutus-core/src/PlutusCore/Builtin/Result.hs

Lines changed: 30 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,9 +1,11 @@
1+
-- editorconfig-checker-disable-file
12
{-# LANGUAGE FlexibleInstances #-}
23
{-# LANGUAGE FunctionalDependencies #-}
34
{-# LANGUAGE LambdaCase #-}
45
{-# LANGUAGE MultiParamTypeClasses #-}
56
{-# LANGUAGE OverloadedStrings #-}
67
{-# LANGUAGE RankNTypes #-}
8+
{-# LANGUAGE StrictData #-}
79
{-# LANGUAGE TemplateHaskell #-}
810

911
module PlutusCore.Builtin.Result
@@ -21,6 +23,7 @@ module PlutusCore.Builtin.Result
2123
, _StructuralUnliftingError
2224
, _OperationalUnliftingError
2325
, throwNotAConstant
26+
, throwUnderTypeError
2427
, withLogs
2528
, throwing
2629
, throwing_
@@ -39,13 +42,14 @@ import Data.Bitraversable
3942
import Data.DList (DList)
4043
import Data.String (IsString)
4144
import Data.Text (Text)
45+
import Data.Text qualified as Text
4246
import Prettyprinter
4347

4448
-- | The error message part of an 'UnliftingEvaluationError'.
4549
newtype UnliftingError = MkUnliftingError
4650
{ unUnliftingError :: Text
4751
} deriving stock (Show, Eq)
48-
deriving newtype (IsString, Semigroup, NFData)
52+
deriving newtype (IsString, Semigroup, Monoid, NFData)
4953

5054
-- | When unlifting of a PLC term into a Haskell value fails, this error is thrown.
5155
newtype UnliftingEvaluationError = MkUnliftingEvaluationError
@@ -55,7 +59,7 @@ newtype UnliftingEvaluationError = MkUnliftingEvaluationError
5559

5660
-- | The type of errors that 'readKnown' and 'makeKnown' can return.
5761
data BuiltinError
58-
= BuiltinUnliftingEvaluationError !UnliftingEvaluationError
62+
= BuiltinUnliftingEvaluationError UnliftingEvaluationError
5963
| BuiltinEvaluationFailure
6064
deriving stock (Show, Eq)
6165

@@ -143,6 +147,10 @@ instance MonadEmitter BuiltinResult where
143147
emit txt = BuiltinSuccessWithLogs (pure txt) ()
144148
{-# INLINE emit #-}
145149

150+
instance MonadFail BuiltinResult where
151+
fail err = BuiltinFailure (pure $ Text.pack err) BuiltinEvaluationFailure
152+
{-# INLINE fail #-}
153+
146154
instance Pretty UnliftingError where
147155
pretty (MkUnliftingError err) = fold
148156
[ "Could not unlift a value:", hardline
@@ -155,6 +163,21 @@ instance Pretty BuiltinError where
155163
pretty (BuiltinUnliftingEvaluationError err) = "Builtin evaluation failure:" <+> pretty err
156164
pretty BuiltinEvaluationFailure = "Builtin evaluation failure"
157165

166+
{- Note [INLINE and OPAQUE on error-related definitions]
167+
We mark error-related definitions such as prisms like '_StructuralUnliftingError' and regular
168+
functions like 'throwNotAConstant' with @INLINE@, because this produces significantly less cluttered
169+
GHC Core. Not doing so results in 20+% larger Core for builtins.
170+
171+
However in a few specific cases we use @OPAQUE@ instead to get tighter Core. @OPAQUE@ is the same as
172+
@NOINLINE@ except the former _actually_ prevents GHC from inlining the definition unlike the latter.
173+
See this for details: https://github.com/ghc-proposals/ghc-proposals/blob/5577fd008924de8d89cfa9855fa454512e7dcc75/proposals/0415-opaque-pragma.rst
174+
175+
It's hard to predict where @OPAQUE@ instead of @INLINE@ will help to make GHC Core tidier, so it's
176+
mostly just looking into the Core and seeing where there's obvious duplication that can be removed.
177+
Such cases tend to be functions returning a value of a concrete error type (as opposed to a type
178+
variable).
179+
-}
180+
158181
-- See Note [Ignoring context in OperationalEvaluationError].
159182
-- | Construct a prism focusing on the @*EvaluationFailure@ part of @err@ by taking
160183
-- that @*EvaluationFailure@ and
@@ -181,6 +204,10 @@ throwNotAConstant :: MonadError BuiltinError m => m void
181204
throwNotAConstant = throwing _StructuralUnliftingError "Not a constant"
182205
{-# INLINE throwNotAConstant #-}
183206

207+
throwUnderTypeError :: MonadError BuiltinError m => m void
208+
throwUnderTypeError = throwing _StructuralUnliftingError "Panic: 'TypeError' was bypassed"
209+
{-# INLINE throwUnderTypeError #-}
210+
184211
-- | Prepend logs to a 'BuiltinResult' computation.
185212
withLogs :: DList Text -> BuiltinResult a -> BuiltinResult a
186213
withLogs logs1 = \case
@@ -242,6 +269,7 @@ instance MonadError BuiltinError BuiltinResult where
242269
(OperationalEvaluationError
243270
(MkUnliftingError operationalErr))) -> pure operationalErr
244271
_ -> mempty
272+
{-# INLINE throwError #-}
245273

246274
-- Throwing logs out is lame, but embedding them into the error would be weird, since that
247275
-- would change the error. Not that any of that matters, we only implement this because it's a

plutus-core/plutus-core/src/PlutusCore/Builtin/Runtime.hs

Lines changed: 6 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -10,6 +10,7 @@ import PlutusCore.Builtin.KnownType
1010
import PlutusCore.Evaluation.Machine.ExBudgetStream
1111

1212
import Control.DeepSeq
13+
import Control.Monad.Except (throwError)
1314
import NoThunks.Class
1415

1516
-- | A 'BuiltinRuntime' represents a possibly partial builtin application, including an empty
@@ -78,6 +79,11 @@ instance (Bounded fun, Enum fun) => NoThunks (BuiltinsRuntime fun val) where
7879
wNoThunks ctx (BuiltinsRuntime env) = allNoThunks $ map (wNoThunks ctx . env) enumerate
7980
showTypeOf = const "PlutusCore.Builtin.Runtime.BuiltinsRuntime"
8081

82+
builtinRuntimeFailure :: BuiltinError -> BuiltinRuntime val
83+
builtinRuntimeFailure = BuiltinCostedResult (ExBudgetLast mempty) . throwError
84+
-- See Note [INLINE and OPAQUE on error-related definitions].
85+
{-# OPAQUE builtinRuntimeFailure #-}
86+
8187
-- | Look up the runtime info of a built-in function during evaluation.
8288
lookupBuiltin :: fun -> BuiltinsRuntime fun val -> BuiltinRuntime val
8389
lookupBuiltin fun (BuiltinsRuntime env) = env fun

plutus-core/plutus-core/src/PlutusCore/Crypto/Utils.hs

Lines changed: 0 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -12,11 +12,6 @@ import Data.Kind (Type)
1212
import Data.Text (Text)
1313
import Text.Printf (printf)
1414

15-
-- TODO: Something like 'failWithMessage x y *> foo' should really fail with
16-
-- 'EvaluationFailure' without evaluating 'foo', but currently it will. This
17-
-- requires a fix to how Emitter and EvaluationResult work, and since we don't
18-
-- expect 'failWithMessage' to be used this way, we note this for future
19-
-- reference only for when such fixes are made.
2015
failWithMessage :: forall (a :: Type). Text -> Text -> BuiltinResult a
2116
failWithMessage location reason = do
2217
emit $ location <> ": " <> reason

0 commit comments

Comments
 (0)