Skip to content

Commit cd615cb

Browse files
committed
refactor: consolidate Value size measurement types
Simplifies the memory usage measurement by consolidating three separate types (Logarithmic, ValueOuterOrMaxInner, LogValueOuterOrMaxInner) into a single ValueLogOuterOrMaxInner type. This reduces complexity while maintaining the same functionality for measuring logarithmic Value sizes. The new type directly encodes the intended semantics: size = log(max(outer, maxInner)), making the code more maintainable and producing clearer type signatures in builtin function definitions.
1 parent 77dbde8 commit cd615cb

File tree

6 files changed

+26
-53
lines changed

6 files changed

+26
-53
lines changed

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

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -13,7 +13,7 @@ import Criterion.Main (Benchmark)
1313
import Data.ByteString (ByteString)
1414
import Data.Int (Int64)
1515
import PlutusCore (DefaultFun (LookupCoin, UnValueData, ValueContains, ValueData))
16-
import PlutusCore.Evaluation.Machine.ExMemoryUsage (LogValueOuterOrMaxInner (..),
16+
import PlutusCore.Evaluation.Machine.ExMemoryUsage (ValueLogOuterOrMaxInner (..),
1717
ValueTotalSize (..))
1818
import PlutusCore.Value (K, Value)
1919
import PlutusCore.Value qualified as Value
@@ -36,7 +36,7 @@ makeBenchmarks gen =
3636
lookupCoinBenchmark :: StdGen -> Benchmark
3737
lookupCoinBenchmark gen =
3838
createThreeTermBuiltinBenchElementwiseWithWrappers
39-
(id, id, LogValueOuterOrMaxInner) -- Wrap Value argument to report outer/max inner size with log
39+
(id, id, ValueLogOuterOrMaxInner) -- Wrap Value argument to report outer/max inner size with log
4040
LookupCoin -- the builtin fun
4141
[] -- no type arguments needed (monomorphic builtin)
4242
(lookupCoinArgs gen) -- the argument combos to generate benchmarks for
@@ -73,7 +73,7 @@ withSearchKeys g genValue = do
7373
valueContainsBenchmark :: StdGen -> Benchmark
7474
valueContainsBenchmark gen =
7575
createTwoTermBuiltinBenchElementwiseWithWrappers
76-
(LogValueOuterOrMaxInner, ValueTotalSize)
76+
(ValueLogOuterOrMaxInner, ValueTotalSize)
7777
-- Container: outer/maxInner with log, Contained: totalSize
7878
ValueContains -- the builtin fun
7979
[] -- no type arguments needed (monomorphic builtin)

plutus-core/plutus-core/src/PlutusCore/Default/Builtins.hs

Lines changed: 5 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -24,8 +24,8 @@ import PlutusCore.Default.Universe
2424
import PlutusCore.Evaluation.Machine.BuiltinCostModel
2525
import PlutusCore.Evaluation.Machine.ExBudgetStream (ExBudgetStream)
2626
import PlutusCore.Evaluation.Machine.ExMemoryUsage (ExMemoryUsage, IntegerCostedLiterally (..),
27-
LogValueOuterOrMaxInner (..),
2827
NumBytesCostedAsNumWords (..),
28+
ValueLogOuterOrMaxInner (..),
2929
ValueTotalSize (..), memoryUsage, singletonRose)
3030
import PlutusCore.Pretty (PrettyConfigPlc)
3131
import PlutusCore.Value (Value)
@@ -2057,8 +2057,8 @@ instance uni ~ DefaultUni => ToBuiltinMeaning uni DefaultFun where
20572057
(runCostingFunFourArguments . unimplementedCostingFun)
20582058

20592059
toBuiltinMeaning _semvar LookupCoin =
2060-
let lookupCoinDenotation :: ByteString -> ByteString -> LogValueOuterOrMaxInner -> Integer
2061-
lookupCoinDenotation p t (LogValueOuterOrMaxInner v) = Value.lookupCoin p t v
2060+
let lookupCoinDenotation :: ByteString -> ByteString -> ValueLogOuterOrMaxInner -> Integer
2061+
lookupCoinDenotation p t (ValueLogOuterOrMaxInner v) = Value.lookupCoin p t v
20622062
{-# INLINE lookupCoinDenotation #-}
20632063
in makeBuiltinMeaning
20642064
lookupCoinDenotation
@@ -2073,8 +2073,8 @@ instance uni ~ DefaultUni => ToBuiltinMeaning uni DefaultFun where
20732073
(runCostingFunTwoArguments . unimplementedCostingFun)
20742074

20752075
toBuiltinMeaning _semvar ValueContains =
2076-
let valueContainsDenotation :: LogValueOuterOrMaxInner -> ValueTotalSize -> BuiltinResult Bool
2077-
valueContainsDenotation (LogValueOuterOrMaxInner v1) (ValueTotalSize v2) =
2076+
let valueContainsDenotation :: ValueLogOuterOrMaxInner -> ValueTotalSize -> BuiltinResult Bool
2077+
valueContainsDenotation (ValueLogOuterOrMaxInner v1) (ValueTotalSize v2) =
20782078
Value.valueContains v1 v2
20792079
{-# INLINE valueContainsDenotation #-}
20802080
in makeBuiltinMeaning

plutus-core/plutus-core/src/PlutusCore/Default/Universe.hs

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -52,8 +52,8 @@ import PlutusCore.Crypto.BLS12_381.G2 qualified as BLS12_381.G2
5252
import PlutusCore.Crypto.BLS12_381.Pairing qualified as BLS12_381.Pairing
5353
import PlutusCore.Data (Data)
5454
import PlutusCore.Evaluation.Machine.ExMemoryUsage (IntegerCostedLiterally (..),
55-
LogValueOuterOrMaxInner (..),
5655
NumBytesCostedAsNumWords (..),
56+
ValueLogOuterOrMaxInner (..),
5757
ValueTotalSize (..))
5858
import PlutusCore.Pretty.Extra (juxtRenderContext)
5959
import PlutusCore.Value (Value)
@@ -635,13 +635,13 @@ instance KnownBuiltinTypeIn DefaultUni term Value =>
635635
{-# INLINE readKnown #-}
636636

637637
deriving newtype instance
638-
KnownTypeAst tyname DefaultUni LogValueOuterOrMaxInner
638+
KnownTypeAst tyname DefaultUni ValueLogOuterOrMaxInner
639639
instance KnownBuiltinTypeIn DefaultUni term Value =>
640-
MakeKnownIn DefaultUni term LogValueOuterOrMaxInner where
640+
MakeKnownIn DefaultUni term ValueLogOuterOrMaxInner where
641641
makeKnown = makeKnownCoerce @Value
642642
{-# INLINE makeKnown #-}
643643
instance KnownBuiltinTypeIn DefaultUni term Value =>
644-
ReadKnownIn DefaultUni term LogValueOuterOrMaxInner where
644+
ReadKnownIn DefaultUni term ValueLogOuterOrMaxInner where
645645
readKnown = readKnownCoerce @Value
646646
{-# INLINE readKnown #-}
647647

plutus-core/plutus-core/src/PlutusCore/Evaluation/Machine/ExMemoryUsage.hs

Lines changed: 4 additions & 38 deletions
Original file line numberDiff line numberDiff line change
@@ -12,9 +12,7 @@ module PlutusCore.Evaluation.Machine.ExMemoryUsage
1212
, NumBytesCostedAsNumWords(..)
1313
, IntegerCostedLiterally(..)
1414
, ValueTotalSize(..)
15-
, ValueOuterOrMaxInner(..)
16-
, Logarithmic(..)
17-
, LogValueOuterOrMaxInner(..)
15+
, ValueLogOuterOrMaxInner(..)
1816
) where
1917

2018
import PlutusCore.Crypto.BLS12_381.G1 as BLS12_381.G1
@@ -380,38 +378,6 @@ newtype ValueTotalSize = ValueTotalSize { unValueTotalSize :: Value }
380378
instance ExMemoryUsage ValueTotalSize where
381379
memoryUsage = singletonRose . fromIntegral . Value.totalSize . unValueTotalSize
382380

383-
-- | Measure the size of a `Value` by taking the max of
384-
-- (size of the outer map, size of the largest inner map).
385-
newtype ValueOuterOrMaxInner = ValueOuterOrMaxInner { unValueOuterOrMaxInner :: Value }
386-
387-
instance ExMemoryUsage ValueOuterOrMaxInner where
388-
memoryUsage (ValueOuterOrMaxInner v) = singletonRose (fromIntegral size)
389-
where
390-
size = Map.size (Value.unpack v) `max` Value.maxInnerSize v
391-
392-
{-| A wrapper that applies a logarithmic transformation to another size measure.
393-
This is useful for modeling operations with logarithmic complexity, where the cost
394-
depends on log(n) where n is the size measure from the wrapped newtype.
395-
396-
For example, @Logarithmic ValueOuterOrMaxInner@ can be used to model operations
397-
that are O(log max(m, k)) where m is the number of policies and k is the max tokens
398-
per policy.
399-
400-
The memory usage is calculated as: @max 1 (floor (log2 size + 1))@ where size comes
401-
from the wrapped newtype's ExMemoryUsage instance.
402-
-}
403-
newtype Logarithmic n = Logarithmic { unLogarithmic :: n }
404-
405-
instance ExMemoryUsage n => ExMemoryUsage (Logarithmic n) where
406-
memoryUsage (Logarithmic wrapped) =
407-
case memoryUsage wrapped of
408-
CostRose size _ ->
409-
let sizeInteger :: Integer
410-
sizeInteger = fromSatInt size
411-
logSize = integerLog2 sizeInteger
412-
in singletonRose $ max 1 (fromIntegral (logSize + 1))
413-
{-# INLINE memoryUsage #-}
414-
415381
{-| A combined wrapper for Value that measures size using outer/max inner map sizes
416382
with logarithmic transformation. This is equivalent to @Logarithmic ValueOuterOrMaxInner@
417383
but defined as a single newtype for simpler type instances and better error messages.
@@ -422,10 +388,10 @@ O(log max(m, k)) where m is the number of policies and k is the max tokens per p
422388
If this is used to wrap an argument in the denotation of a builtin then it *MUST* also
423389
be used to wrap the same argument in the relevant budgeting benchmark.
424390
-}
425-
newtype LogValueOuterOrMaxInner = LogValueOuterOrMaxInner { unLogValueOuterOrMaxInner :: Value }
391+
newtype ValueLogOuterOrMaxInner = ValueLogOuterOrMaxInner { unLogValueOuterOrMaxInner :: Value }
426392

427-
instance ExMemoryUsage LogValueOuterOrMaxInner where
428-
memoryUsage (LogValueOuterOrMaxInner v) =
393+
instance ExMemoryUsage ValueLogOuterOrMaxInner where
394+
memoryUsage (ValueLogOuterOrMaxInner v) =
429395
let size = Map.size (Value.unpack v) `max` Value.maxInnerSize v
430396
logSize = integerLog2 (toInteger size)
431397
in singletonRose $ max 1 (fromIntegral (logSize + 1))

plutus-core/plutus-core/test/CostModelSafety/Spec.hs

Lines changed: 6 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -32,13 +32,15 @@ import PlutusCore.Crypto.BLS12_381.G1 qualified as BLS12_381.G1
3232
import PlutusCore.Crypto.BLS12_381.G2 qualified as BLS12_381.G2
3333
import PlutusCore.Crypto.BLS12_381.Pairing qualified as BLS12_381.Pairing
3434
import PlutusCore.Data (Data (..))
35+
import PlutusCore.Default ()
3536
import PlutusCore.Default.Builtins
3637
import PlutusCore.Evaluation.Machine.BuiltinCostModel (BuiltinCostModel)
3738
import PlutusCore.Evaluation.Machine.ExBudget (ExBudget (ExBudget))
3839
import PlutusCore.Evaluation.Machine.ExBudgetingDefaults (cekCostModelForVariant)
3940
import PlutusCore.Evaluation.Machine.ExBudgetStream (sumExBudgetStream)
4041
import PlutusCore.Evaluation.Machine.ExMemoryUsage (IntegerCostedLiterally,
41-
NumBytesCostedAsNumWords)
42+
NumBytesCostedAsNumWords,
43+
ValueLogOuterOrMaxInner, ValueTotalSize)
4244
import PlutusCore.Evaluation.Machine.MachineParameters (CostModel (..))
4345
import PlutusCore.Value (Value)
4446
import PlutusCore.Value qualified as Value
@@ -129,7 +131,9 @@ smallConstant tr
129131
| Just HRefl <- eqTypeRep tr (typeRep @BLS12_381.Pairing.MlResult) =
130132
SomeConst $ BLS12_381.Pairing.millerLoop
131133
BLS12_381.G1.offchain_zero BLS12_381.G2.offchain_zero
132-
| Just HRefl <- eqTypeRep tr (typeRep @Value) = SomeConst $ Value.empty
134+
| Just HRefl <- eqTypeRep tr (typeRep @Value) = SomeConst Value.empty
135+
| Just HRefl <- eqTypeRep tr (typeRep @ValueTotalSize) = SomeConst Value.empty
136+
| Just HRefl <- eqTypeRep tr (typeRep @ValueLogOuterOrMaxInner) = SomeConst Value.empty
133137
| trPair `App` tr1 `App` tr2 <- tr
134138
, Just HRefl <- eqTypeRep trPair (typeRep @(,)) =
135139
case (smallConstant tr1, smallConstant tr2) of

plutus-core/testlib/PlutusCore/Generators/Hedgehog/Builtin.hs

Lines changed: 4 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -19,7 +19,8 @@ import PlutusCore.Crypto.BLS12_381.G2 qualified as BLS12_381.G2
1919
import PlutusCore.Crypto.BLS12_381.Pairing qualified as BLS12_381.Pairing
2020
import PlutusCore.Data (Data (..))
2121
import PlutusCore.Evaluation.Machine.ExMemoryUsage (IntegerCostedLiterally,
22-
NumBytesCostedAsNumWords)
22+
NumBytesCostedAsNumWords,
23+
ValueLogOuterOrMaxInner, ValueTotalSize)
2324
import PlutusCore.Generators.Hedgehog.AST hiding (genConstant)
2425
import PlutusCore.Generators.QuickCheck.Builtin
2526
import PlutusCore.Value (Value)
@@ -109,6 +110,8 @@ genConstant tr
109110
| Just HRefl <- eqTypeRep tr (typeRep @BLS12_381.Pairing.MlResult) =
110111
genArbitraryBuiltin @BLS12_381.Pairing.MlResult
111112
| Just HRefl <- eqTypeRep tr (typeRep @Value) = genArbitraryBuiltin @Value
113+
| Just HRefl <- eqTypeRep tr (typeRep @ValueTotalSize) = genArbitraryBuiltin @Value
114+
| Just HRefl <- eqTypeRep tr (typeRep @ValueLogOuterOrMaxInner) = genArbitraryBuiltin @Value
112115
| trPair `App` tr1 `App` tr2 <- tr
113116
, Just HRefl <- eqTypeRep trPair (typeRep @(,)) =
114117
-- We can perhaps use the @QuickCheck@ generator here too, but this seems rather hard.

0 commit comments

Comments
 (0)