Skip to content

Commit

Permalink
[Builtins] Expose 'BuiltinResult' (#5728)
Browse files Browse the repository at this point in the history
  • Loading branch information
effectfully authored Jan 18, 2024
1 parent 2e8284c commit dc9f660
Show file tree
Hide file tree
Showing 29 changed files with 396 additions and 297 deletions.
Original file line number Diff line number Diff line change
@@ -0,0 +1,3 @@
### Changed

- #5728 added `BuiltinResult` and leveraged in places where we used to use `Emitter (EvaluationResult Smth)`.
2 changes: 2 additions & 0 deletions plutus-core/plutus-core.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -113,6 +113,7 @@ library
PlutusCore.Default
PlutusCore.Default.Builtins
PlutusCore.Error
PlutusCore.Evaluation.ErrorWithCause
PlutusCore.Evaluation.Machine.BuiltinCostModel
PlutusCore.Evaluation.Machine.Ck
PlutusCore.Evaluation.Machine.CostingFun.Core
Expand Down Expand Up @@ -205,6 +206,7 @@ library
PlutusCore.Builtin.KnownTypeAst
PlutusCore.Builtin.Meaning
PlutusCore.Builtin.Polymorphism
PlutusCore.Builtin.Result
PlutusCore.Builtin.Runtime
PlutusCore.Builtin.TestKnown
PlutusCore.Builtin.TypeScheme
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -24,7 +24,6 @@ import PlutusCore.Data
import PlutusCore.Evaluation.Machine.BuiltinCostModel
import PlutusCore.Evaluation.Machine.ExBudget
import PlutusCore.Evaluation.Machine.ExBudgetStream
import PlutusCore.Evaluation.Machine.Exception
import PlutusCore.Pretty

import PlutusCore.StdLib.Data.ScottList qualified as Plc
Expand Down
1 change: 1 addition & 0 deletions plutus-core/plutus-core/src/PlutusCore/Builtin.hs
Original file line number Diff line number Diff line change
Expand Up @@ -11,6 +11,7 @@ import PlutusCore.Builtin.KnownType as Export
import PlutusCore.Builtin.KnownTypeAst as Export
import PlutusCore.Builtin.Meaning as Export
import PlutusCore.Builtin.Polymorphism as Export
import PlutusCore.Builtin.Result as Export
import PlutusCore.Builtin.Runtime as Export
import PlutusCore.Builtin.TestKnown as Export
import PlutusCore.Builtin.TypeScheme as Export
21 changes: 10 additions & 11 deletions plutus-core/plutus-core/src/PlutusCore/Builtin/Convert.hs
Original file line number Diff line number Diff line change
Expand Up @@ -13,6 +13,9 @@ module PlutusCore.Builtin.Convert (
byteStringToInteger
) where

import PlutusCore.Builtin (BuiltinResult, emit)
import PlutusCore.Evaluation.Result (evaluationFailure)

import ByteString.StrictBuilder (Builder)
import ByteString.StrictBuilder qualified as Builder
import Control.Monad (guard)
Expand All @@ -22,18 +25,15 @@ import Data.ByteString qualified as BS
import Data.Text (pack)
import Data.Word (Word64, Word8)
import GHC.ByteOrder (ByteOrder (BigEndian, LittleEndian))
import PlutusCore.Builtin.Emitter (Emitter, emit)
import PlutusCore.Evaluation.Result (EvaluationResult (EvaluationFailure))

-- | Wrapper for 'integerToByteString' to make it more convenient to define as a builtin.
integerToByteStringWrapper ::
Bool -> Integer -> Integer -> Emitter (EvaluationResult ByteString)
integerToByteStringWrapper :: Bool -> Integer -> Integer -> BuiltinResult ByteString
integerToByteStringWrapper endiannessArg lengthArg input
-- Check that we are within the Int range on the non-negative side.
| lengthArg < 0 || lengthArg >= 536870912 = do
emit "integerToByteString: inappropriate length argument"
emit $ "Length requested: " <> (pack . show $ input)
pure EvaluationFailure
evaluationFailure
-- As this builtin hasn't been costed yet, we have to impose a temporary limit of 10KiB on requested
-- sizes via the padding argument. This shouldn't be necessary long-term, as once this function is
-- costed, this won't be a problem.
Expand All @@ -42,7 +42,7 @@ integerToByteStringWrapper endiannessArg lengthArg input
| lengthArg > 10240 = do
emit "integerToByteString: padding argument too large"
emit "If you are seeing this, it is a bug: please report this!"
pure EvaluationFailure
evaluationFailure
| otherwise = let endianness = endiannessArgToByteOrder endiannessArg in
-- We use fromIntegral here, despite advice to the contrary in general when defining builtin
-- denotations. This is because, if we've made it this far, we know that overflow or truncation
Expand All @@ -54,15 +54,15 @@ integerToByteStringWrapper endiannessArg lengthArg input
-- This does work proportional to the size of input. However, we're in a failing case
-- anyway, and the user's paid for work proportional to this size in any case.
emit $ "Input: " <> (pack . show $ input)
pure EvaluationFailure
evaluationFailure
NotEnoughDigits -> do
emit "integerToByteString: cannot represent Integer in given number of bytes"
-- This does work proportional to the size of input. However, we're in a failing case
-- anyway, and the user's paid for work proportional to this size in any case.
emit $ "Input: " <> (pack . show $ input)
emit $ "Bytes requested: " <> (pack . show $ lengthArg)
pure EvaluationFailure
Right result -> pure . pure $ result
evaluationFailure
Right result -> pure result

-- | Wrapper for 'byteStringToInteger' to make it more convenient to define as a builtin.
byteStringToIntegerWrapper ::
Expand All @@ -82,8 +82,7 @@ data IntegerToByteStringError =
--
-- For performance and clarity, the endianness argument uses
-- 'ByteOrder', and the length argument is an 'Int'.
integerToByteString ::
ByteOrder -> Int -> Integer -> Either IntegerToByteStringError ByteString
integerToByteString :: ByteOrder -> Int -> Integer -> Either IntegerToByteStringError ByteString
integerToByteString requestedByteOrder requestedLength input
| input < 0 = Left NegativeInput
| input == 0 = Right . BS.replicate requestedLength $ 0x00
Expand Down
12 changes: 8 additions & 4 deletions plutus-core/plutus-core/src/PlutusCore/Builtin/Emitter.hs
Original file line number Diff line number Diff line change
@@ -1,7 +1,7 @@
module PlutusCore.Builtin.Emitter
( Emitter (..)
, runEmitter
, emit
, MonadEmitter (..)
) where

import Control.Monad.Trans.Writer.Strict (Writer, runWriter, tell)
Expand All @@ -17,6 +17,10 @@ runEmitter :: Emitter a -> (a, DList Text)
runEmitter = runWriter . unEmitter
{-# INLINE runEmitter #-}

emit :: Text -> Emitter ()
emit = Emitter . tell . pure
{-# INLINE emit #-}
-- | A type class for \"this monad supports logging\".
class MonadEmitter m where
emit :: Text -> m ()

instance MonadEmitter Emitter where
emit = Emitter . tell . pure
{-# INLINE emit #-}
6 changes: 3 additions & 3 deletions plutus-core/plutus-core/src/PlutusCore/Builtin/HasConstant.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,16 +4,16 @@
{-# LANGUAGE TypeOperators #-}

module PlutusCore.Builtin.HasConstant
( KnownTypeError (..)
( BuiltinError (..)
, throwNotAConstant
, HasConstant (..)
, HasConstantIn
, fromValueOf
, fromValue
) where

import PlutusCore.Builtin.Result
import PlutusCore.Core
import PlutusCore.Evaluation.Machine.Exception
import PlutusCore.Name

import Universe
Expand All @@ -35,7 +35,7 @@ class HasConstant term where
-- Switching from 'MonadError' to 'Either' here gave us a speedup of 2-4%.
-- | Unwrap from a 'Constant'-like constructor throwing an 'UnliftingError' if the provided
-- @term@ is not a wrapped Haskell value.
asConstant :: term -> Either KnownTypeError (Some (ValueOf (UniOf term)))
asConstant :: term -> Either BuiltinError (Some (ValueOf (UniOf term)))

-- | Wrap a Haskell value as a @term@.
fromConstant :: Some (ValueOf (UniOf term)) -> term
Expand Down
126 changes: 29 additions & 97 deletions plutus-core/plutus-core/src/PlutusCore/Builtin/KnownType.hs
Original file line number Diff line number Diff line change
Expand Up @@ -16,15 +16,15 @@
{-# LANGUAGE StrictData #-}

module PlutusCore.Builtin.KnownType
( KnownTypeError
, throwKnownTypeErrorWithCause
( BuiltinError
, throwBuiltinErrorWithCause
, KnownBuiltinTypeIn
, KnownBuiltinType
, MakeKnownM (..)
, BuiltinResult (..)
, ReadKnownM
, MakeKnownIn (..)
, liftReadKnownM
, readKnownConstant
, MakeKnownIn (..)
, MakeKnown
, ReadKnownIn (..)
, ReadKnown
Expand All @@ -37,17 +37,15 @@ import PlutusPrelude
import PlutusCore.Builtin.Emitter
import PlutusCore.Builtin.HasConstant
import PlutusCore.Builtin.Polymorphism
import PlutusCore.Builtin.Result
import PlutusCore.Core
import PlutusCore.Evaluation.Machine.Exception
import PlutusCore.Evaluation.ErrorWithCause
import PlutusCore.Evaluation.Result
import PlutusCore.Pretty

import Control.Lens.TH (makeClassyPrisms)
import Control.Monad.Except
import Data.DList (DList)
import Data.Either.Extras
import Data.String
import Data.Text (Text)
import GHC.Exts (inline, oneShot)
import GHC.TypeLits
import Universe
Expand All @@ -67,7 +65,7 @@ It's critically important that 'readKnown' runs in the concrete 'Either' rather
https://github.com/IntersectMBO/plutus/pull/4307
Replacing the @AsUnliftingError err, AsEvaluationFailure err@ constraints with the dedicated
'KnownTypeError' data type gave us a speedup of up to 4%.
'BuiltinError' data type gave us a speedup of up to 4%.
All the same considerations apply to 'makeKnown':
https://github.com/IntersectMBO/plutus/pull/4421
Expand Down Expand Up @@ -241,16 +239,16 @@ Lifting is allowed to the following classes of types:
one, and for another example define an instance for 'Void' in tests
-}

-- | Attach a @cause@ to a 'KnownTypeError' and throw that.
-- | Attach a @cause@ to a 'BuiltinError' and throw that.
-- Note that an evaluator might require the cause to be computed lazily for best performance on the
-- happy path, hence this function must not force its first argument.
-- TODO: wrap @cause@ in 'Lazy' once we have it.
throwKnownTypeErrorWithCause
throwBuiltinErrorWithCause
:: (MonadError (ErrorWithCause err cause) m, AsUnliftingError err, AsEvaluationFailure err)
=> cause -> KnownTypeError -> m void
throwKnownTypeErrorWithCause cause = \case
KnownTypeUnliftingError unlErr -> throwingWithCause _UnliftingError unlErr $ Just cause
KnownTypeEvaluationFailure -> throwingWithCause _EvaluationFailure () $ Just cause
=> cause -> BuiltinError -> m void
throwBuiltinErrorWithCause cause = \case
BuiltinUnliftingError unlErr -> throwingWithCause _UnliftingError unlErr $ Just cause
BuiltinEvaluationFailure -> throwingWithCause _EvaluationFailure () $ Just cause

typeMismatchError
:: PrettyParens (SomeTypeIn uni)
Expand All @@ -266,89 +264,19 @@ typeMismatchError uniExp uniAct = fromString $ concat
-- failure message and evaluation is about to be shut anyway.
{-# NOINLINE typeMismatchError #-}

-- | The monad that 'makeKnown' runs in.
-- Equivalent to @ExceptT KnownTypeError Emitter@, except optimized in two ways:
--
-- 1. everything is strict
-- 2. has the 'MakeKnownSuccess' constructor that is used for returning a value with no logs
-- attached, which is the most common case for us, so it helps a lot not to construct and
-- deconstruct a redundant tuple
--
-- Moving from @ExceptT KnownTypeError Emitter@ to this data type gave us a speedup of 8% of total
-- evaluation time.
--
-- Logs are represented as a 'DList', because we don't particularly care about the efficiency of
-- logging, since there's no logging on the chain and builtins don't emit much anyway. Otherwise
-- we'd have to use @text-builder@ or @text-builder-linear@ or something of this sort.
data MakeKnownM a
= MakeKnownFailure (DList Text) KnownTypeError
| MakeKnownSuccess a
| MakeKnownSuccessWithLogs (DList Text) a

makeClassyPrisms ''MakeKnownM

instance AsEvaluationFailure (MakeKnownM a) where
_EvaluationFailure = _MakeKnownFailure . _EvaluationFailureVia (pure KnownTypeEvaluationFailure)
{-# INLINE _EvaluationFailure #-}

-- | Prepend logs to a 'MakeKnownM' computation.
withLogs :: DList Text -> MakeKnownM a -> MakeKnownM a
withLogs logs1 = \case
MakeKnownFailure logs2 err -> MakeKnownFailure (logs1 <> logs2) err
MakeKnownSuccess x -> MakeKnownSuccessWithLogs logs1 x
MakeKnownSuccessWithLogs logs2 x -> MakeKnownSuccessWithLogs (logs1 <> logs2) x
{-# INLINE withLogs #-}

instance Functor MakeKnownM where
fmap _ (MakeKnownFailure logs err) = MakeKnownFailure logs err
fmap f (MakeKnownSuccess x) = MakeKnownSuccess (f x)
fmap f (MakeKnownSuccessWithLogs logs x) = MakeKnownSuccessWithLogs logs (f x)
{-# INLINE fmap #-}

-- Written out explicitly just in case (see @fmap@ above for what the case might be).
_ <$ MakeKnownFailure logs err = MakeKnownFailure logs err
x <$ MakeKnownSuccess _ = MakeKnownSuccess x
x <$ MakeKnownSuccessWithLogs logs _ = MakeKnownSuccessWithLogs logs x
{-# INLINE (<$) #-}

instance Applicative MakeKnownM where
pure = MakeKnownSuccess
{-# INLINE pure #-}

MakeKnownFailure logs err <*> _ = MakeKnownFailure logs err
MakeKnownSuccess f <*> a = fmap f a
MakeKnownSuccessWithLogs logs f <*> a = withLogs logs $ fmap f a
{-# INLINE (<*>) #-}

-- Better than the default implementation, because the value in the 'MakeKnownSuccess' case
-- doesn't need to be retained.
MakeKnownFailure logs err *> _ = MakeKnownFailure logs err
MakeKnownSuccess _ *> a = a
MakeKnownSuccessWithLogs logs _ *> a = withLogs logs a
{-# INLINE (*>) #-}

instance Monad MakeKnownM where
MakeKnownFailure logs err >>= _ = MakeKnownFailure logs err
MakeKnownSuccess x >>= f = f x
MakeKnownSuccessWithLogs logs x >>= f = withLogs logs $ f x
{-# INLINE (>>=) #-}

(>>) = (*>)
{-# INLINE (>>) #-}

-- Normally it's a good idea for an exported abstraction not to be a type synonym, since a @newtype@
-- is cheap, looks good in error messages and clearly emphasize an abstraction barrier. However we
-- make 'ReadKnownM' a type synonym for convenience: that way we don't need to derive all the
-- instances (and add new ones whenever we need them), wrap and unwrap all the time (including in
-- user code), which can be non-trivial for such performance-sensitive code (see e.g. 'coerceVia'
-- and 'coerceArg') and there is no abstraction barrier anyway.
-- | The monad that 'readKnown' runs in.
type ReadKnownM = Either KnownTypeError
type ReadKnownM = Either BuiltinError

-- | Lift a 'ReadKnownM' computation into 'MakeKnownM'.
liftReadKnownM :: ReadKnownM a -> MakeKnownM a
liftReadKnownM (Left err) = MakeKnownFailure mempty err
liftReadKnownM (Right x) = MakeKnownSuccess x
-- | Lift a 'ReadKnownM' computation into 'BuiltinResult'.
liftReadKnownM :: ReadKnownM a -> BuiltinResult a
liftReadKnownM (Left err) = BuiltinFailure mempty err
liftReadKnownM (Right x) = BuiltinSuccess x
{-# INLINE liftReadKnownM #-}

-- See Note [Unlifting values of built-in types].
Expand All @@ -363,15 +291,15 @@ readKnownConstant val = asConstant val >>= oneShot \case
-- optimize some of the matching away.
case uniExp `geq` uniAct of
Just Refl -> pure x
Nothing -> Left . KnownTypeUnliftingError $ typeMismatchError uniExp uniAct
Nothing -> throwing _UnliftingError $ typeMismatchError uniExp uniAct
{-# INLINE readKnownConstant #-}

-- See Note [Performance of ReadKnownIn and MakeKnownIn instances].
class uni ~ UniOf val => MakeKnownIn uni val a where
-- | Convert a Haskell value to the corresponding PLC value.
-- The inverse of 'readKnown'.
makeKnown :: a -> MakeKnownM val
default makeKnown :: KnownBuiltinType val a => a -> MakeKnownM val
makeKnown :: a -> BuiltinResult val
default makeKnown :: KnownBuiltinType val a => a -> BuiltinResult val
-- Everything on evaluation path has to be strict in production, so in theory we don't need to
-- force anything here. In practice however all kinds of weird things happen in tests and @val@
-- can be non-strict enough to cause trouble here, so we're forcing the argument. Looking at the
Expand Down Expand Up @@ -400,9 +328,9 @@ type ReadKnown val = ReadKnownIn (UniOf val) val
-- | Same as 'makeKnown', but allows for neither emitting nor storing the cause of a failure.
makeKnownOrFail :: MakeKnownIn uni val a => a -> EvaluationResult val
makeKnownOrFail x = case makeKnown x of
MakeKnownFailure _ _ -> EvaluationFailure
MakeKnownSuccess val -> EvaluationSuccess val
MakeKnownSuccessWithLogs _ val -> EvaluationSuccess val
BuiltinFailure _ _ -> EvaluationFailure
BuiltinSuccess val -> EvaluationSuccess val
BuiltinSuccessWithLogs _ val -> EvaluationSuccess val
{-# INLINE makeKnownOrFail #-}

-- | Same as 'readKnown', but the cause of a potential failure is the provided term itself.
Expand All @@ -411,14 +339,18 @@ readKnownSelf
, AsUnliftingError err, AsEvaluationFailure err
)
=> val -> Either (ErrorWithCause err val) a
readKnownSelf val = fromRightM (throwKnownTypeErrorWithCause val) $ readKnown val
readKnownSelf val = fromRightM (throwBuiltinErrorWithCause val) $ readKnown val
{-# INLINE readKnownSelf #-}

instance MakeKnownIn uni val a => MakeKnownIn uni val (EvaluationResult a) where
makeKnown EvaluationFailure = evaluationFailure
makeKnown (EvaluationSuccess x) = makeKnown x
{-# INLINE makeKnown #-}

instance MakeKnownIn uni val a => MakeKnownIn uni val (BuiltinResult a) where
makeKnown res = res >>= makeKnown
{-# INLINE makeKnown #-}

-- Catching 'EvaluationFailure' here would allow *not* to short-circuit when 'readKnown' fails
-- to read a Haskell value of type @a@. Instead, in the denotation of the builtin function
-- the programmer would be given an explicit 'EvaluationResult' value to handle, which means
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -33,6 +33,7 @@ module PlutusCore.Builtin.KnownTypeAst
import PlutusCore.Builtin.Emitter
import PlutusCore.Builtin.KnownKind
import PlutusCore.Builtin.Polymorphism
import PlutusCore.Builtin.Result
import PlutusCore.Core
import PlutusCore.Evaluation.Result
import PlutusCore.Name
Expand Down Expand Up @@ -223,6 +224,13 @@ instance KnownTypeAst tyname uni a => KnownTypeAst tyname uni (EvaluationResult
toTypeAst _ = toTypeAst $ Proxy @a
{-# INLINE toTypeAst #-}

instance KnownTypeAst tyname uni a => KnownTypeAst tyname uni (BuiltinResult a) where
type IsBuiltin _ (BuiltinResult a) = 'False
type ToHoles _ (BuiltinResult a) = '[TypeHole a]
type ToBinds uni acc (BuiltinResult a) = ToBinds uni acc a
toTypeAst _ = toTypeAst $ Proxy @a
{-# INLINE toTypeAst #-}

instance KnownTypeAst tyname uni a => KnownTypeAst tyname uni (Emitter a) where
type IsBuiltin _ (Emitter a) = 'False
type ToHoles _ (Emitter a) = '[TypeHole a]
Expand Down
Loading

1 comment on commit dc9f660

@github-actions
Copy link
Contributor

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

⚠️ Performance Alert ⚠️

Possible performance regression was detected for benchmark 'Plutus Benchmarks'.
Benchmark result of this commit is worse than the previous benchmark result exceeding threshold 1.05.

Benchmark suite Current: dc9f660 Previous: 2e8284c Ratio
validation-decode-escrow-redeem_2-2 316.6 μs 297.9 μs 1.06
validation-decode-escrow-redeem_2-3 314 μs 297.6 μs 1.06
validation-decode-pubkey-1 167.4 μs 157.1 μs 1.07
marlowe-semantics/eb4a605ed3a64961e9e66ad9631c2813dadf7131740212762ae4483ec749fe1d 283.9 μs 270.3 μs 1.05
marlowe-semantics/e3afd22d01ff12f381cf915fd32358634e6c413f979f2492cf3339319d8cc079 286.7 μs 271.2 μs 1.06
marlowe-semantics/dc241ac6ad1e04fb056d555d6a4f2d08a45d054c6f7f34355fcfeefebef479f3 434.9 μs 412.9 μs 1.05
marlowe-semantics/d64607eb8a1448595081547ea8780886fcbd9e06036460eea3705c88ea867e33 283.6 μs 270 μs 1.05
marlowe-semantics/cf542b7df466b228ca2197c2aaa89238a8122f3330fe5b77b3222f570395d9f5 445.7 μs 421.8 μs 1.06
marlowe-semantics/acce04815e8fd51be93322888250060da173eccf3df3a605bd6bc6a456cde871 285.6 μs 269.3 μs 1.06
marlowe-semantics/96e1a2fa3ceb9a402f2a5841a0b645f87b4e8e75beb636692478ec39f74ee221 286 μs 271.7 μs 1.05
marlowe-semantics/7529b206a78becb793da74b78c04d9d33a2540a1abd79718e681228f4057403a 761.7 μs 724.4 μs 1.05
marlowe-semantics/71965c9ccae31f1ffc1d85aa20a356d4ed97a420954018d8301ec4f9783be0d7 429.4 μs 406.3 μs 1.06
marlowe-semantics/5f3d46c57a56cef6764f96c9de9677ac6e494dd7a4e368d1c8dd9c1f7a4309a5 439.6 μs 417.4 μs 1.05
marlowe-semantics/5f130d19918807b60eab4c03119d67878fb6c6712c28c54f5a25792049294acc 287.1 μs 271.6 μs 1.06
marlowe-semantics/5d0a88250f13c49c20e146819357a808911c878a0e0a7d6f7fe1d4a619e06112 947.9 μs 899.2 μs 1.05
marlowe-semantics/52df7c8dfaa5f801cd837faa65f2fd333665fff00a555ce8c55e36ddc003007a 344.4 μs 324.9 μs 1.06
marlowe-semantics/44a9e339fa25948b48637fe7e10dcfc6d1256319a7b5ce4202cb54dfef8e37e7 283.8 μs 269.2 μs 1.05
marlowe-semantics/3bb75b2e53eb13f718eacd3263ab4535f9137fabffc9de499a0de7cabb335479 284 μs 269.4 μs 1.05
marlowe-semantics/1d6e3c137149a440f35e0efc685b16bfb8052ebcf66ec4ad77e51c11501381c7 286.2 μs 270.5 μs 1.06
marlowe-semantics/1a2f2540121f09321216090b2b1f211e3f020c2c133a1a3c3f3c232a26153a04 286.6 μs 270.7 μs 1.06
marlowe-semantics/0bcfd9487614104ec48de2ea0b2c0979866a95115748c026f9ec129384c262c4 975.6 μs 927.7 μs 1.05
marlowe-semantics/0705030002040601010206030604080208020207000101060706050502040301 1057 μs 1002.9999999999999 μs 1.05
marlowe-semantics/0543a00ba1f63076c1db6bf94c6ff13ae7d266dd7544678743890b0e8e1add63 948.1 μs 898.6 μs 1.06
marlowe-semantics/0101080808040600020306010000000302050807010208060100070207080202 743.5 μs 706.6 μs 1.05
marlowe-semantics/0000020002010200020101020201000100010001020101020201010000020102 301.7 μs 285.6 μs 1.06
marlowe-role-payout/ff38b1ec89952d0247630f107a90cbbeb92ecbfcd19b284f60255718e4ec7548 161.2 μs 151.3 μs 1.07
marlowe-role-payout/fc8c5f45ffcdb024c21e0f34b22c23de8045a94d5e1a5bda1555c45ddb059f82 138.1 μs 131.4 μs 1.05
marlowe-role-payout/f7275afb60e33a550df13a132102e7e925dd28965a4efbe510a89b077ff9417f 133 μs 125.3 μs 1.06
marlowe-role-payout/f2932e4ca4bbb94b0a9ffbe95fcb7bd5639d9751d75d56d5e14efa5bbed981df 131.2 μs 123.7 μs 1.06
marlowe-role-payout/f1a1e6a487f91feca5606f72bbb1e948c71abf043c6a0ea83bfea9ec6a0f08d8 132.8 μs 125.3 μs 1.06
marlowe-role-payout/eabeeae18131af89fa57936c0e9eb8d2c7adba534f7e1a517d75410028fa0d6c 133.2 μs 125.7 μs 1.06
marlowe-role-payout/df487b2fd5c1583fa33644423849bc1ab5f02f37edc0c235f34ef01cb12604f6 137.7 μs 129.2 μs 1.07
marlowe-role-payout/dc45c5f1b700b1334db99f50823321daaef0e6925b9b2fabbc9df7cde65af62e 138 μs 130.9 μs 1.05
marlowe-role-payout/da353bf9219801fa1bf703fc161497570954e9af7e10ffe95c911a9ef97e77bd 139.1 μs 132.4 μs 1.05
marlowe-role-payout/d5cda74eb0947e025e02fb8ed365df39d0a43e4b42cd3573ac2d8fcb29115997 152 μs 142.7 μs 1.07
marlowe-role-payout/cc1e82927f6c65b3e912200ae30588793d2066e1d4a6627c21955944ac9bd528 151.9 μs 143.7 μs 1.06
marlowe-role-payout/caa409c40e39aed9b0f59214b4baa178c375526dea6026b4552b88d2cc729716 131.9 μs 124.4 μs 1.06
marlowe-role-payout/c78eeba7681d2ab51b4758efa4c812cc041928837c6e7563d8283cce67ce2e02 143.8 μs 135.5 μs 1.06
marlowe-role-payout/c4d4c88c5fe378a25a034025994a0d0b1642f10c8e6e513f872327fa895bfc7e 140.9 μs 133.6 μs 1.05
marlowe-role-payout/c11490431db3a92efdda70933ba411a0423935e73a75c856e326dbcf6672f3bf 132 μs 125.1 μs 1.06
marlowe-role-payout/bd79f4a84db23b7c4cd219d498bd581e085cbc3437957e74a8862281a700700b 151.5 μs 143.7 μs 1.05
marlowe-role-payout/bcdbc576d63b0454100ad06893812edafc2e7e4934fec1b44e2d06eb34f36eb8 133.9 μs 125.6 μs 1.07
marlowe-role-payout/b869f3928200061abb1c3060425b9354b0e08cbf4400b340b8707c14b34317cd 193.2 μs 181.6 μs 1.06
marlowe-role-payout/b43564af5f13cc5208b92b1ad6d45369446f378d3891e5cb3e353b30d4f3fb10 133.2 μs 126 μs 1.06
marlowe-role-payout/a92b4072cb8601fa697e1150c08463b14ffced54eb963df08d322216e27373cb 133.1 μs 126.1 μs 1.06
marlowe-role-payout/a7cb09f417c3f089619fe25b7624392026382b458486129efcff18f8912bf302 132.8 μs 125.3 μs 1.06
marlowe-role-payout/a6f064b83b31032ea7f25921364727224707268e472a569f584cc6b1d8c017e8 132.6 μs 125.6 μs 1.06
marlowe-role-payout/a6664a2d2a82f370a34a36a45234f6b33120a39372331678a3b3690312560ce9 160.8 μs 151.3 μs 1.06
marlowe-role-payout/a27524cfad019df45e4e8316f927346d4cc39da6bdd294fb2c33c3f58e6a8994 133 μs 125.6 μs 1.06
marlowe-role-payout/a1b25347409c3993feca1a60b6fcaf93d1d4bbaae19ab06fdf50cedc26cee68d 129.3 μs 122 μs 1.06
marlowe-role-payout/a0fba5740174b5cd24036c8b008cb1efde73f1edae097b9325c6117a0ff40d3b 148.2 μs 141.1 μs 1.05
marlowe-role-payout/962c2c658b19904372984a56409707401e64e9b03c1986647134cfd329ec5139 143.7 μs 136 μs 1.06
marlowe-role-payout/8c0fa5d9d6724c5c72c67e055d4bfc36a385ded7c3c81c08cdbd8705829af6e6 160.2 μs 151.1 μs 1.06
marlowe-role-payout/87167fc5469adac97c1be749326fa79a6b7862ce68aa4abcb438e3c034bd0899 154 μs 144.4 μs 1.07
marlowe-role-payout/7b1dd76edc27f00eb382bf996378155baf74d6a7c6f3d5ec837c39d29784aade 133.5 μs 126.4 μs 1.06
marlowe-role-payout/73f044f34a30f26639c58bafe952047f74c7bf1eafebab5aadf5b73cfb9024ed 132.7 μs 125.3 μs 1.06
marlowe-role-payout/6d66bddb4269bdf77392d3894da5341cf019d39787522af4f83f01285991e93c 132.9 μs 125.7 μs 1.06
marlowe-role-payout/6c364699767a84059ffd99cf718562a8c09d96e343f23dc481e8ffda13af424f 132.6 μs 125.4 μs 1.06
marlowe-role-payout/6b7bc2b9002a71b33cfd535d43f26334a283d0b9ad189b7cd74baac232c3b9fc 131.7 μs 124.8 μs 1.06
marlowe-role-payout/674b0577409957172ad85223c765d17e94c27714276c49c38dfae0a47a561a1e 129.8 μs 123.5 μs 1.05
marlowe-role-payout/622a7f3bc611b5149253c9189da022a9ff296f60a5b7c172a6dc286faa7284fa 158.8 μs 148.8 μs 1.07
marlowe-role-payout/5ade103e9530dd0d572fe1b053ea65ad925c6ebbe321e873ace8b804363fa82c 184.3 μs 175.3 μs 1.05
marlowe-role-payout/5a2aae344e569a2c644dd9fa8c7b1f129850937eb562b7748c275f9e40bed596 133.2 μs 126.1 μs 1.06
marlowe-role-payout/4fbcfdb577a56b842d6f6938187a783f71d9da7519353e3da3ef0c564e1eb344 164.5 μs 156.2 μs 1.05
marlowe-role-payout/4dd7755b6ca1f0c9747c1fc0ee4da799f6f1c07108e980bd9f820911ad711ff2 171.1 μs 162.7 μs 1.05
marlowe-role-payout/49b8275d0cb817be40865694ab05e3cfe5fc35fb43b78e7de68c1f3519b536bd 138.7 μs 132 μs 1.05
marlowe-role-payout/47364cfaf2c00f7d633283dce6cf84e4fd4e8228c0a0aa50e7c55f35c3ecaa1c 133.4 μs 125.6 μs 1.06
marlowe-role-payout/46f8d00030436e4da490a86b331fa6c3251425fb8c19556080e124d75bad7bd6 132.7 μs 125.6 μs 1.06
marlowe-role-payout/452e17d16222a427707fa83f63ffb79f606cc25c755a18b1e3274c964ed5ec99 159.6 μs 150.5 μs 1.06
marlowe-role-payout/4299c7fcf093a5dbfe114c188e32ca199b571a7c25cb7f766bf49f12dab308be 142.9 μs 135.7 μs 1.05
marlowe-role-payout/371c10d2526fc0f09dbe9ed59e44dcd949270b27dc42035addd7ff9f7e0d05e7 153.6 μs 146 μs 1.05
marlowe-role-payout/36866914aa07cf62ef36cf2cd64c7f240e3371e27bb9fff5464301678e809c40 130.9 μs 124.1 μs 1.05
marlowe-role-payout/3569299fc986f5354d02e627a9eaa48ab46d5af52722307a0af72bae87e256dc 130.6 μs 123.7 μs 1.06
marlowe-role-payout/3565ee025317e065e8555eef288080276716366769aad89e03389f5ec4ce26d7 140.9 μs 133.4 μs 1.06
marlowe-role-payout/332c2b1c11383d1b373e1315201f1128010e0e1518332f273f141b23243f2a07 126.9 μs 119.9 μs 1.06
marlowe-role-payout/224ce46046fab9a17be4197622825f45cc0c59a6bd1604405148e43768c487ef 135.5 μs 128.3 μs 1.06
marlowe-role-payout/211e1b6c10260c4620074d2e372c260d38643a3d605f63772524034f0a4a7632 138 μs 131.2 μs 1.05
marlowe-role-payout/195f522b596360690d04586a2563470f2214163435331a6622311f7323433f1c 130.3 μs 122.8 μs 1.06
marlowe-role-payout/159e5a1bf16fe984b5569be7011b61b5e98f5d2839ca7e1b34c7f2afc7ffb58e 132.9 μs 125.9 μs 1.06
marlowe-role-payout/121a0a1b12030616111f02121a0e070716090a0e031c071419121f141409031d 134.3 μs 125.8 μs 1.07
marlowe-role-payout/1138a04a83edc0579053f9ffa9394b41df38230121fbecebee8c039776a88c0c 135.7 μs 128.5 μs 1.06
marlowe-role-payout/0e97c9d9417354d9460f2eb35018d3904b7b035af16ab299258adab93be0911a 143.2 μs 134.6 μs 1.06
marlowe-role-payout/0e72f62b0f922e31a2340baccc768104025400cf7fdd7dae62fbba5fc770936d 150.5 μs 140.1 μs 1.07
marlowe-role-payout/0dbb692d2bf22d25eeceac461cfebf616f54003077a8473abc0457f18e025960 156.8 μs 147.1 μs 1.07
marlowe-role-payout/0d0f01050a0a0a0b0b050d0404090e0d0506000d0a041003040e0f100e0a0408 140.4 μs 131.9 μs 1.06
marlowe-role-payout/07658a6c898ad6d624c37df1e49e909c2e9349ba7f4c0a6be5f166fe239bfcae 132.5 μs 124.8 μs 1.06
marlowe-role-payout/057ebc80922f16a5f4bf13e985bf586b8cff37a2f6fe0f3ce842178c16981027 131.2 μs 123.7 μs 1.06
marlowe-role-payout/04f592afc6e57c633b9c55246e7c82e87258f04e2fb910c37d8e2417e9db46e5 175.6 μs 166.4 μs 1.06
marlowe-role-payout/0403020000030204010000030001000202010101000304030001040404030100 143.7 μs 136 μs 1.06
marlowe-role-payout/03d730a62332c51c7b70c16c64da72dd1c3ea36c26b41cd1a1e00d39fda3d6cc 154.2 μs 145.3 μs 1.06
marlowe-role-payout/031d56d71454e2c4216ffaa275c4a8b3eb631109559d0e56f44ea8489f57ba97 160.5 μs 150.7 μs 1.07
marlowe-role-payout/0303020000020001010201060303040208070100050401080304020801030001 132.9 μs 126.2 μs 1.05
marlowe-role-payout/0201020201020000020000010201020001020200000002010200000101010100 142.9 μs 135.9 μs 1.05
marlowe-role-payout/01dcc372ea619cb9f23c45b17b9a0a8a16b7ca0e04093ef8ecce291667a99a4c 130.4 μs 121.8 μs 1.07
marlowe-role-payout/0004000402010401030101030100040000010104020201030001000204020401 142.7 μs 135.7 μs 1.05

This comment was automatically generated by workflow using github-action-benchmark.

CC: @input-output-hk/plutus-core

Please sign in to comment.