From bc446834fdff64f193c64b197540aceb46c4204d Mon Sep 17 00:00:00 2001 From: Yura Lazaryev Date: Wed, 24 Sep 2025 18:04:57 +0200 Subject: [PATCH 01/17] feat: add cost model infrastructure for Value builtins Extends the cost modeling framework to support lookupCoin, valueContains, valueData, and unValueData builtins. Adds parameter definitions, arity specifications, and integrates with the cost model generation system. Establishes foundation for accurate costing of Value operations in Plutus Core execution. --- .../create-cost-model/BuiltinMemoryModels.hs | 5 ++++ .../CreateBuiltinCostModel.hs | 10 +++++++ plutus-core/cost-model/data/models.R | 29 +++++++++++++++++-- plutus-core/plutus-core.cabal | 1 + .../Evaluation/Machine/BuiltinCostModel.hs | 5 ++++ .../Evaluation/Machine/ExBudgetingDefaults.hs | 5 ++++ 6 files changed, 53 insertions(+), 2 deletions(-) diff --git a/plutus-core/cost-model/create-cost-model/BuiltinMemoryModels.hs b/plutus-core/cost-model/create-cost-model/BuiltinMemoryModels.hs index 65e647d48f9..a138a9bbf1b 100644 --- a/plutus-core/cost-model/create-cost-model/BuiltinMemoryModels.hs +++ b/plutus-core/cost-model/create-cost-model/BuiltinMemoryModels.hs @@ -176,5 +176,10 @@ builtinMemoryModels = BuiltinCostModelBase , paramLengthOfArray = Id $ ModelOneArgumentConstantCost 10 , paramListToArray = Id $ ModelOneArgumentLinearInX $ OneVariableLinearFunction 7 1 , paramIndexArray = Id $ ModelTwoArgumentsConstantCost 32 + -- Builtin values + , paramLookupCoin = Id $ ModelThreeArgumentsConstantCost 1 + , paramValueContains = Id $ ModelTwoArgumentsConstantCost 1 + , paramValueData = Id $ ModelOneArgumentConstantCost 1 + , paramUnValueData = Id $ ModelOneArgumentConstantCost 1 } where identityFunction = OneVariableLinearFunction 0 1 diff --git a/plutus-core/cost-model/create-cost-model/CreateBuiltinCostModel.hs b/plutus-core/cost-model/create-cost-model/CreateBuiltinCostModel.hs index 889d43da60a..9d138865dde 100644 --- a/plutus-core/cost-model/create-cost-model/CreateBuiltinCostModel.hs +++ b/plutus-core/cost-model/create-cost-model/CreateBuiltinCostModel.hs @@ -131,6 +131,11 @@ builtinCostModelNames = BuiltinCostModelBase , paramLengthOfArray = "lengthOfArrayModel" , paramListToArray = "listToArrayModel" , paramIndexArray = "indexArrayModel" + -- Builtin values + , paramLookupCoin = "lookupCoinModel" + , paramValueContains = "valueContainsModel" + , paramValueData = "valueDataModel" + , paramUnValueData = "unValueDataModel" } @@ -279,6 +284,11 @@ createBuiltinCostModel bmfile rfile = do paramLengthOfArray <- getParams readCF1 paramLengthOfArray paramListToArray <- getParams readCF1 paramListToArray paramIndexArray <- getParams readCF2 paramIndexArray + -- Builtin values + paramLookupCoin <- getParams readCF3 paramLookupCoin + paramValueContains <- getParams readCF2 paramValueContains + paramValueData <- getParams readCF1 paramValueData + paramUnValueData <- getParams readCF1 paramUnValueData pure $ BuiltinCostModelBase {..} diff --git a/plutus-core/cost-model/data/models.R b/plutus-core/cost-model/data/models.R index 974d83d64a4..802a2db11b1 100644 --- a/plutus-core/cost-model/data/models.R +++ b/plutus-core/cost-model/data/models.R @@ -152,6 +152,10 @@ arity <- function(name) { "LengthOfArray" = 1, "ListToArray" = 1, "IndexArray" = 2, + "LookupCoin" = 3, + "ValueContains" = 2, + "ValueData" = 1, + "UnValueData" = 1, -1 ## Default for missing values ) } @@ -804,11 +808,28 @@ modelFun <- function(path) { dropListModel <- linearInX ("DropList") - ## Arrays + ## Arrays lengthOfArrayModel <- constantModel ("LengthOfArray") listToArrayModel <- linearInX ("ListToArray") indexArrayModel <- constantModel ("IndexArray") + ## Values + lookupCoinModel <- linearInZ ("LookupCoin") + + ## ValueContains is O(n₂ × log max(m₁, k₁)) where n₂ is the total size of the second Value + ## We model this as linear in the sum of sizes, which is conservative + valueContainsModel <- { + fname <- "ValueContains" + filtered <- data %>% + filter.and.check.nonempty(fname) %>% + discard.upper.outliers() + m <- lm(t ~ I(x_mem + y_mem), filtered) + mk.result(m, "added_sizes") + } + + valueDataModel <- constantModel ("ValueData") + unValueDataModel <- linearInX ("UnValueData") + ##### Models to be returned to Haskell ##### models.for.adjustment <- @@ -902,7 +923,11 @@ modelFun <- function(path) { dropListModel = dropListModel, lengthOfArrayModel = lengthOfArrayModel, listToArrayModel = listToArrayModel, - indexArrayModel = indexArrayModel + indexArrayModel = indexArrayModel, + lookupCoinModel = lookupCoinModel, + valueContainsModel = valueContainsModel, + valueDataModel = valueDataModel, + unValueDataModel = unValueDataModel ) ## The integer division functions have a complex costing behaviour that requires some negative diff --git a/plutus-core/plutus-core.cabal b/plutus-core/plutus-core.cabal index 412c942303c..3a0e48cb017 100644 --- a/plutus-core/plutus-core.cabal +++ b/plutus-core/plutus-core.cabal @@ -935,6 +935,7 @@ executable cost-model-budgeting-bench Benchmarks.Strings Benchmarks.Tracing Benchmarks.Unit + Benchmarks.Values Common CriterionExtensions Generators diff --git a/plutus-core/plutus-core/src/PlutusCore/Evaluation/Machine/BuiltinCostModel.hs b/plutus-core/plutus-core/src/PlutusCore/Evaluation/Machine/BuiltinCostModel.hs index 9cb77e0bb64..35ff0ee0e74 100644 --- a/plutus-core/plutus-core/src/PlutusCore/Evaluation/Machine/BuiltinCostModel.hs +++ b/plutus-core/plutus-core/src/PlutusCore/Evaluation/Machine/BuiltinCostModel.hs @@ -193,6 +193,11 @@ data BuiltinCostModelBase f = , paramLengthOfArray :: f ModelOneArgument , paramListToArray :: f ModelOneArgument , paramIndexArray :: f ModelTwoArguments + -- Builtin values + , paramLookupCoin :: f ModelThreeArguments + , paramValueContains :: f ModelTwoArguments + , paramValueData :: f ModelOneArgument + , paramUnValueData :: f ModelOneArgument } deriving stock (Generic) deriving anyclass (FunctorB, TraversableB, ConstraintsB) diff --git a/plutus-core/plutus-core/src/PlutusCore/Evaluation/Machine/ExBudgetingDefaults.hs b/plutus-core/plutus-core/src/PlutusCore/Evaluation/Machine/ExBudgetingDefaults.hs index b70266cb250..a5a1a2e97c9 100644 --- a/plutus-core/plutus-core/src/PlutusCore/Evaluation/Machine/ExBudgetingDefaults.hs +++ b/plutus-core/plutus-core/src/PlutusCore/Evaluation/Machine/ExBudgetingDefaults.hs @@ -355,6 +355,11 @@ unitCostBuiltinCostModel = BuiltinCostModelBase , paramLengthOfArray = unitCostOneArgument , paramListToArray = unitCostOneArgument , paramIndexArray = unitCostTwoArguments + -- Builtin values + , paramLookupCoin = unitCostThreeArguments + , paramValueContains = unitCostTwoArguments + , paramValueData = unitCostOneArgument + , paramUnValueData = unitCostOneArgument } unitCekParameters :: Typeable ann => MachineParameters CekMachineCosts DefaultFun (CekValue DefaultUni DefaultFun ann) From 7e68def0816645a0ac7f6e0b74490e07ae7e86fe Mon Sep 17 00:00:00 2001 From: Yura Lazaryev Date: Wed, 24 Sep 2025 18:05:07 +0200 Subject: [PATCH 02/17] feat: implement comprehensive Value benchmarking framework Creates Values.hs benchmark module with systematic test generation for lookupCoin, valueContains, valueData, and unValueData operations. Includes value generation utilities, individual benchmark functions, and edge case testing with empty values. Enables data collection for accurate cost model parameter fitting. --- .../budgeting-bench/Benchmarks/Values.hs | 399 ++++++++++++++++++ .../cost-model/budgeting-bench/Main.hs | 2 + 2 files changed, 401 insertions(+) create mode 100644 plutus-core/cost-model/budgeting-bench/Benchmarks/Values.hs diff --git a/plutus-core/cost-model/budgeting-bench/Benchmarks/Values.hs b/plutus-core/cost-model/budgeting-bench/Benchmarks/Values.hs new file mode 100644 index 00000000000..ad1b8e56fbc --- /dev/null +++ b/plutus-core/cost-model/budgeting-bench/Benchmarks/Values.hs @@ -0,0 +1,399 @@ +{-# LANGUAGE BlockArguments #-} +{-# LANGUAGE ImportQualifiedPost #-} +{-# LANGUAGE NumericUnderscores #-} + +module Benchmarks.Values (makeBenchmarks) where + +import Prelude + +import Common +import Control.Monad (replicateM) +import Control.Monad.State.Strict (State) +import Criterion.Main (Benchmark) +import Data.ByteString (ByteString) +import Data.ByteString qualified as BS +import PlutusCore (DefaultFun (LookupCoin, UnValueData, ValueContains, ValueData)) +import PlutusCore.Evaluation.Machine.ExMemoryUsage (ValueOuterOrMaxInner (..), ValueTotalSize (..)) +import PlutusCore.Value (Value) +import PlutusCore.Value qualified as Value +import System.Random.Stateful (StatefulGen, StdGen, runStateGen_, uniformByteStringM, uniformRM) + +---------------------------------------------------------------------------------------------------- +-- Benchmarks -------------------------------------------------------------------------------------- + +makeBenchmarks :: StdGen -> [Benchmark] +makeBenchmarks gen = + [ lookupCoinBenchmark gen + , valueContainsBenchmark gen + , valueDataBenchmark gen + , unValueDataBenchmark gen + ] + +---------------------------------------------------------------------------------------------------- +-- LookupCoin -------------------------------------------------------------------------------------- + +lookupCoinBenchmark :: StdGen -> Benchmark +lookupCoinBenchmark gen = + createThreeTermBuiltinBenchElementwiseWithWrappers + (id, id, ValueOuterOrMaxInner) -- Wrap Value argument to report outer/max inner size + LookupCoin -- the builtin fun + [] -- no type arguments needed (monomorphic builtin) + (lookupCoinArgs gen) -- the argument combos to generate benchmarks for + +lookupCoinArgs :: StdGen -> [(ByteString, ByteString, Value)] +lookupCoinArgs gen = runStateGen_ gen $ \(g :: g) -> do + let + -- Use common test values and add search keys + testValues = generateTestValues gen + + -- Also include additional random tests specific to lookupCoin + additionalTests = runStateGen_ gen $ \g' -> do + let keySizes = [0, 1, 30, 100, 1_000, 10_000, 20_000] + sequence $ + concat + [ -- Key size impact tests with large keys + [ generateLookupTest g' policySize tokenSize 100 10 + | policySize <- keySizes + , tokenSize <- [0, 30, 1_000, 20_000] + ] + , -- Budget-constrained tests (at 30KB limit) + [ generateBudgetTest g' policySize tokenSize 30_000 + | (policySize, tokenSize) <- + [ (20_000, 1) -- Huge policy, tiny token + , (1, 20_000) -- Tiny policy, huge token + , (10_000, 10_000) -- Both large + , (1, 1) -- Both tiny (max entries) + , (0, 0) -- Empty keys (pathological) + ] + ] + , -- Additional random tests for parameter spread + replicate 50 (generateRandomLookupTest g') + ] + + -- Add search keys to common test values + + -- Add search keys to a value for lookup testing + -- Generates random keys that may or may not exist in the value + addSearchKeysToValue :: Value -> State StdGen (ByteString, ByteString, Value) + addSearchKeysToValue value = do + -- Generate search keys with varying sizes (mostly 30 bytes for consistency) + let keySize = 30 -- Standard key size used in most tests + searchPolicyId <- generatePolicyId keySize g + searchTokenName <- generateTokenName keySize g + pure (searchPolicyId, searchTokenName, value) + + commonWithKeys <- sequence [addSearchKeysToValue value | value <- testValues] + + pure $ commonWithKeys ++ additionalTests + +-- | Generate lookup test with specified parameters +generateLookupTest + :: (StatefulGen g m) + => g + -> Int -- Policy ID byte size + -> Int -- Token name byte size + -> Int -- Number of policies + -> Int -- Tokens per policy + -> m (ByteString, ByteString, Value) +generateLookupTest + g + policyIdBytes + tokenNameBytes + numPolicies + tokensPerPolicy = do + value <- + generateConstrainedValue + numPolicies + tokensPerPolicy + policyIdBytes + tokenNameBytes + g + -- Generate lookup keys (may or may not exist in value) + searchPolicyId <- generatePolicyId policyIdBytes g + searchTokenName <- generateTokenName tokenNameBytes g + pure (searchPolicyId, searchTokenName, value) + +-- | Generate budget-constrained test +generateBudgetTest + :: (StatefulGen g m) + => g + -> Int -- Policy ID byte size + -> Int -- Token name byte size + -> Int -- Total budget + -> m (ByteString, ByteString, Value) +generateBudgetTest g policyIdBytes tokenNameBytes budget = do + value <- generateValueWithBudget policyIdBytes tokenNameBytes budget g + searchPolicyId <- generatePolicyId policyIdBytes g + searchTokenName <- generateTokenName tokenNameBytes g + pure (searchPolicyId, searchTokenName, value) + +-- | Generate random lookup test with varied parameters for better spread +generateRandomLookupTest :: (StatefulGen g m) => g -> m (ByteString, ByteString, Value) +generateRandomLookupTest g = do + policyIdBytes <- uniformRM (0, 20_000) g -- 0-20KB policy ID + tokenNameBytes <- uniformRM (0, 20_000) g -- 0-20KB token name + numPolicies <- uniformRM (1, 2_000) g -- 1-2000 policies + tokensPerPolicy <- uniformRM (1, 1_000) g -- 1-1000 tokens per policy + + -- Generate value with random parameters + value <- generateConstrainedValue numPolicies tokensPerPolicy policyIdBytes tokenNameBytes g + + -- Generate search keys + searchPolicyId <- uniformByteStringM policyIdBytes g + searchTokenName <- uniformByteStringM tokenNameBytes g + + pure (searchPolicyId, searchTokenName, value) + +---------------------------------------------------------------------------------------------------- +-- ValueContains ----------------------------------------------------------------------------------- + +valueContainsBenchmark :: StdGen -> Benchmark +valueContainsBenchmark gen = + createTwoTermBuiltinBenchElementwiseWithWrappers + (ValueOuterOrMaxInner, ValueTotalSize) + -- Container: outer/maxInner, Contained: totalSize + ValueContains -- the builtin fun + [] -- no type arguments needed (monomorphic builtin) + (valueContainsArgs gen) -- the argument combos to generate benchmarks for + +valueContainsArgs :: StdGen -> [(Value, Value)] +valueContainsArgs gen = runStateGen_ gen \g -> do + let + baseKeySizes = [0, 30, 1_000, 10_000] + baseValueSizes = [1, 10, 100, 1_000] + + sequence $ + concat + [ -- Standard key tests with varying value sizes (original Size-based tests) + [ generateContainsTest g containerSize containedSize 30 + | containerSize <- baseValueSizes + , containedSize <- baseValueSizes + , containedSize <= containerSize + ] + , -- Key size impact tests + [ generateContainsTest g 100 10 keySize + | keySize <- baseKeySizes + ] + , -- Budget-constrained tests + [ generateContainsBudgetTest g 30_000 keySize + | keySize <- [0, 30, 3_000, 20_000] + ] + , -- Edge cases + [ generateEmptyContainedTest g containerSize 30 + | containerSize <- [0, 10, 100, 1_000] + ] + , -- Random tests for parameter spread (100 combinations) + replicate 100 (generateRandomContainsTest g) + ] + +-- | Generate valueContains test with specified parameters +generateContainsTest + :: (StatefulGen g m) + => g + -> Int -- Container value size + -> Int -- Contained value size + -> Int -- Key byte size (for both policy and token) + -> m (Value, Value) +generateContainsTest g containerSize containedSize keySize = do + -- Generate container value + container <- generateConstrainedValue containerSize 10 keySize keySize g + + -- Generate contained as subset of container (for true contains relationship) + let containerList = Value.toList container + containedEntries = take containedSize containerList + + let contained = + Value.fromList $ + [ (policyId, take (containedSize `div` max 1 (length containerList)) tokens) + | (policyId, tokens) <- containedEntries + ] + + pure (container, contained) + +-- | Generate budget-constrained contains test +generateContainsBudgetTest + :: (StatefulGen g m) + => g + -> Int -- Total budget + -> Int -- Key size + -> m (Value, Value) +generateContainsBudgetTest g budget keySize = do + container <- generateValueWithBudget keySize keySize budget g + -- Generate smaller contained value (subset) + let containerList = Value.toList container + containedEntries = take (length containerList `div` 2) containerList + pure (container, Value.fromList containedEntries) + +-- | Generate test with empty contained value +generateEmptyContainedTest + :: (StatefulGen g m) + => g + -> Int -- Container size + -> Int -- Key size + -> m (Value, Value) +generateEmptyContainedTest g containerSize keySize = do + container <- generateConstrainedValue containerSize 10 keySize keySize g + pure (container, Value.empty) + +-- | Generate random valueContains test with varied parameters for better spread +generateRandomContainsTest :: (StatefulGen g m) => g -> m (Value, Value) +generateRandomContainsTest g = do + -- Generate random parameters with good spread + containerEntries <- uniformRM (1, 5_000) g -- 1-5000 container entries + containedEntries <- uniformRM (1, containerEntries) g -- 1-container count + keyBytes <- uniformRM (1, 5_000) g -- 1-5000 byte keys + + -- Generate container value with exact entry count + container <- generateRandomValueForContains containerEntries keyBytes g + + -- Generate contained as subset of container entries + let containerList = Value.toList container + containedList = take containedEntries containerList + contained = Value.fromList containedList + + pure (container, contained) + +-- | Generate Value for contains tests with exact entry count +generateRandomValueForContains + :: (StatefulGen g m) + => Int -- Entry count + -> Int -- Key byte size + -> g + -> m Value +generateRandomValueForContains entryCount keyBytes g = do + -- Generate policies and tokens with exact entry count + policyIds <- replicateM entryCount (uniformByteStringM keyBytes g) + tokenNames <- replicateM entryCount (uniformByteStringM keyBytes g) + + let + -- Create amounts (1 to 1000000) + amounts = [fromIntegral (1 + i `mod` 1_000_000) | i <- [0 .. entryCount - 1]] + + pure $ + Value.fromList + [ (policy, [(token, amount)]) + | (policy, token, amount) <- zip3 policyIds tokenNames amounts + ] + +---------------------------------------------------------------------------------------------------- +-- ValueData --------------------------------------------------------------------------------------- + +valueDataBenchmark :: StdGen -> Benchmark +valueDataBenchmark gen = createOneTermBuiltinBench ValueData [] (generateTestValues gen) + +---------------------------------------------------------------------------------------------------- +-- UnValueData ------------------------------------------------------------------------------------- + +unValueDataBenchmark :: StdGen -> Benchmark +unValueDataBenchmark gen = + createOneTermBuiltinBench UnValueData [] (Value.valueData <$> generateTestValues gen) + +---------------------------------------------------------------------------------------------------- +-- Value Generators -------------------------------------------------------------------------------- + +-- | Generate common test values for benchmarking +generateTestValues :: StdGen -> [Value] +generateTestValues gen = runStateGen_ gen \g -> do + let + baseValueSizes = [1, 10, 50, 100, 500, 1_000] + keySizes = [0, 30, 100, 1_000, 10_000] + + sequence $ + concat + [ -- Empty value as edge case (first test cbase) + [pure Value.empty] + , -- Standard value sizes with varying key sizes + [ generateConstrainedValue valueSize 10 keySize keySize g + | valueSize <- baseValueSizes + , keySize <- [30, 1_000] + ] + , -- Key size impact tests (fixed value structure, varying key sizes) + [ generateConstrainedValue 100 10 keySize keySize g + | keySize <- keySizes + ] + , -- Budget-constrained tests + [ generateValueWithBudget keySize keySize budget g + | keySize <- [0, 30, 1_000, 10_000] + , budget <- [1_000, 10_000, 30_000] + ] + , -- Random tests for parameter spread (50 combinations) + replicate 50 $ do + numPolicies <- uniformRM (1, 1_000) g + tokensPerPolicy <- uniformRM (1, 500) g + policyIdBytes <- uniformRM (0, 10_000) g + tokenNameBytes <- uniformRM (0, 10_000) g + generateConstrainedValue numPolicies tokensPerPolicy policyIdBytes tokenNameBytes g + ] + +-- | Generate constrained Value with total size budget +generateConstrainedValue + :: (StatefulGen g m) + => Int -- Number of policies + -> Int -- Number of tokens per policy + -> Int -- Policy ID byte length + -> Int -- Token name byte length + -> g + -> m Value +generateConstrainedValue numPolicies tokensPerPolicy policyIdBytes tokenNameBytes g = do + policyIds <- -- Generate policy IDs of specified size + replicateM numPolicies (generatePolicyId policyIdBytes g) + + tokenNames <- -- Generate token names of specified size + replicateM tokensPerPolicy (generateTokenName tokenNameBytes g) + + -- Generate positive quantities (1 to 1000000) + let quantity :: Int -> Int -> Integer + quantity policyIndex tokenIndex = + fromIntegral (1 + (policyIndex * 1_000 + tokenIndex) `mod` 1_000_000) + + nestedMap :: [(ByteString, [(ByteString, Integer)])] + nestedMap = + [ ( policyId + , [ (tokenName, quantity policyIndex tokenIndex) + | (tokenIndex, tokenName) <- zip [0 ..] tokenNames + ] + ) + | (policyIndex, policyId) <- zip [0 ..] policyIds + ] + pure $ Value.fromList nestedMap + +-- | Generate Value within total size budget +generateValueWithBudget + :: (StatefulGen g m) + => Int -- Policy ID byte length + -> Int -- Token name byte length + -> Int -- Target total size budget + -> g + -> m Value +generateValueWithBudget policyIdBytes tokenNameBytes budget g = do + let + overhead = 8 -- bytes per amount + + -- Calculate maximum possible entries + bytesPerEntry = policyIdBytes + tokenNameBytes + overhead + maxEntries = + if bytesPerEntry > 0 + then min (budget `div` bytesPerEntry) budget + else budget -- Handle 0 case + + -- Simple distribution: try to balance policies and tokens + numPolicies = max 1 (floor (sqrt (fromIntegral maxEntries :: Double))) + tokensPerPolicy = if numPolicies > 0 then maxEntries `div` numPolicies else 0 + + generateConstrainedValue numPolicies tokensPerPolicy policyIdBytes tokenNameBytes g + +---------------------------------------------------------------------------------------------------- +-- Other Generators -------------------------------------------------------------------------------- + +-- | Generate policy ID of specified size +generatePolicyId :: (StatefulGen g m) => Int -> g -> m ByteString +generatePolicyId = generateByteString + +-- | Generate token name of specified size +generateTokenName :: (StatefulGen g m) => Int -> g -> m ByteString +generateTokenName = generateByteString + +-- | Generate ByteString of specified size +generateByteString :: (StatefulGen g m) => Int -> g -> m ByteString +generateByteString 0 _ = pure BS.empty +generateByteString l g = uniformByteStringM l g diff --git a/plutus-core/cost-model/budgeting-bench/Main.hs b/plutus-core/cost-model/budgeting-bench/Main.hs index 51be377f0e8..6c9124f4a38 100644 --- a/plutus-core/cost-model/budgeting-bench/Main.hs +++ b/plutus-core/cost-model/budgeting-bench/Main.hs @@ -17,6 +17,7 @@ import Benchmarks.Pairs qualified import Benchmarks.Strings qualified import Benchmarks.Tracing qualified import Benchmarks.Unit qualified +import Benchmarks.Values qualified import Criterion.Main import Criterion.Types as C @@ -60,6 +61,7 @@ main = do <> Benchmarks.Strings.makeBenchmarks gen <> Benchmarks.Tracing.makeBenchmarks gen <> Benchmarks.Unit.makeBenchmarks gen + <> Benchmarks.Values.makeBenchmarks gen {- Run the nop benchmarks with a large time limit (30 seconds) in an attempt to get accurate results. -} From 8171bf61ae39174f58899b94aabc1b068de0f725 Mon Sep 17 00:00:00 2001 From: Yura Lazaryev Date: Wed, 24 Sep 2025 18:05:17 +0200 Subject: [PATCH 03/17] feat: add statistical models and cost parameters for Value builtins Implements optimal statistical models for Value operations based on performance characteristics: linear models for lookupCoin and valueContains (size-dependent), constant model for valueData (uniform performance), and linear model for unValueData. Provides accurate cost parameters across all builtin cost model configurations and updates test expectations. --- .../cost-model/data/builtinCostModelA.json | 2461 +++++++++-------- .../cost-model/data/builtinCostModelB.json | 49 + .../cost-model/data/builtinCostModelC.json | 49 + plutus-core/cost-model/test/TestCostModels.hs | 6 + 4 files changed, 1359 insertions(+), 1206 deletions(-) diff --git a/plutus-core/cost-model/data/builtinCostModelA.json b/plutus-core/cost-model/data/builtinCostModelA.json index d1c4baf684c..c49ff540ad2 100644 --- a/plutus-core/cost-model/data/builtinCostModelA.json +++ b/plutus-core/cost-model/data/builtinCostModelA.json @@ -1,1209 +1,1258 @@ { - "addInteger": { - "cpu": { - "arguments": { - "intercept": 205665, - "slope": 812 - }, - "type": "max_size" - }, - "memory": { - "arguments": { - "intercept": 1, - "slope": 1 - }, - "type": "max_size" - } - }, - "appendByteString": { - "cpu": { - "arguments": { - "intercept": 1000, - "slope": 571 - }, - "type": "added_sizes" - }, - "memory": { - "arguments": { - "intercept": 0, - "slope": 1 - }, - "type": "added_sizes" - } - }, - "appendString": { - "cpu": { - "arguments": { - "intercept": 1000, - "slope": 24177 - }, - "type": "added_sizes" - }, - "memory": { - "arguments": { - "intercept": 4, - "slope": 1 - }, - "type": "added_sizes" - } - }, - "bData": { - "cpu": { - "arguments": 1000, - "type": "constant_cost" - }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } - }, - "blake2b_224": { - "cpu": { - "arguments": { - "intercept": 207616, - "slope": 8310 - }, - "type": "linear_in_x" - }, - "memory": { - "arguments": 4, - "type": "constant_cost" - } - }, - "blake2b_256": { - "cpu": { - "arguments": { - "intercept": 117366, - "slope": 10475 - }, - "type": "linear_in_x" - }, - "memory": { - "arguments": 4, - "type": "constant_cost" - } - }, - "bls12_381_G1_add": { - "cpu": { - "arguments": 962335, - "type": "constant_cost" - }, - "memory": { - "arguments": 18, - "type": "constant_cost" - } - }, - "bls12_381_G1_compress": { - "cpu": { - "arguments": 2780678, - "type": "constant_cost" - }, - "memory": { - "arguments": 6, - "type": "constant_cost" - } - }, - "bls12_381_G1_equal": { - "cpu": { - "arguments": 442008, - "type": "constant_cost" - }, - "memory": { - "arguments": 1, - "type": "constant_cost" - } - }, - "bls12_381_G1_hashToGroup": { - "cpu": { - "arguments": { - "intercept": 52538055, - "slope": 3756 - }, - "type": "linear_in_x" - }, - "memory": { - "arguments": 18, - "type": "constant_cost" - } - }, - "bls12_381_G1_neg": { - "cpu": { - "arguments": 267929, - "type": "constant_cost" - }, - "memory": { - "arguments": 18, - "type": "constant_cost" - } - }, - "bls12_381_G1_scalarMul": { - "cpu": { - "arguments": { - "intercept": 76433006, - "slope": 8868 - }, - "type": "linear_in_x" - }, - "memory": { - "arguments": 18, - "type": "constant_cost" - } - }, - "bls12_381_G1_multiScalarMul": { - "cpu": { - "arguments": { - "intercept": 321837444, - "slope": 25087669 - }, - "type": "linear_in_x" - }, - "memory": { - "arguments": 18, - "type": "constant_cost" - } - }, - "bls12_381_G1_uncompress": { - "cpu": { - "arguments": 52948122, - "type": "constant_cost" - }, - "memory": { - "arguments": 18, - "type": "constant_cost" - } - }, - "bls12_381_G2_add": { - "cpu": { - "arguments": 1995836, - "type": "constant_cost" - }, - "memory": { - "arguments": 36, - "type": "constant_cost" - } - }, - "bls12_381_G2_compress": { - "cpu": { - "arguments": 3227919, - "type": "constant_cost" - }, - "memory": { - "arguments": 12, - "type": "constant_cost" - } - }, - "bls12_381_G2_equal": { - "cpu": { - "arguments": 901022, - "type": "constant_cost" - }, - "memory": { - "arguments": 1, - "type": "constant_cost" - } - }, - "bls12_381_G2_hashToGroup": { - "cpu": { - "arguments": { - "intercept": 166917843, - "slope": 4307 - }, - "type": "linear_in_x" - }, - "memory": { - "arguments": 36, - "type": "constant_cost" - } - }, - "bls12_381_G2_neg": { - "cpu": { - "arguments": 284546, - "type": "constant_cost" - }, - "memory": { - "arguments": 36, - "type": "constant_cost" - } - }, - "bls12_381_G2_scalarMul": { - "cpu": { - "arguments": { - "intercept": 158221314, - "slope": 26549 - }, - "type": "linear_in_x" - }, - "memory": { - "arguments": 36, - "type": "constant_cost" - } - }, - "bls12_381_G2_multiScalarMul": { - "cpu": { - "arguments": { - "intercept": 617887431, - "slope": 67302824 - }, - "type": "linear_in_x" - }, - "memory": { - "arguments": 36, - "type": "constant_cost" - } - }, - "bls12_381_G2_uncompress": { - "cpu": { - "arguments": 74698472, - "type": "constant_cost" - }, - "memory": { - "arguments": 36, - "type": "constant_cost" - } - }, - "bls12_381_finalVerify": { - "cpu": { - "arguments": 333849714, - "type": "constant_cost" - }, - "memory": { - "arguments": 1, - "type": "constant_cost" - } - }, - "bls12_381_millerLoop": { - "cpu": { - "arguments": 254006273, - "type": "constant_cost" - }, - "memory": { - "arguments": 72, - "type": "constant_cost" - } - }, - "bls12_381_mulMlResult": { - "cpu": { - "arguments": 2174038, - "type": "constant_cost" - }, - "memory": { - "arguments": 72, - "type": "constant_cost" - } - }, - "byteStringToInteger": { - "cpu": { - "arguments": { - "c0": 1006041, - "c1": 43623, - "c2": 251 - }, - "type": "quadratic_in_y" - }, - "memory": { - "arguments": { - "intercept": 0, - "slope": 1 - }, - "type": "linear_in_y" - } - }, - "chooseData": { - "cpu": { - "arguments": 19537, - "type": "constant_cost" - }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } - }, - "chooseList": { - "cpu": { - "arguments": 175354, - "type": "constant_cost" - }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } - }, - "chooseUnit": { - "cpu": { - "arguments": 46417, - "type": "constant_cost" - }, - "memory": { - "arguments": 4, - "type": "constant_cost" - } - }, - "consByteString": { - "cpu": { - "arguments": { - "intercept": 221973, - "slope": 511 - }, - "type": "linear_in_y" - }, - "memory": { - "arguments": { - "intercept": 0, - "slope": 1 - }, - "type": "added_sizes" - } - }, - "constrData": { - "cpu": { - "arguments": 89141, - "type": "constant_cost" - }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } - }, - "decodeUtf8": { - "cpu": { - "arguments": { - "intercept": 497525, - "slope": 14068 - }, - "type": "linear_in_x" - }, - "memory": { - "arguments": { - "intercept": 4, - "slope": 2 - }, - "type": "linear_in_x" - } - }, - "divideInteger": { - "cpu": { - "arguments": { - "constant": 196500, - "model": { - "arguments": { - "intercept": 453240, - "slope": 220 - }, - "type": "multiplied_sizes" - } - }, - "type": "const_above_diagonal" - }, - "memory": { - "arguments": { - "intercept": 0, - "minimum": 1, - "slope": 1 - }, - "type": "subtracted_sizes" - } - }, - "encodeUtf8": { - "cpu": { - "arguments": { - "intercept": 1000, - "slope": 28662 - }, - "type": "linear_in_x" - }, - "memory": { - "arguments": { - "intercept": 4, - "slope": 2 - }, - "type": "linear_in_x" - } - }, - "equalsByteString": { - "cpu": { - "arguments": { - "constant": 245000, - "intercept": 216773, - "slope": 62 - }, - "type": "linear_on_diagonal" - }, - "memory": { - "arguments": 1, - "type": "constant_cost" - } - }, - "equalsData": { - "cpu": { - "arguments": { - "intercept": 1060367, - "slope": 12586 - }, - "type": "min_size" - }, - "memory": { - "arguments": 1, - "type": "constant_cost" - } - }, - "equalsInteger": { - "cpu": { - "arguments": { - "intercept": 208512, - "slope": 421 - }, - "type": "min_size" - }, - "memory": { - "arguments": 1, - "type": "constant_cost" - } - }, - "equalsString": { - "cpu": { - "arguments": { - "constant": 187000, - "intercept": 1000, - "slope": 52998 - }, - "type": "linear_on_diagonal" - }, - "memory": { - "arguments": 1, - "type": "constant_cost" - } - }, - "fstPair": { - "cpu": { - "arguments": 80436, - "type": "constant_cost" - }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } - }, - "headList": { - "cpu": { - "arguments": 43249, - "type": "constant_cost" - }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } - }, - "iData": { - "cpu": { - "arguments": 1000, - "type": "constant_cost" - }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } - }, - "ifThenElse": { - "cpu": { - "arguments": 80556, - "type": "constant_cost" - }, - "memory": { - "arguments": 1, - "type": "constant_cost" - } - }, - "indexByteString": { - "cpu": { - "arguments": 57667, - "type": "constant_cost" - }, - "memory": { - "arguments": 4, - "type": "constant_cost" - } - }, - "integerToByteString": { - "cpu": { - "arguments": { - "c0": 1293828, - "c1": 28716, - "c2": 63 - }, - "type": "quadratic_in_z" - }, - "memory": { - "arguments": { - "intercept": 0, - "slope": 1 - }, - "type": "literal_in_y_or_linear_in_z" - } - }, - "keccak_256": { - "cpu": { - "arguments": { - "intercept": 2261318, - "slope": 64571 - }, - "type": "linear_in_x" - }, - "memory": { - "arguments": 4, - "type": "constant_cost" - } - }, - "lengthOfByteString": { - "cpu": { - "arguments": 1000, - "type": "constant_cost" - }, - "memory": { - "arguments": 10, - "type": "constant_cost" - } - }, - "lessThanByteString": { - "cpu": { - "arguments": { - "intercept": 197145, - "slope": 156 - }, - "type": "min_size" - }, - "memory": { - "arguments": 1, - "type": "constant_cost" - } - }, - "lessThanEqualsByteString": { - "cpu": { - "arguments": { - "intercept": 197145, - "slope": 156 - }, - "type": "min_size" - }, - "memory": { - "arguments": 1, - "type": "constant_cost" - } - }, - "lessThanEqualsInteger": { - "cpu": { - "arguments": { - "intercept": 204924, - "slope": 473 - }, - "type": "min_size" - }, - "memory": { - "arguments": 1, - "type": "constant_cost" - } - }, - "lessThanInteger": { - "cpu": { - "arguments": { - "intercept": 208896, - "slope": 511 - }, - "type": "min_size" - }, - "memory": { - "arguments": 1, - "type": "constant_cost" - } - }, - "listData": { - "cpu": { - "arguments": 52467, - "type": "constant_cost" - }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } - }, - "mapData": { - "cpu": { - "arguments": 64832, - "type": "constant_cost" - }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } - }, - "mkCons": { - "cpu": { - "arguments": 65493, - "type": "constant_cost" - }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } - }, - "mkNilData": { - "cpu": { - "arguments": 22558, - "type": "constant_cost" - }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } - }, - "mkNilPairData": { - "cpu": { - "arguments": 16563, - "type": "constant_cost" - }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } - }, - "mkPairData": { - "cpu": { - "arguments": 76511, - "type": "constant_cost" - }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } - }, - "modInteger": { - "cpu": { - "arguments": { - "constant": 196500, - "model": { - "arguments": { - "intercept": 453240, - "slope": 220 - }, - "type": "multiplied_sizes" - } - }, - "type": "const_above_diagonal" - }, - "memory": { - "arguments": { - "intercept": 0, - "minimum": 1, - "slope": 1 - }, - "type": "subtracted_sizes" - } - }, - "multiplyInteger": { - "cpu": { - "arguments": { - "intercept": 69522, - "slope": 11687 - }, - "type": "added_sizes" - }, - "memory": { - "arguments": { - "intercept": 0, - "slope": 1 - }, - "type": "added_sizes" - } - }, - "nullList": { - "cpu": { - "arguments": 60091, - "type": "constant_cost" - }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } - }, - "indexArray": { - "cpu": { - "arguments": 194922, - "type": "constant_cost" - }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } - }, - "lengthOfArray": { - "cpu": { - "arguments": 198994, - "type": "constant_cost" - }, - "memory": { - "arguments": 10, - "type": "constant_cost" - } - }, - "listToArray": { - "cpu": { - "arguments": { - "intercept": 307802, - "slope": 8496 - }, - "type": "linear_in_x" - }, - "memory": { - "arguments": { - "intercept": 7, - "slope": 1 - }, - "type": "linear_in_x" - } - }, - "quotientInteger": { - "cpu": { - "arguments": { - "constant": 196500, - "model": { - "arguments": { - "intercept": 453240, - "slope": 220 - }, - "type": "multiplied_sizes" - } - }, - "type": "const_above_diagonal" - }, - "memory": { - "arguments": { - "intercept": 0, - "minimum": 1, - "slope": 1 - }, - "type": "subtracted_sizes" - } - }, - "remainderInteger": { - "cpu": { - "arguments": { - "constant": 196500, - "model": { - "arguments": { - "intercept": 453240, - "slope": 220 - }, - "type": "multiplied_sizes" - } - }, - "type": "const_above_diagonal" - }, - "memory": { - "arguments": { - "intercept": 0, - "minimum": 1, - "slope": 1 - }, - "type": "subtracted_sizes" - } - }, - "serialiseData": { - "cpu": { - "arguments": { - "intercept": 1159724, - "slope": 392670 - }, - "type": "linear_in_x" - }, - "memory": { - "arguments": { - "intercept": 0, - "slope": 2 - }, - "type": "linear_in_x" - } - }, - "sha2_256": { - "cpu": { - "arguments": { - "intercept": 806990, - "slope": 30482 - }, - "type": "linear_in_x" - }, - "memory": { - "arguments": 4, - "type": "constant_cost" - } - }, - "sha3_256": { - "cpu": { - "arguments": { - "intercept": 1927926, - "slope": 82523 - }, - "type": "linear_in_x" - }, - "memory": { - "arguments": 4, - "type": "constant_cost" - } - }, - "sliceByteString": { - "cpu": { - "arguments": { - "intercept": 265318, - "slope": 0 - }, - "type": "linear_in_z" - }, - "memory": { - "arguments": { - "intercept": 4, - "slope": 0 - }, - "type": "linear_in_z" - } - }, - "sndPair": { - "cpu": { - "arguments": 85931, - "type": "constant_cost" - }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } - }, - "subtractInteger": { - "cpu": { - "arguments": { - "intercept": 205665, - "slope": 812 - }, - "type": "max_size" - }, - "memory": { - "arguments": { - "intercept": 1, - "slope": 1 - }, - "type": "max_size" - } - }, - "tailList": { - "cpu": { - "arguments": 41182, - "type": "constant_cost" - }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } - }, - "trace": { - "cpu": { - "arguments": 212342, - "type": "constant_cost" - }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } - }, - "unBData": { - "cpu": { - "arguments": 31220, - "type": "constant_cost" - }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } - }, - "unConstrData": { - "cpu": { - "arguments": 32696, - "type": "constant_cost" - }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } - }, - "unIData": { - "cpu": { - "arguments": 43357, - "type": "constant_cost" - }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } - }, - "unListData": { - "cpu": { - "arguments": 32247, - "type": "constant_cost" - }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } - }, - "unMapData": { - "cpu": { - "arguments": 38314, - "type": "constant_cost" - }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } - }, - "verifyEcdsaSecp256k1Signature": { - "cpu": { - "arguments": 35190005, - "type": "constant_cost" - }, - "memory": { - "arguments": 10, - "type": "constant_cost" - } - }, - "verifyEd25519Signature": { - "cpu": { - "arguments": { - "intercept": 57996947, - "slope": 18975 - }, - "type": "linear_in_z" - }, - "memory": { - "arguments": 10, - "type": "constant_cost" - } - }, - "verifySchnorrSecp256k1Signature": { - "cpu": { - "arguments": { - "intercept": 39121781, - "slope": 32260 - }, - "type": "linear_in_y" - }, - "memory": { - "arguments": 10, - "type": "constant_cost" - } - }, - "andByteString": { - "cpu": { - "arguments": { - "intercept": 100181, - "slope1": 726, - "slope2": 719 - }, - "type": "linear_in_y_and_z" - }, - "memory": { - "arguments": { - "intercept": 0, - "slope": 1 - }, - "type": "linear_in_max_yz" - } - }, - "orByteString": { - "cpu": { - "arguments": { - "intercept": 100181, - "slope1": 726, - "slope2": 719 - }, - "type": "linear_in_y_and_z" - }, - "memory": { - "arguments": { - "intercept": 0, - "slope": 1 - }, - "type": "linear_in_max_yz" - } - }, - "xorByteString": { - "cpu": { - "arguments": { - "intercept": 100181, - "slope1": 726, - "slope2": 719 - }, - "type": "linear_in_y_and_z" - }, - "memory": { - "arguments": { - "intercept": 0, - "slope": 1 - }, - "type": "linear_in_max_yz" - } - }, - "complementByteString": { - "cpu": { - "arguments": { - "intercept": 107878, - "slope": 680 - }, - "type": "linear_in_x" - }, - "memory": { - "arguments": { - "intercept": 0, - "slope": 1 - }, - "type": "linear_in_x" - } - }, - "readBit": { - "cpu": { - "arguments": 95336, - "type": "constant_cost" - }, - "memory": { - "arguments": 1, - "type": "constant_cost" - } - }, - "writeBits": { - "cpu": { - "arguments": { - "intercept": 281145, - "slope": 18848 - }, - "type": "linear_in_y" - }, - "memory": { - "arguments": { - "intercept": 0, - "slope": 1 - }, - "type": "linear_in_x" - } - }, - "replicateByte": { - "cpu": { - "arguments": { - "intercept": 180194, - "slope": 159 - }, - "type": "linear_in_x" - }, - "memory": { - "arguments": { - "intercept": 1, - "slope": 1 - }, - "type": "linear_in_x" - } - }, - "shiftByteString": { - "cpu": { - "arguments": { - "intercept": 158519, - "slope": 8942 - }, - "type": "linear_in_x" - }, - "memory": { - "arguments": { - "intercept": 0, - "slope": 1 - }, - "type": "linear_in_x" - } - }, - "rotateByteString": { - "cpu": { - "arguments": { - "intercept": 159378, - "slope": 8813 - }, - "type": "linear_in_x" - }, - "memory": { - "arguments": { - "intercept": 0, - "slope": 1 - }, - "type": "linear_in_x" - } - }, - "countSetBits": { - "cpu": { - "arguments": { - "intercept": 107490, - "slope": 3298 - }, - "type": "linear_in_x" - }, - "memory": { - "arguments": 1, - "type": "constant_cost" - } - }, - "findFirstSetBit": { - "cpu": { - "arguments": { - "intercept": 106057, - "slope": 655 - }, - "type": "linear_in_x" - }, - "memory": { - "arguments": 1, - "type": "constant_cost" - } - }, - "ripemd_160": { - "cpu": { - "arguments": { - "intercept": 1964219, - "slope": 24520 - }, - "type": "linear_in_x" - }, - "memory": { - "arguments": 3, - "type": "constant_cost" - } - }, - "expModInteger": { - "cpu": { - "arguments": { - "coefficient00": 607153, - "coefficient11": 231697, - "coefficient12": 53144 - }, - "type": "exp_mod_cost" - }, - "memory": { - "arguments": { - "intercept": 0, - "slope": 1 - }, - "type": "linear_in_z" - } - }, - "dropList": { - "cpu": { - "arguments": { - "intercept": 116711, - "slope": 1957 - }, - "type": "linear_in_x" - }, - "memory": { - "arguments": 4, - "type": "constant_cost" - } + "addInteger": { + "cpu": { + "arguments": { + "intercept": 205665, + "slope": 812 + }, + "type": "max_size" + }, + "memory": { + "arguments": { + "intercept": 1, + "slope": 1 + }, + "type": "max_size" + } + }, + "appendByteString": { + "cpu": { + "arguments": { + "intercept": 1000, + "slope": 571 + }, + "type": "added_sizes" + }, + "memory": { + "arguments": { + "intercept": 0, + "slope": 1 + }, + "type": "added_sizes" + } + }, + "appendString": { + "cpu": { + "arguments": { + "intercept": 1000, + "slope": 24177 + }, + "type": "added_sizes" + }, + "memory": { + "arguments": { + "intercept": 4, + "slope": 1 + }, + "type": "added_sizes" + } + }, + "bData": { + "cpu": { + "arguments": 1000, + "type": "constant_cost" + }, + "memory": { + "arguments": 32, + "type": "constant_cost" + } + }, + "blake2b_224": { + "cpu": { + "arguments": { + "intercept": 207616, + "slope": 8310 + }, + "type": "linear_in_x" + }, + "memory": { + "arguments": 4, + "type": "constant_cost" + } + }, + "blake2b_256": { + "cpu": { + "arguments": { + "intercept": 117366, + "slope": 10475 + }, + "type": "linear_in_x" + }, + "memory": { + "arguments": 4, + "type": "constant_cost" + } + }, + "bls12_381_G1_add": { + "cpu": { + "arguments": 962335, + "type": "constant_cost" + }, + "memory": { + "arguments": 18, + "type": "constant_cost" + } + }, + "bls12_381_G1_compress": { + "cpu": { + "arguments": 2780678, + "type": "constant_cost" + }, + "memory": { + "arguments": 6, + "type": "constant_cost" + } + }, + "bls12_381_G1_equal": { + "cpu": { + "arguments": 442008, + "type": "constant_cost" + }, + "memory": { + "arguments": 1, + "type": "constant_cost" + } + }, + "bls12_381_G1_hashToGroup": { + "cpu": { + "arguments": { + "intercept": 52538055, + "slope": 3756 + }, + "type": "linear_in_x" + }, + "memory": { + "arguments": 18, + "type": "constant_cost" + } + }, + "bls12_381_G1_neg": { + "cpu": { + "arguments": 267929, + "type": "constant_cost" + }, + "memory": { + "arguments": 18, + "type": "constant_cost" + } + }, + "bls12_381_G1_scalarMul": { + "cpu": { + "arguments": { + "intercept": 76433006, + "slope": 8868 + }, + "type": "linear_in_x" + }, + "memory": { + "arguments": 18, + "type": "constant_cost" + } + }, + "bls12_381_G1_multiScalarMul": { + "cpu": { + "arguments": { + "intercept": 321837444, + "slope": 25087669 + }, + "type": "linear_in_x" + }, + "memory": { + "arguments": 18, + "type": "constant_cost" + } + }, + "bls12_381_G1_uncompress": { + "cpu": { + "arguments": 52948122, + "type": "constant_cost" + }, + "memory": { + "arguments": 18, + "type": "constant_cost" + } + }, + "bls12_381_G2_add": { + "cpu": { + "arguments": 1995836, + "type": "constant_cost" + }, + "memory": { + "arguments": 36, + "type": "constant_cost" + } + }, + "bls12_381_G2_compress": { + "cpu": { + "arguments": 3227919, + "type": "constant_cost" + }, + "memory": { + "arguments": 12, + "type": "constant_cost" + } + }, + "bls12_381_G2_equal": { + "cpu": { + "arguments": 901022, + "type": "constant_cost" + }, + "memory": { + "arguments": 1, + "type": "constant_cost" + } + }, + "bls12_381_G2_hashToGroup": { + "cpu": { + "arguments": { + "intercept": 166917843, + "slope": 4307 + }, + "type": "linear_in_x" + }, + "memory": { + "arguments": 36, + "type": "constant_cost" + } + }, + "bls12_381_G2_neg": { + "cpu": { + "arguments": 284546, + "type": "constant_cost" + }, + "memory": { + "arguments": 36, + "type": "constant_cost" + } + }, + "bls12_381_G2_scalarMul": { + "cpu": { + "arguments": { + "intercept": 158221314, + "slope": 26549 + }, + "type": "linear_in_x" + }, + "memory": { + "arguments": 36, + "type": "constant_cost" + } + }, + "bls12_381_G2_multiScalarMul": { + "cpu": { + "arguments": { + "intercept": 617887431, + "slope": 67302824 + }, + "type": "linear_in_x" + }, + "memory": { + "arguments": 36, + "type": "constant_cost" + } + }, + "bls12_381_G2_uncompress": { + "cpu": { + "arguments": 74698472, + "type": "constant_cost" + }, + "memory": { + "arguments": 36, + "type": "constant_cost" + } + }, + "bls12_381_finalVerify": { + "cpu": { + "arguments": 333849714, + "type": "constant_cost" + }, + "memory": { + "arguments": 1, + "type": "constant_cost" + } + }, + "bls12_381_millerLoop": { + "cpu": { + "arguments": 254006273, + "type": "constant_cost" + }, + "memory": { + "arguments": 72, + "type": "constant_cost" + } + }, + "bls12_381_mulMlResult": { + "cpu": { + "arguments": 2174038, + "type": "constant_cost" + }, + "memory": { + "arguments": 72, + "type": "constant_cost" + } + }, + "byteStringToInteger": { + "cpu": { + "arguments": { + "c0": 1006041, + "c1": 43623, + "c2": 251 + }, + "type": "quadratic_in_y" + }, + "memory": { + "arguments": { + "intercept": 0, + "slope": 1 + }, + "type": "linear_in_y" + } + }, + "chooseData": { + "cpu": { + "arguments": 19537, + "type": "constant_cost" + }, + "memory": { + "arguments": 32, + "type": "constant_cost" + } + }, + "chooseList": { + "cpu": { + "arguments": 175354, + "type": "constant_cost" + }, + "memory": { + "arguments": 32, + "type": "constant_cost" + } + }, + "chooseUnit": { + "cpu": { + "arguments": 46417, + "type": "constant_cost" + }, + "memory": { + "arguments": 4, + "type": "constant_cost" + } + }, + "consByteString": { + "cpu": { + "arguments": { + "intercept": 221973, + "slope": 511 + }, + "type": "linear_in_y" + }, + "memory": { + "arguments": { + "intercept": 0, + "slope": 1 + }, + "type": "added_sizes" + } + }, + "constrData": { + "cpu": { + "arguments": 89141, + "type": "constant_cost" + }, + "memory": { + "arguments": 32, + "type": "constant_cost" + } + }, + "decodeUtf8": { + "cpu": { + "arguments": { + "intercept": 497525, + "slope": 14068 + }, + "type": "linear_in_x" + }, + "memory": { + "arguments": { + "intercept": 4, + "slope": 2 + }, + "type": "linear_in_x" + } + }, + "divideInteger": { + "cpu": { + "arguments": { + "constant": 196500, + "model": { + "arguments": { + "intercept": 453240, + "slope": 220 + }, + "type": "multiplied_sizes" + } + }, + "type": "const_above_diagonal" + }, + "memory": { + "arguments": { + "intercept": 0, + "minimum": 1, + "slope": 1 + }, + "type": "subtracted_sizes" + } + }, + "encodeUtf8": { + "cpu": { + "arguments": { + "intercept": 1000, + "slope": 28662 + }, + "type": "linear_in_x" + }, + "memory": { + "arguments": { + "intercept": 4, + "slope": 2 + }, + "type": "linear_in_x" + } + }, + "equalsByteString": { + "cpu": { + "arguments": { + "constant": 245000, + "intercept": 216773, + "slope": 62 + }, + "type": "linear_on_diagonal" + }, + "memory": { + "arguments": 1, + "type": "constant_cost" + } + }, + "equalsData": { + "cpu": { + "arguments": { + "intercept": 1060367, + "slope": 12586 + }, + "type": "min_size" + }, + "memory": { + "arguments": 1, + "type": "constant_cost" + } + }, + "equalsInteger": { + "cpu": { + "arguments": { + "intercept": 208512, + "slope": 421 + }, + "type": "min_size" + }, + "memory": { + "arguments": 1, + "type": "constant_cost" + } + }, + "equalsString": { + "cpu": { + "arguments": { + "constant": 187000, + "intercept": 1000, + "slope": 52998 + }, + "type": "linear_on_diagonal" + }, + "memory": { + "arguments": 1, + "type": "constant_cost" + } + }, + "fstPair": { + "cpu": { + "arguments": 80436, + "type": "constant_cost" + }, + "memory": { + "arguments": 32, + "type": "constant_cost" + } + }, + "headList": { + "cpu": { + "arguments": 43249, + "type": "constant_cost" + }, + "memory": { + "arguments": 32, + "type": "constant_cost" + } + }, + "iData": { + "cpu": { + "arguments": 1000, + "type": "constant_cost" + }, + "memory": { + "arguments": 32, + "type": "constant_cost" + } + }, + "ifThenElse": { + "cpu": { + "arguments": 80556, + "type": "constant_cost" + }, + "memory": { + "arguments": 1, + "type": "constant_cost" + } + }, + "indexByteString": { + "cpu": { + "arguments": 57667, + "type": "constant_cost" + }, + "memory": { + "arguments": 4, + "type": "constant_cost" + } + }, + "integerToByteString": { + "cpu": { + "arguments": { + "c0": 1293828, + "c1": 28716, + "c2": 63 + }, + "type": "quadratic_in_z" + }, + "memory": { + "arguments": { + "intercept": 0, + "slope": 1 + }, + "type": "literal_in_y_or_linear_in_z" + } + }, + "keccak_256": { + "cpu": { + "arguments": { + "intercept": 2261318, + "slope": 64571 + }, + "type": "linear_in_x" + }, + "memory": { + "arguments": 4, + "type": "constant_cost" + } + }, + "lengthOfByteString": { + "cpu": { + "arguments": 1000, + "type": "constant_cost" + }, + "memory": { + "arguments": 10, + "type": "constant_cost" + } + }, + "lessThanByteString": { + "cpu": { + "arguments": { + "intercept": 197145, + "slope": 156 + }, + "type": "min_size" + }, + "memory": { + "arguments": 1, + "type": "constant_cost" + } + }, + "lessThanEqualsByteString": { + "cpu": { + "arguments": { + "intercept": 197145, + "slope": 156 + }, + "type": "min_size" + }, + "memory": { + "arguments": 1, + "type": "constant_cost" + } + }, + "lessThanEqualsInteger": { + "cpu": { + "arguments": { + "intercept": 204924, + "slope": 473 + }, + "type": "min_size" + }, + "memory": { + "arguments": 1, + "type": "constant_cost" + } + }, + "lessThanInteger": { + "cpu": { + "arguments": { + "intercept": 208896, + "slope": 511 + }, + "type": "min_size" + }, + "memory": { + "arguments": 1, + "type": "constant_cost" + } + }, + "listData": { + "cpu": { + "arguments": 52467, + "type": "constant_cost" + }, + "memory": { + "arguments": 32, + "type": "constant_cost" + } + }, + "mapData": { + "cpu": { + "arguments": 64832, + "type": "constant_cost" + }, + "memory": { + "arguments": 32, + "type": "constant_cost" + } + }, + "mkCons": { + "cpu": { + "arguments": 65493, + "type": "constant_cost" + }, + "memory": { + "arguments": 32, + "type": "constant_cost" + } + }, + "mkNilData": { + "cpu": { + "arguments": 22558, + "type": "constant_cost" + }, + "memory": { + "arguments": 32, + "type": "constant_cost" + } + }, + "mkNilPairData": { + "cpu": { + "arguments": 16563, + "type": "constant_cost" + }, + "memory": { + "arguments": 32, + "type": "constant_cost" + } + }, + "mkPairData": { + "cpu": { + "arguments": 76511, + "type": "constant_cost" + }, + "memory": { + "arguments": 32, + "type": "constant_cost" + } + }, + "modInteger": { + "cpu": { + "arguments": { + "constant": 196500, + "model": { + "arguments": { + "intercept": 453240, + "slope": 220 + }, + "type": "multiplied_sizes" + } + }, + "type": "const_above_diagonal" + }, + "memory": { + "arguments": { + "intercept": 0, + "minimum": 1, + "slope": 1 + }, + "type": "subtracted_sizes" + } + }, + "multiplyInteger": { + "cpu": { + "arguments": { + "intercept": 69522, + "slope": 11687 + }, + "type": "added_sizes" + }, + "memory": { + "arguments": { + "intercept": 0, + "slope": 1 + }, + "type": "added_sizes" + } + }, + "nullList": { + "cpu": { + "arguments": 60091, + "type": "constant_cost" + }, + "memory": { + "arguments": 32, + "type": "constant_cost" + } + }, + "indexArray": { + "cpu": { + "arguments": 194922, + "type": "constant_cost" + }, + "memory": { + "arguments": 32, + "type": "constant_cost" + } + }, + "lengthOfArray": { + "cpu": { + "arguments": 198994, + "type": "constant_cost" + }, + "memory": { + "arguments": 10, + "type": "constant_cost" + } + }, + "listToArray": { + "cpu": { + "arguments": { + "intercept": 307802, + "slope": 8496 + }, + "type": "linear_in_x" + }, + "memory": { + "arguments": { + "intercept": 7, + "slope": 1 + }, + "type": "linear_in_x" + } + }, + "quotientInteger": { + "cpu": { + "arguments": { + "constant": 196500, + "model": { + "arguments": { + "intercept": 453240, + "slope": 220 + }, + "type": "multiplied_sizes" + } + }, + "type": "const_above_diagonal" + }, + "memory": { + "arguments": { + "intercept": 0, + "minimum": 1, + "slope": 1 + }, + "type": "subtracted_sizes" + } + }, + "remainderInteger": { + "cpu": { + "arguments": { + "constant": 196500, + "model": { + "arguments": { + "intercept": 453240, + "slope": 220 + }, + "type": "multiplied_sizes" + } + }, + "type": "const_above_diagonal" + }, + "memory": { + "arguments": { + "intercept": 0, + "minimum": 1, + "slope": 1 + }, + "type": "subtracted_sizes" + } + }, + "serialiseData": { + "cpu": { + "arguments": { + "intercept": 1159724, + "slope": 392670 + }, + "type": "linear_in_x" + }, + "memory": { + "arguments": { + "intercept": 0, + "slope": 2 + }, + "type": "linear_in_x" + } + }, + "sha2_256": { + "cpu": { + "arguments": { + "intercept": 806990, + "slope": 30482 + }, + "type": "linear_in_x" + }, + "memory": { + "arguments": 4, + "type": "constant_cost" + } + }, + "sha3_256": { + "cpu": { + "arguments": { + "intercept": 1927926, + "slope": 82523 + }, + "type": "linear_in_x" + }, + "memory": { + "arguments": 4, + "type": "constant_cost" + } + }, + "sliceByteString": { + "cpu": { + "arguments": { + "intercept": 265318, + "slope": 0 + }, + "type": "linear_in_z" + }, + "memory": { + "arguments": { + "intercept": 4, + "slope": 0 + }, + "type": "linear_in_z" + } + }, + "sndPair": { + "cpu": { + "arguments": 85931, + "type": "constant_cost" + }, + "memory": { + "arguments": 32, + "type": "constant_cost" + } + }, + "subtractInteger": { + "cpu": { + "arguments": { + "intercept": 205665, + "slope": 812 + }, + "type": "max_size" + }, + "memory": { + "arguments": { + "intercept": 1, + "slope": 1 + }, + "type": "max_size" + } + }, + "tailList": { + "cpu": { + "arguments": 41182, + "type": "constant_cost" + }, + "memory": { + "arguments": 32, + "type": "constant_cost" + } + }, + "trace": { + "cpu": { + "arguments": 212342, + "type": "constant_cost" + }, + "memory": { + "arguments": 32, + "type": "constant_cost" + } + }, + "unBData": { + "cpu": { + "arguments": 31220, + "type": "constant_cost" + }, + "memory": { + "arguments": 32, + "type": "constant_cost" + } + }, + "unConstrData": { + "cpu": { + "arguments": 32696, + "type": "constant_cost" + }, + "memory": { + "arguments": 32, + "type": "constant_cost" + } + }, + "unIData": { + "cpu": { + "arguments": 43357, + "type": "constant_cost" + }, + "memory": { + "arguments": 32, + "type": "constant_cost" + } + }, + "unListData": { + "cpu": { + "arguments": 32247, + "type": "constant_cost" + }, + "memory": { + "arguments": 32, + "type": "constant_cost" + } + }, + "unMapData": { + "cpu": { + "arguments": 38314, + "type": "constant_cost" + }, + "memory": { + "arguments": 32, + "type": "constant_cost" + } + }, + "verifyEcdsaSecp256k1Signature": { + "cpu": { + "arguments": 35190005, + "type": "constant_cost" + }, + "memory": { + "arguments": 10, + "type": "constant_cost" + } + }, + "verifyEd25519Signature": { + "cpu": { + "arguments": { + "intercept": 57996947, + "slope": 18975 + }, + "type": "linear_in_z" + }, + "memory": { + "arguments": 10, + "type": "constant_cost" + } + }, + "verifySchnorrSecp256k1Signature": { + "cpu": { + "arguments": { + "intercept": 39121781, + "slope": 32260 + }, + "type": "linear_in_y" + }, + "memory": { + "arguments": 10, + "type": "constant_cost" + } + }, + "andByteString": { + "cpu": { + "arguments": { + "intercept": 100181, + "slope1": 726, + "slope2": 719 + }, + "type": "linear_in_y_and_z" + }, + "memory": { + "arguments": { + "intercept": 0, + "slope": 1 + }, + "type": "linear_in_max_yz" + } + }, + "orByteString": { + "cpu": { + "arguments": { + "intercept": 100181, + "slope1": 726, + "slope2": 719 + }, + "type": "linear_in_y_and_z" + }, + "memory": { + "arguments": { + "intercept": 0, + "slope": 1 + }, + "type": "linear_in_max_yz" + } + }, + "xorByteString": { + "cpu": { + "arguments": { + "intercept": 100181, + "slope1": 726, + "slope2": 719 + }, + "type": "linear_in_y_and_z" + }, + "memory": { + "arguments": { + "intercept": 0, + "slope": 1 + }, + "type": "linear_in_max_yz" + } + }, + "complementByteString": { + "cpu": { + "arguments": { + "intercept": 107878, + "slope": 680 + }, + "type": "linear_in_x" + }, + "memory": { + "arguments": { + "intercept": 0, + "slope": 1 + }, + "type": "linear_in_x" + } + }, + "readBit": { + "cpu": { + "arguments": 95336, + "type": "constant_cost" + }, + "memory": { + "arguments": 1, + "type": "constant_cost" + } + }, + "writeBits": { + "cpu": { + "arguments": { + "intercept": 281145, + "slope": 18848 + }, + "type": "linear_in_y" + }, + "memory": { + "arguments": { + "intercept": 0, + "slope": 1 + }, + "type": "linear_in_x" + } + }, + "replicateByte": { + "cpu": { + "arguments": { + "intercept": 180194, + "slope": 159 + }, + "type": "linear_in_x" + }, + "memory": { + "arguments": { + "intercept": 1, + "slope": 1 + }, + "type": "linear_in_x" + } + }, + "shiftByteString": { + "cpu": { + "arguments": { + "intercept": 158519, + "slope": 8942 + }, + "type": "linear_in_x" + }, + "memory": { + "arguments": { + "intercept": 0, + "slope": 1 + }, + "type": "linear_in_x" + } + }, + "rotateByteString": { + "cpu": { + "arguments": { + "intercept": 159378, + "slope": 8813 + }, + "type": "linear_in_x" + }, + "memory": { + "arguments": { + "intercept": 0, + "slope": 1 + }, + "type": "linear_in_x" + } + }, + "countSetBits": { + "cpu": { + "arguments": { + "intercept": 107490, + "slope": 3298 + }, + "type": "linear_in_x" + }, + "memory": { + "arguments": 1, + "type": "constant_cost" + } + }, + "findFirstSetBit": { + "cpu": { + "arguments": { + "intercept": 106057, + "slope": 655 + }, + "type": "linear_in_x" + }, + "memory": { + "arguments": 1, + "type": "constant_cost" + } + }, + "ripemd_160": { + "cpu": { + "arguments": { + "intercept": 1964219, + "slope": 24520 + }, + "type": "linear_in_x" + }, + "memory": { + "arguments": 3, + "type": "constant_cost" + } + }, + "expModInteger": { + "cpu": { + "arguments": { + "coefficient00": 607153, + "coefficient11": 231697, + "coefficient12": 53144 + }, + "type": "exp_mod_cost" + }, + "memory": { + "arguments": { + "intercept": 0, + "slope": 1 + }, + "type": "linear_in_z" + } + }, + "dropList": { + "cpu": { + "arguments": { + "intercept": 116711, + "slope": 1957 + }, + "type": "linear_in_x" + }, + "memory": { + "arguments": 4, + "type": "constant_cost" + } + }, + "lookupCoin": { + "cpu": { + "arguments": { + "intercept": 284421, + "slope": 1 + }, + "type": "linear_in_z" + }, + "memory": { + "arguments": 1, + "type": "constant_cost" + } + }, + "valueContains": { + "cpu": { + "arguments": { + "intercept": 42125119, + "slope": 30 + }, + "type": "added_sizes" + }, + "memory": { + "arguments": 1, + "type": "constant_cost" + } + }, + "valueData": { + "cpu": { + "arguments": 205465, + "type": "constant_cost" + }, + "memory": { + "arguments": 1, + "type": "constant_cost" + } + }, + "unValueData": { + "cpu": { + "arguments": { + "intercept": 10532326261, + "slope": 431 + }, + "type": "linear_in_x" + }, + "memory": { + "arguments": 1, + "type": "constant_cost" } + } } diff --git a/plutus-core/cost-model/data/builtinCostModelB.json b/plutus-core/cost-model/data/builtinCostModelB.json index 7b4350c3c10..8cb65a566d7 100644 --- a/plutus-core/cost-model/data/builtinCostModelB.json +++ b/plutus-core/cost-model/data/builtinCostModelB.json @@ -1205,5 +1205,54 @@ "arguments": 4, "type": "constant_cost" } + }, + "lookupCoin": { + "cpu": { + "arguments": { + "intercept": 284421, + "slope": 1 + }, + "type": "linear_in_z" + }, + "memory": { + "arguments": 1, + "type": "constant_cost" + } + }, + "valueContains": { + "cpu": { + "arguments": { + "intercept": 42125119, + "slope": 30 + }, + "type": "added_sizes" + }, + "memory": { + "arguments": 1, + "type": "constant_cost" + } + }, + "valueData": { + "cpu": { + "arguments": 205465, + "type": "constant_cost" + }, + "memory": { + "arguments": 1, + "type": "constant_cost" + } + }, + "unValueData": { + "cpu": { + "arguments": { + "intercept": 10532326261, + "slope": 431 + }, + "type": "linear_in_x" + }, + "memory": { + "arguments": 1, + "type": "constant_cost" + } } } diff --git a/plutus-core/cost-model/data/builtinCostModelC.json b/plutus-core/cost-model/data/builtinCostModelC.json index f69154d323c..b31f63df1b8 100644 --- a/plutus-core/cost-model/data/builtinCostModelC.json +++ b/plutus-core/cost-model/data/builtinCostModelC.json @@ -1223,5 +1223,54 @@ "arguments": 4, "type": "constant_cost" } + }, + "lookupCoin": { + "cpu": { + "arguments": { + "intercept": 284421, + "slope": 1 + }, + "type": "linear_in_z" + }, + "memory": { + "arguments": 1, + "type": "constant_cost" + } + }, + "valueContains": { + "cpu": { + "arguments": { + "intercept": 42125119, + "slope": 30 + }, + "type": "added_sizes" + }, + "memory": { + "arguments": 1, + "type": "constant_cost" + } + }, + "valueData": { + "cpu": { + "arguments": 205465, + "type": "constant_cost" + }, + "memory": { + "arguments": 1, + "type": "constant_cost" + } + }, + "unValueData": { + "cpu": { + "arguments": { + "intercept": 10532326261, + "slope": 431 + }, + "type": "linear_in_x" + }, + "memory": { + "arguments": 1, + "type": "constant_cost" + } } } diff --git a/plutus-core/cost-model/test/TestCostModels.hs b/plutus-core/cost-model/test/TestCostModels.hs index e202ce228d7..fa0d4ef0652 100644 --- a/plutus-core/cost-model/test/TestCostModels.hs +++ b/plutus-core/cost-model/test/TestCostModels.hs @@ -387,6 +387,12 @@ main = , $(genTest 1 "listToArray") , $(genTest 2 "indexArray") Everywhere + -- Builtin Values + , $(genTest 3 "lookupCoin") + , $(genTest 2 "valueContains") Everywhere + , $(genTest 1 "valueData") + , $(genTest 1 "unValueData") + -- Data , $(genTest 6 "chooseData") , $(genTest 2 "constrData") Everywhere From 447c4dbcb802ea35a9cb1e308c2cc8c0551a8d78 Mon Sep 17 00:00:00 2001 From: Yura Lazaryev Date: Wed, 24 Sep 2025 18:05:26 +0200 Subject: [PATCH 04/17] feat: replace placeholder costing with parameter-driven implementation Removes unimplementedCostingFun placeholders for Value builtins and connects them to their respective cost model parameters (paramLookupCoin, paramValueContains, paramValueData, paramUnValueData). Enables accurate execution cost calculation for Value operations in Plutus Core scripts. --- .../plutus-core/src/PlutusCore/Default/Builtins.hs | 8 ++++---- 1 file changed, 4 insertions(+), 4 deletions(-) diff --git a/plutus-core/plutus-core/src/PlutusCore/Default/Builtins.hs b/plutus-core/plutus-core/src/PlutusCore/Default/Builtins.hs index 4604478d300..8cf1fdf4739 100644 --- a/plutus-core/plutus-core/src/PlutusCore/Default/Builtins.hs +++ b/plutus-core/plutus-core/src/PlutusCore/Default/Builtins.hs @@ -2060,7 +2060,7 @@ instance uni ~ DefaultUni => ToBuiltinMeaning uni DefaultFun where {-# INLINE lookupCoinDenotation #-} in makeBuiltinMeaning lookupCoinDenotation - (runCostingFunThreeArguments . unimplementedCostingFun) + (runCostingFunThreeArguments . paramLookupCoin) toBuiltinMeaning _semvar UnionValue = let unionValueDenotation :: Value -> Value -> Value @@ -2076,7 +2076,7 @@ instance uni ~ DefaultUni => ToBuiltinMeaning uni DefaultFun where {-# INLINE valueContainsDenotation #-} in makeBuiltinMeaning valueContainsDenotation - (runCostingFunTwoArguments . unimplementedCostingFun) + (runCostingFunTwoArguments . paramValueContains) toBuiltinMeaning _semvar ValueData = let valueDataDenotation :: Value -> Data @@ -2084,7 +2084,7 @@ instance uni ~ DefaultUni => ToBuiltinMeaning uni DefaultFun where {-# INLINE valueDataDenotation #-} in makeBuiltinMeaning valueDataDenotation - (runCostingFunOneArgument . unimplementedCostingFun) + (runCostingFunOneArgument . paramValueData) toBuiltinMeaning _semvar UnValueData = let unValueDataDenotation :: Data -> BuiltinResult Value @@ -2092,7 +2092,7 @@ instance uni ~ DefaultUni => ToBuiltinMeaning uni DefaultFun where {-# INLINE unValueDataDenotation #-} in makeBuiltinMeaning unValueDataDenotation - (runCostingFunOneArgument . unimplementedCostingFun) + (runCostingFunOneArgument . paramUnValueData) -- See Note [Inlining meanings of builtins]. {-# INLINE toBuiltinMeaning #-} From 1b2c9de3d1ad1a4639d48b1470a689adfaef9ae8 Mon Sep 17 00:00:00 2001 From: Yura Lazaryev Date: Wed, 24 Sep 2025 18:05:35 +0200 Subject: [PATCH 05/17] feat: add comprehensive benchmark data for Value operations Includes extensive benchmark results covering various input sizes and edge cases for lookupCoin, valueContains, valueData, and unValueData. Data validates the chosen statistical models and cost parameters. Provides empirical foundation confirming model accuracy across different operation profiles. --- .../cost-model/data/benching-conway.csv | 845 +++++++++++++----- 1 file changed, 645 insertions(+), 200 deletions(-) diff --git a/plutus-core/cost-model/data/benching-conway.csv b/plutus-core/cost-model/data/benching-conway.csv index e9f8f948ddd..876f5af946f 100644 --- a/plutus-core/cost-model/data/benching-conway.csv +++ b/plutus-core/cost-model/data/benching-conway.csv @@ -12094,203 +12094,648 @@ IndexArray/42/1,1.075506579052359e-6,1.0748433439930302e-6,1.0762684407023462e-6 IndexArray/46/1,1.0697135554442532e-6,1.0690902192698813e-6,1.0704133377013816e-6,2.2124820728450233e-9,1.8581237858977844e-9,2.6526943923047553e-9 IndexArray/98/1,1.0700747499373992e-6,1.0693842628239684e-6,1.070727062396803e-6,2.2506114869928674e-9,1.9376849028666025e-9,2.7564941558204088e-9 IndexArray/82/1,1.0755056682976695e-6,1.0750405368241111e-6,1.076102212770973e-6,1.8355219893844098e-9,1.5161640335164335e-9,2.4443625958006994e-9 -Bls12_381_G1_multiScalarMul/1/1,8.232134704712041e-5,8.228195390475752e-5,8.23582682466318e-5,1.224261187989977e-7,9.011720721178711e-8,1.843107342917502e-7 -Bls12_381_G1_multiScalarMul/2/2,1.5603352113689742e-4,1.5600025884754734e-4,1.56065185257734e-4,1.094394761986619e-7,8.779071446458298e-8,1.4947970533315267e-7 -Bls12_381_G1_multiScalarMul/3/3,1.939329666457593e-4,1.9388354851368188e-4,1.9402197408734082e-4,2.1995467058503616e-7,1.0779055620051168e-7,3.598144610846602e-7 -Bls12_381_G1_multiScalarMul/4/4,2.3193769861120354e-4,2.3185777330912127e-4,2.3201206490119206e-4,2.61940592999759e-7,2.2941719187582037e-7,3.077882579221989e-7 -Bls12_381_G1_multiScalarMul/5/5,2.7024485787950484e-4,2.701985832375676e-4,2.703562833994201e-4,2.504717874031756e-7,1.061103089376427e-7,4.5178956774050623e-7 -Bls12_381_G1_multiScalarMul/6/6,3.0832848017233854e-4,3.0828505860448953e-4,3.0841239554252326e-4,2.0081914026068556e-7,9.503560402226141e-8,3.348991421491274e-7 -Bls12_381_G1_multiScalarMul/7/7,3.453960291097332e-4,3.4529502000293173e-4,3.455551893661785e-4,4.503893151758501e-7,3.083661872443178e-7,7.81083043020636e-7 -Bls12_381_G1_multiScalarMul/8/8,3.832976511516978e-4,3.831399415816367e-4,3.8350168059661554e-4,6.425351357987778e-7,4.905809379814108e-7,9.901201715565621e-7 -Bls12_381_G1_multiScalarMul/9/9,4.208393675237262e-4,4.207594143609449e-4,4.209463240895972e-4,2.9714485369386276e-7,2.3487011012607412e-7,3.8965401426852136e-7 -Bls12_381_G1_multiScalarMul/10/10,4.590267934709921e-4,4.589529485523938e-4,4.5921225223072857e-4,3.674247719157326e-7,1.960955535102652e-7,6.745469596123421e-7 -Bls12_381_G1_multiScalarMul/11/11,4.97527732566443e-4,4.972281860134679e-4,4.986282302732426e-4,1.7151877711893442e-6,5.122548200854059e-7,3.5332096552138613e-6 -Bls12_381_G1_multiScalarMul/12/12,5.356509855658948e-4,5.355651207657092e-4,5.357300213867713e-4,2.869286988508056e-7,2.2118709297739587e-7,3.945684847893835e-7 -Bls12_381_G1_multiScalarMul/13/13,5.728512759489744e-4,5.726915276394053e-4,5.733007180741135e-4,8.949768255378629e-7,2.990100102556068e-7,1.799582591634419e-6 -Bls12_381_G1_multiScalarMul/14/14,6.102677458891477e-4,6.101406595840958e-4,6.104800133890259e-4,5.730641911125035e-7,4.2156110110763734e-7,9.874293144495503e-7 -Bls12_381_G1_multiScalarMul/15/15,6.477995208670887e-4,6.475756774649752e-4,6.480865282403314e-4,8.809829049973348e-7,7.579659277726546e-7,1.1589928070099792e-6 -Bls12_381_G1_multiScalarMul/16/16,7.10232795606239e-4,7.101357580525187e-4,7.103534690693274e-4,3.9630772993102876e-7,3.017996615312032e-7,6.065624023561599e-7 -Bls12_381_G1_multiScalarMul/17/17,7.482241201028533e-4,7.479063489174819e-4,7.493005226515e-4,1.7468995103377413e-6,4.207394233578458e-7,3.5919072692845237e-6 -Bls12_381_G1_multiScalarMul/18/18,7.705925934553824e-4,7.701144938606196e-4,7.727806329806679e-4,2.721631169491716e-6,7.981968678057562e-7,5.845417811648959e-6 -Bls12_381_G1_multiScalarMul/19/19,8.07991568665831e-4,8.078519602328661e-4,8.082935546448865e-4,6.822381786366707e-7,4.1123728418619586e-7,1.2817508134125719e-6 -Bls12_381_G1_multiScalarMul/20/20,8.305413129620952e-4,8.304197199200644e-4,8.306902645257076e-4,4.3666055013588826e-7,3.4850947949373826e-7,5.517969661861731e-7 -Bls12_381_G1_multiScalarMul/21/21,8.686137577309382e-4,8.683705360374326e-4,8.690514729472171e-4,1.0365305564754837e-6,6.15324072934707e-7,1.7554645846499009e-6 -Bls12_381_G1_multiScalarMul/22/22,8.91652773561559e-4,8.91448841424083e-4,8.919251447254486e-4,8.003760296748043e-7,5.948851969272322e-7,1.1100316085161068e-6 -Bls12_381_G1_multiScalarMul/23/23,9.294873328615929e-4,9.2931706336974e-4,9.29674543066649e-4,6.225406051789035e-7,4.744164895701269e-7,8.695237190578588e-7 -Bls12_381_G1_multiScalarMul/24/24,9.517388775125774e-4,9.51297780087541e-4,9.521482216169379e-4,1.3722719341729154e-6,1.062307342501858e-6,1.7843971621271001e-6 -Bls12_381_G1_multiScalarMul/25/25,9.886064604005137e-4,9.882251183807264e-4,9.897265063364012e-4,1.8798264902284367e-6,6.736369822886704e-7,3.814951405763071e-6 -Bls12_381_G1_multiScalarMul/26/26,1.0107695436644823e-3,1.0105299581864577e-3,1.0111683184415275e-3,9.824869954193735e-7,6.273786628516054e-7,1.789759844703243e-6 -Bls12_381_G1_multiScalarMul/27/27,1.0481752477344507e-3,1.0477770452434242e-3,1.0488436059663702e-3,1.70119074982601e-6,1.1033927625372998e-6,2.421859397722192e-6 -Bls12_381_G1_multiScalarMul/28/28,1.071199845880856e-3,1.0708432481182537e-3,1.0720804641719981e-3,1.6595833959304896e-6,8.543899072576939e-7,2.9475871714734805e-6 -Bls12_381_G1_multiScalarMul/29/29,1.1091453942723057e-3,1.1088806422385156e-3,1.1094556190265087e-3,9.884003711358195e-7,8.097303732520417e-7,1.3599340574873413e-6 -Bls12_381_G1_multiScalarMul/30/30,1.1316695694102287e-3,1.1314082924647447e-3,1.1319750321409226e-3,9.66367104215988e-7,7.685686878341102e-7,1.204378285010742e-6 -Bls12_381_G1_multiScalarMul/31/31,1.1706362298123296e-3,1.1701248243111372e-3,1.1713912110155227e-3,2.1219139874861063e-6,1.5567879843419155e-6,2.916931910163364e-6 -Bls12_381_G1_multiScalarMul/32/32,1.2183054885742289e-3,1.2178167501590653e-3,1.2191423331752846e-3,2.082314742656685e-6,1.3954922622922078e-6,3.3606861800964793e-6 -Bls12_381_G1_multiScalarMul/33/33,1.25554775700385e-3,1.2553212908295874e-3,1.256064024330601e-3,1.103995478961421e-6,6.577553035929982e-7,1.960982872144134e-6 -Bls12_381_G1_multiScalarMul/34/34,1.2814120185183533e-3,1.2811113200601465e-3,1.2817386977410077e-3,1.066328231240918e-6,8.498751061674896e-7,1.3581581158462333e-6 -Bls12_381_G1_multiScalarMul/35/35,1.3147784280299476e-3,1.3142019737646283e-3,1.3159148898431248e-3,2.7821602645732677e-6,1.2576600123958567e-6,4.71910870274486e-6 -Bls12_381_G1_multiScalarMul/36/36,1.3219048104980895e-3,1.3213844160889154e-3,1.3233093194833564e-3,2.6731627087817e-6,1.1691449038920677e-6,4.595666907784908e-6 -Bls12_381_G1_multiScalarMul/37/37,1.3589352301097773e-3,1.3587799204790097e-3,1.3590865392381088e-3,5.239660989144622e-7,4.210132126501093e-7,7.044936055207908e-7 -Bls12_381_G1_multiScalarMul/38/38,1.3842305731809087e-3,1.3838013940827385e-3,1.3851882129520007e-3,2.140116379547782e-6,1.1344089830602969e-6,4.3500220741287305e-6 -Bls12_381_G1_multiScalarMul/39/39,1.4193844818012396e-3,1.4188890128645811e-3,1.4206267802236144e-3,2.384279344480344e-6,1.286298194419277e-6,4.088466911461954e-6 -Bls12_381_G1_multiScalarMul/40/40,1.4275969257372889e-3,1.4266990139967814e-3,1.4296056424476227e-3,4.36532975493508e-6,2.6378910656369093e-6,7.81360464614563e-6 -Bls12_381_G1_multiScalarMul/41/41,1.4662734042718765e-3,1.4655915349289289e-3,1.4670583531661572e-3,2.5114188995059114e-6,2.0097342160937628e-6,3.247155614235915e-6 -Bls12_381_G1_multiScalarMul/42/42,1.4944060105751547e-3,1.493879150367226e-3,1.4952135866693312e-3,2.1205348113616285e-6,1.5093258926943527e-6,2.962889746140889e-6 -Bls12_381_G1_multiScalarMul/43/43,1.5276593205735154e-3,1.5273658668217916e-3,1.5279331130431386e-3,9.74498489934415e-7,7.482627424771116e-7,1.420616015176624e-6 -Bls12_381_G1_multiScalarMul/44/44,1.5353847806862466e-3,1.5346147866390108e-3,1.5363954193265963e-3,2.814562457758291e-6,2.1143530632424383e-6,3.821045577572284e-6 -Bls12_381_G1_multiScalarMul/45/45,1.5694620743296511e-3,1.5687635390181445e-3,1.57029874920667e-3,2.507144487167149e-6,2.0785255381527325e-6,3.0811759778156036e-6 -Bls12_381_G1_multiScalarMul/46/46,1.5907223707740364e-3,1.5893800235731621e-3,1.592471840103437e-3,5.178470382170926e-6,3.88044580623702e-6,6.694012070239517e-6 -Bls12_381_G1_multiScalarMul/47/47,1.628661974360063e-3,1.6283512846939465e-3,1.6291669828813618e-3,1.3671525674743757e-6,9.627490393739244e-7,2.0277210680304897e-6 -Bls12_381_G1_multiScalarMul/48/48,1.6361548091125416e-3,1.6357926793118167e-3,1.6366869716805837e-3,1.442057725476356e-6,1.0667638215275559e-6,2.1942788690677544e-6 -Bls12_381_G1_multiScalarMul/49/49,1.6779864698862684e-3,1.6774419144888844e-3,1.678564301607901e-3,1.9536763807617875e-6,1.5861735530685062e-6,2.9241156321278288e-6 -Bls12_381_G1_multiScalarMul/50/50,1.7052634275253997e-3,1.7041895762385994e-3,1.706524687220049e-3,3.84152102882327e-6,2.956410364369988e-6,4.951832103647607e-6 -Bls12_381_G1_multiScalarMul/51/51,1.7406739448052255e-3,1.739741519600114e-3,1.743488273211799e-3,4.901730860712033e-6,1.681687713060746e-6,9.63314624934489e-6 -Bls12_381_G1_multiScalarMul/52/52,1.7493504703501312e-3,1.7485291809717686e-3,1.7506247910129787e-3,3.6153633132872805e-6,2.6479825651733657e-6,5.832623352761088e-6 -Bls12_381_G1_multiScalarMul/53/53,1.7868267249247544e-3,1.786050505290007e-3,1.7882000160916365e-3,3.3230153222471118e-6,2.3257047340548217e-6,5.4135122168717275e-6 -Bls12_381_G1_multiScalarMul/54/54,1.8119093305955243e-3,1.8112017731004542e-3,1.8128745438316246e-3,2.9582354520945714e-6,2.0538396464527634e-6,4.974892599302226e-6 -Bls12_381_G1_multiScalarMul/55/55,1.84471674435397e-3,1.8442599600963505e-3,1.8452634559156386e-3,1.7601881093901428e-6,1.4750625737533917e-6,2.210525678689879e-6 -Bls12_381_G1_multiScalarMul/56/56,1.8550924625942802e-3,1.8544531007068019e-3,1.8564385668508347e-3,2.9780016999383592e-6,1.8191076732735432e-6,5.031379898838522e-6 -Bls12_381_G1_multiScalarMul/57/57,1.8950408145264643e-3,1.8939992827596826e-3,1.8961977234850831e-3,3.706120655598944e-6,2.9949347749033603e-6,4.641731171151639e-6 -Bls12_381_G1_multiScalarMul/58/58,1.9214190162986646e-3,1.9205644658902652e-3,1.9227436492195735e-3,3.7919868436730406e-6,2.5151125481564216e-6,5.528965031038841e-6 -Bls12_381_G1_multiScalarMul/59/59,1.95611884939017e-3,1.9555311058998062e-3,1.9567680207463758e-3,2.0724783716238652e-6,1.7915625799228621e-6,2.6388010558596374e-6 -Bls12_381_G1_multiScalarMul/60/60,1.9594365520224813e-3,1.958943767917802e-3,1.9600328304991543e-3,1.8565912278242626e-6,1.3182944308809232e-6,3.0498262686954687e-6 -Bls12_381_G1_multiScalarMul/61/61,1.9978785940453596e-3,1.9970364354546e-3,1.9988044814993563e-3,2.814765620751774e-6,2.215278427132277e-6,3.9079749949813176e-6 -Bls12_381_G1_multiScalarMul/62/62,2.025163972129198e-3,2.024292907473527e-3,2.026477198808721e-3,3.4328117679417816e-6,2.424532695157738e-6,4.901533766106334e-6 -Bls12_381_G1_multiScalarMul/63/63,2.0586979562927845e-3,2.057984455859352e-3,2.059909135640746e-3,3.1733556435024334e-6,1.9174464587367093e-6,5.2504225730683016e-6 -Bls12_381_G1_multiScalarMul/64/64,2.0900368436079005e-3,2.088028375590593e-3,2.0984775655780315e-3,1.1646874789686276e-5,3.4252094381705674e-6,2.554205960853732e-5 -Bls12_381_G1_multiScalarMul/65/65,1.8968147378605645e-3,1.8955310391900796e-3,1.898278206886905e-3,4.680707702478362e-6,3.6933847226616885e-6,6.782185825195487e-6 -Bls12_381_G1_multiScalarMul/66/66,1.915527316948408e-3,1.9151048085532891e-3,1.916079596378419e-3,1.652232700882608e-6,1.268984752321262e-6,2.218302657360697e-6 -Bls12_381_G1_multiScalarMul/67/67,1.939873715995447e-3,1.9390300141714943e-3,1.9415345431927143e-3,3.909637666223789e-6,2.4669716449410535e-6,6.3729495513604696e-6 -Bls12_381_G1_multiScalarMul/68/68,1.963955860876783e-3,1.9634908135732973e-3,1.9647235096952164e-3,1.9301982657436205e-6,1.331287045500568e-6,3.069218630466695e-6 -Bls12_381_G1_multiScalarMul/69/69,1.981736462216709e-3,1.9812744529486425e-3,1.982304257342455e-3,1.7179723192754665e-6,1.2576978196442669e-6,2.585535309310991e-6 -Bls12_381_G1_multiScalarMul/70/70,2.015096024360793e-3,2.013930296536576e-3,2.016550975850134e-3,4.183586924132327e-6,2.9592834069943323e-6,5.903222403671096e-6 -Bls12_381_G1_multiScalarMul/71/71,2.039593310853405e-3,2.039230558943095e-3,2.040135103696278e-3,1.517677057313753e-6,1.246493361769726e-6,1.8411731331069727e-6 -Bls12_381_G1_multiScalarMul/72/72,2.058111599882653e-3,2.057193666273917e-3,2.0594723408391942e-3,3.5844251775633503e-6,2.7202401005013457e-6,5.864305886696207e-6 -Bls12_381_G1_multiScalarMul/73/73,2.0934159227994436e-3,2.0906201835026532e-3,2.095693684947171e-3,8.491298188831756e-6,7.241167338179682e-6,1.0176406230578143e-5 -Bls12_381_G1_multiScalarMul/74/74,2.1291335834122513e-3,2.1278241958452133e-3,2.1299943701228743e-3,3.7951510816769475e-6,2.9761746545534362e-6,5.135763083938416e-6 -Bls12_381_G1_multiScalarMul/75/75,2.1496696746573056e-3,2.148587264452237e-3,2.1520893411774615e-3,5.214017226179326e-6,2.831700993722389e-6,9.897946072389741e-6 -Bls12_381_G1_multiScalarMul/76/76,2.1791297355152578e-3,2.1763917538151966e-3,2.1862885859611804e-3,1.3564060446508161e-5,5.983327115746122e-6,2.4308866464862185e-5 -Bls12_381_G1_multiScalarMul/77/77,2.181325091429973e-3,2.1807942464757432e-3,2.1818133665519207e-3,1.7039353205909792e-6,1.3786145694127499e-6,2.27968640731267e-6 -Bls12_381_G1_multiScalarMul/78/78,2.2165097719499824e-3,2.213684889701067e-3,2.219024702852442e-3,9.476092692961542e-6,6.898527736606062e-6,1.3202270738128961e-5 -Bls12_381_G1_multiScalarMul/79/79,2.2220017642692208e-3,2.221452887745163e-3,2.2226621102249605e-3,1.9668594276026276e-6,1.6059114512897864e-6,2.54873438507269e-6 -Bls12_381_G1_multiScalarMul/80/80,2.2649145692548805e-3,2.264315257045781e-3,2.2659321574184485e-3,2.6476167211476292e-6,1.8114591949521001e-6,4.5100102111080466e-6 -Bls12_381_G1_multiScalarMul/81/81,2.2815568928021565e-3,2.2809268030696116e-3,2.282682684357514e-3,2.6571578380668003e-6,1.7065827732222851e-6,4.487951031499547e-6 -Bls12_381_G1_multiScalarMul/82/82,2.310620963737306e-3,2.3090927285613193e-3,2.3126689982238035e-3,5.977435209471239e-6,4.4804403698017714e-6,8.09057887928092e-6 -Bls12_381_G1_multiScalarMul/83/83,2.336733472141597e-3,2.3360361666493012e-3,2.337632382036757e-3,2.560471483733304e-6,1.920620453068812e-6,3.7021660444619836e-6 -Bls12_381_G1_multiScalarMul/84/84,2.373268168042132e-3,2.371319876892892e-3,2.3766426567644805e-3,8.021527609000714e-6,4.830364162650037e-6,1.252095716980909e-5 -Bls12_381_G1_multiScalarMul/85/85,2.384876078524913e-3,2.383959246461071e-3,2.3867334229422466e-3,4.094196151783379e-6,2.3902100912772977e-6,6.961154738344854e-6 -Bls12_381_G1_multiScalarMul/86/86,2.410565039227443e-3,2.4084234057296094e-3,2.412268328550986e-3,6.65915218385595e-6,4.329988822432703e-6,1.0326826016055168e-5 -Bls12_381_G1_multiScalarMul/87/87,2.4297666625285345e-3,2.4270653907625746e-3,2.432196481389161e-3,8.58024905300566e-6,7.109703139729458e-6,1.0051366987525497e-5 -Bls12_381_G1_multiScalarMul/88/88,2.460570343151193e-3,2.459544035208346e-3,2.4615274058159917e-3,3.5198413136176365e-6,2.8384817517665127e-6,4.815807097623251e-6 -Bls12_381_G1_multiScalarMul/89/89,2.489853458509472e-3,2.48760518697685e-3,2.491311540051355e-3,6.19046891378905e-6,4.307330671671395e-6,7.986452835536224e-6 -Bls12_381_G1_multiScalarMul/90/90,2.518729619807173e-3,2.5175955675903593e-3,2.5197557395444242e-3,3.6740724105737384e-6,3.011297773639394e-6,4.579753037221892e-6 -Bls12_381_G1_multiScalarMul/91/91,2.507346287557815e-3,2.5048432606199636e-3,2.5101409467740204e-3,9.127067962491492e-6,7.736890525902875e-6,1.0224347243298884e-5 -Bls12_381_G1_multiScalarMul/92/92,2.5623659852219262e-3,2.5612024891175753e-3,2.564829446827521e-3,5.6507070170772565e-6,3.2998574451510087e-6,9.57583819470183e-6 -Bls12_381_G1_multiScalarMul/93/93,2.5847869535442504e-3,2.5837480732719756e-3,2.5860413313409e-3,3.848008008883357e-6,3.135969999546864e-6,4.874051925178418e-6 -Bls12_381_G1_multiScalarMul/94/94,2.6234813638524954e-3,2.6221188936467322e-3,2.627015683950028e-3,6.9065042519955485e-6,3.5404891910020863e-6,1.266990728387938e-5 -Bls12_381_G1_multiScalarMul/95/95,2.642628219940988e-3,2.641768011136227e-3,2.6442054118635916e-3,3.6007375940600177e-6,2.2125834942189697e-6,6.234015624110293e-6 -Bls12_381_G1_multiScalarMul/96/96,2.6601519782021863e-3,2.6585725995916932e-3,2.6631507793169816e-3,7.137222035771094e-6,4.623560832534806e-6,1.2950373021381417e-5 -Bls12_381_G1_multiScalarMul/97/97,2.681023460582192e-3,2.679568015031102e-3,2.683278541155578e-3,5.991522440852137e-6,3.858505228846451e-6,8.60021764374252e-6 -Bls12_381_G1_multiScalarMul/98/98,2.7083684530633586e-3,2.70727640883435e-3,2.7110584196105647e-3,5.013062986030381e-6,2.3597699562053853e-6,1.002284515969446e-5 -Bls12_381_G1_multiScalarMul/99/99,2.7213371259787855e-3,2.720704088882147e-3,2.722244079978909e-3,2.444787958433492e-6,1.793699194794548e-6,3.7994420578130953e-6 -Bls12_381_G1_multiScalarMul/100/100,2.7642727676665296e-3,2.763395576301587e-3,2.7675024929907544e-3,4.726547836308982e-6,1.8913959977112497e-6,1.0025613006686808e-5 -Bls12_381_G2_multiScalarMul/1/1,1.6266495442804972e-4,1.6264736086074068e-4,1.6270124805713648e-4,7.793865350083726e-8,4.635475091813956e-8,1.4247066440608091e-7 -Bls12_381_G2_multiScalarMul/2/2,3.543638522088684e-4,3.541772068342348e-4,3.5485931188723925e-4,9.360391344324354e-7,3.4976363756994914e-7,1.8211931894900913e-6 -Bls12_381_G2_multiScalarMul/3/3,4.47702794969825e-4,4.475045705500375e-4,4.478850505015342e-4,6.493823174661071e-7,3.5878763258263287e-7,1.0803507174684568e-6 -Bls12_381_G2_multiScalarMul/4/4,5.420723557652644e-4,5.417274673810824e-4,5.426125367479333e-4,1.4301753976362207e-6,9.988141199987564e-7,2.267296520674632e-6 -Bls12_381_G2_multiScalarMul/5/5,6.370512849618329e-4,6.36900784787239e-4,6.37202712666071e-4,5.292403814549932e-7,4.022430073091077e-7,7.556842750685239e-7 -Bls12_381_G2_multiScalarMul/6/6,7.310526489754525e-4,7.30629670999753e-4,7.317446144730351e-4,1.8119026166925256e-6,1.1454709674089216e-6,3.3632913939344345e-6 -Bls12_381_G2_multiScalarMul/7/7,8.236776396240537e-4,8.233271514827839e-4,8.241067273174465e-4,1.3657308675882766e-6,1.0410102352442255e-6,1.83210797347741e-6 -Bls12_381_G2_multiScalarMul/8/8,9.197543555033109e-4,9.189658738224084e-4,9.209830008370004e-4,3.3412724036424652e-6,2.3248417111070747e-6,5.070176355554298e-6 -Bls12_381_G2_multiScalarMul/9/9,1.011991406751168e-3,1.0117382842987513e-3,1.012512156595354e-3,1.1429892811506008e-6,7.64572284352035e-7,1.824620728201617e-6 -Bls12_381_G2_multiScalarMul/10/10,1.109394930774612e-3,1.1087682317862343e-3,1.1115776119988174e-3,3.4944409285465694e-6,1.0503647842087067e-6,7.149880658627584e-6 -Bls12_381_G2_multiScalarMul/11/11,1.2023934491440338e-3,1.202171934481395e-3,1.2026423197250766e-3,7.922161025400925e-7,6.258416318073706e-7,1.029606114863458e-6 -Bls12_381_G2_multiScalarMul/12/12,1.2963025275871496e-3,1.2952163686698916e-3,1.2983463505741011e-3,4.960268500618734e-6,2.845337116066531e-6,9.687158836086103e-6 -Bls12_381_G2_multiScalarMul/13/13,1.3869285962502872e-3,1.3866231292243125e-3,1.3872893550098244e-3,1.1726919062774188e-6,8.791906263916984e-7,1.5913921990012086e-6 -Bls12_381_G2_multiScalarMul/14/14,1.4823956781971994e-3,1.4815973050589385e-3,1.4842137535372652e-3,3.760848566094728e-6,2.472183908899497e-6,6.4465275732684205e-6 -Bls12_381_G2_multiScalarMul/15/15,1.574445631700049e-3,1.574063788581931e-3,1.5749578982368424e-3,1.443263633319882e-6,1.0628032736563463e-6,2.1565979694667185e-6 -Bls12_381_G2_multiScalarMul/16/16,1.5000875796284717e-3,1.4994665426513504e-3,1.5014717203342867e-3,2.802372121079838e-6,1.7676048441935653e-6,4.644089354729122e-6 -Bls12_381_G2_multiScalarMul/17/17,1.5940905703219718e-3,1.5936217521556593e-3,1.5945282467814278e-3,1.547468548627245e-6,1.1967489868918594e-6,2.082313772097416e-6 -Bls12_381_G2_multiScalarMul/18/18,1.6481937447323397e-3,1.6471788901492087e-3,1.6502528733967521e-3,4.67746155264807e-6,2.5560426788421386e-6,8.493562555710135e-6 -Bls12_381_G2_multiScalarMul/19/19,1.7408620063694292e-3,1.7403685953485991e-3,1.7416086573762834e-3,2.034339176777199e-6,1.5411497874186401e-6,2.888074021221646e-6 -Bls12_381_G2_multiScalarMul/20/20,1.7983360168952664e-3,1.7968063959178204e-3,1.8007319622437476e-3,6.701452941660098e-6,3.915890097926392e-6,1.1565951790899295e-5 -Bls12_381_G2_multiScalarMul/21/21,1.8948751419094719e-3,1.8943849272806152e-3,1.8954945505194202e-3,1.8264677812158936e-6,1.5180676580123575e-6,2.3043238795090236e-6 -Bls12_381_G2_multiScalarMul/22/22,1.9483638492318052e-3,1.9468479306608071e-3,1.952898337552636e-3,8.246725685061966e-6,2.916390890917488e-6,1.6554460898097785e-5 -Bls12_381_G2_multiScalarMul/23/23,2.0441566797094976e-3,2.0436200484617298e-3,2.0448120935495366e-3,1.9807680962425035e-6,1.4047597581205637e-6,2.861374149657612e-6 -Bls12_381_G2_multiScalarMul/24/24,2.0976111797810742e-3,2.0969141362790775e-3,2.0983042002160226e-3,2.294409781298406e-6,1.7816482691771947e-6,3.2363169164003804e-6 -Bls12_381_G2_multiScalarMul/25/25,2.1916934430134647e-3,2.1911766683971054e-3,2.192454586070339e-3,2.0791512216562315e-6,1.5171229138063835e-6,2.812518408756342e-6 -Bls12_381_G2_multiScalarMul/26/26,2.2452874242475463e-3,2.2438224649193378e-3,2.248020575104657e-3,6.546744756250407e-6,4.224171258471438e-6,1.1357661995132573e-5 -Bls12_381_G2_multiScalarMul/27/27,2.3342313432099604e-3,2.3334417036587492e-3,2.335903802244924e-3,3.7924501525196913e-6,2.084116468653706e-6,6.745286115407234e-6 -Bls12_381_G2_multiScalarMul/28/28,2.3924196934986424e-3,2.3905980952149135e-3,2.39744572554579e-3,9.270395166568168e-6,3.857502451986574e-6,1.8266974876360255e-5 -Bls12_381_G2_multiScalarMul/29/29,2.4921574096234654e-3,2.4911465295363233e-3,2.4951214940058244e-3,5.209897620887097e-6,2.3932366963378704e-6,1.007979235143704e-5 -Bls12_381_G2_multiScalarMul/30/30,2.5442112572946624e-3,2.5431826880834667e-3,2.5479216241766365e-3,5.7374902589030385e-6,2.166916577225313e-6,1.24589648550128e-5 -Bls12_381_G2_multiScalarMul/31/31,2.6387551082366705e-3,2.6380466280120883e-3,2.6396291501284983e-3,2.5285910565402825e-6,2.0132127254936795e-6,3.4207259760745164e-6 -Bls12_381_G2_multiScalarMul/32/32,2.5150931462186196e-3,2.513387917297599e-3,2.5181977065017046e-3,7.657009385145557e-6,4.5131093648664805e-6,1.3678490989164753e-5 -Bls12_381_G2_multiScalarMul/33/33,3.0889519233376545e-3,3.0883882511648234e-3,3.089672507460859e-3,2.0979675388899346e-6,1.603912694016453e-6,3.0603682324660857e-6 -Bls12_381_G2_multiScalarMul/34/34,3.16771726298734e-3,3.16501045273763e-3,3.172197179196162e-3,1.0825021580641719e-5,6.671829453430046e-6,1.8892794609350383e-5 -Bls12_381_G2_multiScalarMul/35/35,3.2525975758965855e-3,3.251923568635943e-3,3.2534974414252724e-3,2.3923622222660625e-6,1.771511114169158e-6,3.613237863752478e-6 -Bls12_381_G2_multiScalarMul/36/36,3.336138244007564e-3,3.333789111955089e-3,3.344298373821e-3,1.3359645865766898e-5,3.2128822247268738e-6,2.7638521011789944e-5 -Bls12_381_G2_multiScalarMul/37/37,3.4191138605455746e-3,3.4179135859041592e-3,3.4233605791000876e-3,6.592098823336916e-6,2.5157731785295883e-6,1.3141627481895897e-5 -Bls12_381_G2_multiScalarMul/38/38,3.4883584083644226e-3,3.4862131678210493e-3,3.4925344207942677e-3,9.623236210916872e-6,5.191214954965976e-6,1.7597405473000066e-5 -Bls12_381_G2_multiScalarMul/39/39,3.530386408142463e-3,3.5295959082416793e-3,3.531411239014294e-3,2.79677085673492e-6,2.1274732913274754e-6,3.925571150385237e-6 -Bls12_381_G2_multiScalarMul/40/40,3.6147002382323538e-3,3.611572624230025e-3,3.6292011188412323e-3,1.7990113412185996e-5,2.845513840934602e-6,4.043993566101094e-5 -Bls12_381_G2_multiScalarMul/41/41,3.672723290652948e-3,3.6718602367145966e-3,3.673688181816288e-3,2.84241014465167e-6,2.3021696308807956e-6,3.7655879313695054e-6 -Bls12_381_G2_multiScalarMul/42/42,3.793747136886243e-3,3.78926839608175e-3,3.809348971725428e-3,2.269174801044769e-5,4.7237643544819555e-6,4.9663768681186095e-5 -Bls12_381_G2_multiScalarMul/43/43,3.877862027839689e-3,3.876819161298888e-3,3.8794572953528964e-3,4.162065327624179e-6,3.2714009413120982e-6,5.1550470389566275e-6 -Bls12_381_G2_multiScalarMul/44/44,3.965116399895544e-3,3.962804992549213e-3,3.97345386215166e-3,1.3112609308794646e-5,1.8812805162759533e-6,2.7437540345266834e-5 -Bls12_381_G2_multiScalarMul/45/45,4.004527665871219e-3,4.003216183025186e-3,4.00656406563525e-3,5.2564769639065946e-6,2.696936689436533e-6,7.823236463877045e-6 -Bls12_381_G2_multiScalarMul/46/46,4.076804027301204e-3,4.074764849350912e-3,4.082954370562564e-3,1.0195134478551572e-5,3.59758066050906e-6,2.02607321633781e-5 -Bls12_381_G2_multiScalarMul/47/47,4.167774429892586e-3,4.1666246852367335e-3,4.169331500283441e-3,4.095651022675052e-6,3.1833448207887804e-6,5.089866484578962e-6 -Bls12_381_G2_multiScalarMul/48/48,4.2249981616795705e-3,4.222778156184377e-3,4.226612496226903e-3,5.7784805597787715e-6,4.4339723066230185e-6,7.3377180823161815e-6 -Bls12_381_G2_multiScalarMul/49/49,4.3524164098415665e-3,4.351263723172645e-3,4.353648896076485e-3,3.7577346495739375e-6,3.092141280492094e-6,4.52320031610404e-6 -Bls12_381_G2_multiScalarMul/50/50,4.343123429888507e-3,4.341239145934485e-3,4.345694580031099e-3,7.032494846534855e-6,5.430307563910816e-6,1.0261289957428346e-5 -Bls12_381_G2_multiScalarMul/51/51,4.484856489477111e-3,4.481774784858851e-3,4.487312713793393e-3,8.158820364283e-6,6.798014601558509e-6,1.086960763925229e-5 -Bls12_381_G2_multiScalarMul/52/52,4.546562051796544e-3,4.5455748661040974e-3,4.548037932926745e-3,3.6580687673211806e-6,2.8901424834133615e-6,5.219822997121614e-6 -Bls12_381_G2_multiScalarMul/53/53,4.654474034299822e-3,4.65318130717014e-3,4.655917064534823e-3,4.116466278137667e-6,3.166891661793465e-6,5.567941155062992e-6 -Bls12_381_G2_multiScalarMul/54/54,4.721927123629685e-3,4.72071287904244e-3,4.723138528981887e-3,3.94193309418702e-6,3.113913371425901e-6,5.136276379939376e-6 -Bls12_381_G2_multiScalarMul/55/55,4.795039804834155e-3,4.793771853613166e-3,4.796041252525426e-3,3.523502774916879e-6,2.8612449092910447e-6,4.464716550457647e-6 -Bls12_381_G2_multiScalarMul/56/56,4.864016888196152e-3,4.862934237209827e-3,4.865878015473469e-3,4.339172192062833e-6,3.120561122208654e-6,7.091594219853984e-6 -Bls12_381_G2_multiScalarMul/57/57,4.930026691468103e-3,4.928660811034607e-3,4.93184431837138e-3,4.92694965505342e-6,3.631274655946987e-6,6.916774799932921e-6 -Bls12_381_G2_multiScalarMul/58/58,4.999478205962443e-3,4.996476656269146e-3,5.002509748355277e-3,9.65312271848907e-6,8.212314993018033e-6,1.121977177338798e-5 -Bls12_381_G2_multiScalarMul/59/59,5.109930645097379e-3,5.108695300209485e-3,5.111720735214837e-3,4.307666456047917e-6,3.2036925396243358e-6,7.010008721447832e-6 -Bls12_381_G2_multiScalarMul/60/60,5.182636587074396e-3,5.1812215576612815e-3,5.184867458236281e-3,5.045266958501895e-6,3.3630808719106254e-6,7.598293873580799e-6 -Bls12_381_G2_multiScalarMul/61/61,5.261201467559662e-3,5.259483119610097e-3,5.2651003452464235e-3,6.794062799442452e-6,3.965079449462158e-6,1.2745803244159386e-5 -Bls12_381_G2_multiScalarMul/62/62,5.355085149782543e-3,5.353521974098854e-3,5.3568364980710005e-3,5.127106845655141e-6,3.956280257430231e-6,6.764557833667277e-6 -Bls12_381_G2_multiScalarMul/63/63,5.404870448491742e-3,5.401124837066587e-3,5.407497875504651e-3,8.934660522629549e-6,6.290321430881255e-6,1.2732030907646999e-5 -Bls12_381_G2_multiScalarMul/64/64,4.8782659702195615e-3,4.876660673660171e-3,4.8804522014555e-3,5.830661634910927e-6,3.955325665036216e-6,9.38894371358523e-6 -Bls12_381_G2_multiScalarMul/65/65,4.9061548862185346e-3,4.904813116841975e-3,4.9086495754739915e-3,5.295424246670201e-6,3.7451476035762403e-6,8.334611829514347e-6 -Bls12_381_G2_multiScalarMul/66/66,4.967076866858588e-3,4.96587704975757e-3,4.970208209096129e-3,5.500738791485448e-6,2.7782883129256445e-6,1.0490016182322088e-5 -Bls12_381_G2_multiScalarMul/67/67,5.0384188004806525e-3,5.036297660856063e-3,5.040874280488966e-3,7.20767347691469e-6,5.18593994354578e-6,1.1000885848108839e-5 -Bls12_381_G2_multiScalarMul/68/68,5.082679596088205e-3,5.081788191855941e-3,5.083677026915687e-3,2.9879915262955836e-6,2.402250840802348e-6,3.7388441162211205e-6 -Bls12_381_G2_multiScalarMul/69/69,5.131805217231941e-3,5.129945152668336e-3,5.134860292773551e-3,7.121015258734736e-6,4.754387036952524e-6,1.0407485911539298e-5 -Bls12_381_G2_multiScalarMul/70/70,5.223131098010917e-3,5.220270707999523e-3,5.226515783222153e-3,9.515319707834862e-6,7.924704664502419e-6,1.197266014225403e-5 -Bls12_381_G2_multiScalarMul/71/71,5.2882851289316885e-3,5.286944845429294e-3,5.2901838154393414e-3,4.850407193371409e-6,3.951323934404944e-6,6.909977742394703e-6 -Bls12_381_G2_multiScalarMul/72/72,5.31973147751225e-3,5.318376432387295e-3,5.32119875028863e-3,4.277946466566538e-6,3.32076690250808e-6,5.635737244144887e-6 -Bls12_381_G2_multiScalarMul/73/73,5.415258160623588e-3,5.413782714872596e-3,5.416918547393203e-3,4.874528900097905e-6,4.170514576006458e-6,5.848559988534025e-6 -Bls12_381_G2_multiScalarMul/74/74,5.504234496008557e-3,5.500576962955019e-3,5.508481864691515e-3,1.1590261990431737e-5,7.963644443790475e-6,2.0109944098147845e-5 -Bls12_381_G2_multiScalarMul/75/75,5.564079990869667e-3,5.562681956747252e-3,5.56567336402758e-3,4.352958051265566e-6,3.4422969438156352e-6,6.286896453598817e-6 -Bls12_381_G2_multiScalarMul/76/76,5.636188875483629e-3,5.63517382713922e-3,5.637553743099741e-3,3.670518446053137e-6,2.6204373559816722e-6,5.576211218482488e-6 -Bls12_381_G2_multiScalarMul/77/77,5.653980663508052e-3,5.652296820298524e-3,5.657670797268361e-3,7.080543955082813e-6,3.7855994178883683e-6,1.2879875104746403e-5 -Bls12_381_G2_multiScalarMul/78/78,5.740407480489808e-3,5.7391493805168635e-3,5.7418065167963e-3,3.904427361041286e-6,3.074226799333372e-6,5.442029866027754e-6 -Bls12_381_G2_multiScalarMul/79/79,5.751010900543999e-3,5.748323596643336e-3,5.754728295889315e-3,9.270531833024517e-6,6.035547009683968e-6,1.4379971767424256e-5 -Bls12_381_G2_multiScalarMul/80/80,5.858800364486109e-3,5.857269600819101e-3,5.860372363714095e-3,4.878855487808653e-6,3.7581767493947793e-6,6.996843420054578e-6 -Bls12_381_G2_multiScalarMul/81/81,5.896817994473183e-3,5.894063205963552e-3,5.902366128185444e-3,1.1536253196991757e-5,6.383910727541163e-6,2.0982102749864474e-5 -Bls12_381_G2_multiScalarMul/82/82,5.954935473178033e-3,5.953063910957776e-3,5.957530288931881e-3,6.253389324766823e-6,4.779351132702418e-6,7.979956410106285e-6 -Bls12_381_G2_multiScalarMul/83/83,6.0161468367483225e-3,6.013693044072133e-3,6.02177468728205e-3,1.0835798229125257e-5,6.207595030876202e-6,1.9548081431230584e-5 -Bls12_381_G2_multiScalarMul/84/84,6.094614704088679e-3,6.092574358893842e-3,6.0971100378228475e-3,6.666176870479611e-6,5.145944335262237e-6,8.274826825353507e-6 -Bls12_381_G2_multiScalarMul/85/85,6.1380376895836565e-3,6.133725428191463e-3,6.145329879147275e-3,1.626622922741078e-5,1.0821722335694483e-5,2.700730631296616e-5 -Bls12_381_G2_multiScalarMul/86/86,6.2140860516838245e-3,6.212851863373451e-3,6.215546358212723e-3,4.0395006569626435e-6,3.346822769756149e-6,4.7839437803151336e-6 -Bls12_381_G2_multiScalarMul/87/87,6.27302455453059e-3,6.270885529060964e-3,6.275809157451918e-3,6.999595649144767e-6,4.947819532780126e-6,1.0251538631768462e-5 -Bls12_381_G2_multiScalarMul/88/88,6.3404523682942995e-3,6.338680115532713e-3,6.3420519237891515e-3,5.208923709646363e-6,4.108671865132737e-6,6.370714767856116e-6 -Bls12_381_G2_multiScalarMul/89/89,6.410017615442629e-3,6.406159123069732e-3,6.41315635661642e-3,1.0622224787961102e-5,7.696172865576866e-6,1.3963076368862973e-5 -Bls12_381_G2_multiScalarMul/90/90,6.481791869329977e-3,6.479839995502555e-3,6.484276415426917e-3,6.258729255672214e-6,4.848352706810262e-6,7.988412553980431e-6 -Bls12_381_G2_multiScalarMul/91/91,6.475168018503552e-3,6.470179709488667e-3,6.483048340856914e-3,1.7646142713249933e-5,1.3097969794456097e-5,2.6957602312106938e-5 -Bls12_381_G2_multiScalarMul/92/92,6.569285931833285e-3,6.566882844069322e-3,6.574172843329704e-3,9.752702509029438e-6,5.6501870652183995e-6,1.6741066006979055e-5 -Bls12_381_G2_multiScalarMul/93/93,6.629457299321055e-3,6.625183482996535e-3,6.638841711503604e-3,1.7538389603216873e-5,1.0528950637309035e-5,3.0379658274480686e-5 -Bls12_381_G2_multiScalarMul/94/94,6.7320607492387515e-3,6.730167903973191e-3,6.736598035759103e-3,8.15218783569633e-6,3.741189882233103e-6,1.6185222568739163e-5 -Bls12_381_G2_multiScalarMul/95/95,6.801145393237103e-3,6.796607904593793e-3,6.8137432062137055e-3,1.9691935909923513e-5,7.536520887751789e-6,3.768941248607555e-5 -Bls12_381_G2_multiScalarMul/96/96,6.821360358060845e-3,6.816810519501433e-3,6.829564504014655e-3,1.6752380908242913e-5,1.0237675196995415e-5,3.083226102494789e-5 -Bls12_381_G2_multiScalarMul/97/97,6.90522012785712e-3,6.901544208299667e-3,6.918761450372084e-3,1.7088371694161855e-5,5.773286197099474e-6,3.643360035316389e-5 -Bls12_381_G2_multiScalarMul/98/98,6.9597205589059085e-3,6.9554579231546464e-3,6.963825444927238e-3,1.230537047747648e-5,9.828399035508776e-6,1.581113740579338e-5 -Bls12_381_G2_multiScalarMul/99/99,6.998605748330429e-3,6.993956045528542e-3,7.003564931628933e-3,1.3941888558415054e-5,1.1848281516892752e-5,1.8598404587423643e-5 -Bls12_381_G2_multiScalarMul/100/100,7.090569654857228e-3,7.08876305884669e-3,7.093035056145744e-3,6.187076669186285e-6,4.689206191622249e-6,8.297705725121281e-6 +Bls12_381_G1_multiScalarMul/1/1,8.232134704712041e-5,8.228195390475752e-5,8.23582682466318e-5,1.224261187989977e-7,9.011720721178711e-8,1.843107342917502e-7 +Bls12_381_G1_multiScalarMul/2/2,1.5603352113689742e-4,1.5600025884754734e-4,1.56065185257734e-4,1.094394761986619e-7,8.779071446458298e-8,1.4947970533315267e-7 +Bls12_381_G1_multiScalarMul/3/3,1.939329666457593e-4,1.9388354851368188e-4,1.9402197408734082e-4,2.1995467058503616e-7,1.0779055620051168e-7,3.598144610846602e-7 +Bls12_381_G1_multiScalarMul/4/4,2.3193769861120354e-4,2.3185777330912127e-4,2.3201206490119206e-4,2.61940592999759e-7,2.2941719187582037e-7,3.077882579221989e-7 +Bls12_381_G1_multiScalarMul/5/5,2.7024485787950484e-4,2.701985832375676e-4,2.703562833994201e-4,2.504717874031756e-7,1.061103089376427e-7,4.5178956774050623e-7 +Bls12_381_G1_multiScalarMul/6/6,3.0832848017233854e-4,3.0828505860448953e-4,3.0841239554252326e-4,2.0081914026068556e-7,9.503560402226141e-8,3.348991421491274e-7 +Bls12_381_G1_multiScalarMul/7/7,3.453960291097332e-4,3.4529502000293173e-4,3.455551893661785e-4,4.503893151758501e-7,3.083661872443178e-7,7.81083043020636e-7 +Bls12_381_G1_multiScalarMul/8/8,3.832976511516978e-4,3.831399415816367e-4,3.8350168059661554e-4,6.425351357987778e-7,4.905809379814108e-7,9.901201715565621e-7 +Bls12_381_G1_multiScalarMul/9/9,4.208393675237262e-4,4.207594143609449e-4,4.209463240895972e-4,2.9714485369386276e-7,2.3487011012607412e-7,3.8965401426852136e-7 +Bls12_381_G1_multiScalarMul/10/10,4.590267934709921e-4,4.589529485523938e-4,4.5921225223072857e-4,3.674247719157326e-7,1.960955535102652e-7,6.745469596123421e-7 +Bls12_381_G1_multiScalarMul/11/11,4.97527732566443e-4,4.972281860134679e-4,4.986282302732426e-4,1.7151877711893442e-6,5.122548200854059e-7,3.5332096552138613e-6 +Bls12_381_G1_multiScalarMul/12/12,5.356509855658948e-4,5.355651207657092e-4,5.357300213867713e-4,2.869286988508056e-7,2.2118709297739587e-7,3.945684847893835e-7 +Bls12_381_G1_multiScalarMul/13/13,5.728512759489744e-4,5.726915276394053e-4,5.733007180741135e-4,8.949768255378629e-7,2.990100102556068e-7,1.799582591634419e-6 +Bls12_381_G1_multiScalarMul/14/14,6.102677458891477e-4,6.101406595840958e-4,6.104800133890259e-4,5.730641911125035e-7,4.2156110110763734e-7,9.874293144495503e-7 +Bls12_381_G1_multiScalarMul/15/15,6.477995208670887e-4,6.475756774649752e-4,6.480865282403314e-4,8.809829049973348e-7,7.579659277726546e-7,1.1589928070099792e-6 +Bls12_381_G1_multiScalarMul/16/16,7.10232795606239e-4,7.101357580525187e-4,7.103534690693274e-4,3.9630772993102876e-7,3.017996615312032e-7,6.065624023561599e-7 +Bls12_381_G1_multiScalarMul/17/17,7.482241201028533e-4,7.479063489174819e-4,7.493005226515e-4,1.7468995103377413e-6,4.207394233578458e-7,3.5919072692845237e-6 +Bls12_381_G1_multiScalarMul/18/18,7.705925934553824e-4,7.701144938606196e-4,7.727806329806679e-4,2.721631169491716e-6,7.981968678057562e-7,5.845417811648959e-6 +Bls12_381_G1_multiScalarMul/19/19,8.07991568665831e-4,8.078519602328661e-4,8.082935546448865e-4,6.822381786366707e-7,4.1123728418619586e-7,1.2817508134125719e-6 +Bls12_381_G1_multiScalarMul/20/20,8.305413129620952e-4,8.304197199200644e-4,8.306902645257076e-4,4.3666055013588826e-7,3.4850947949373826e-7,5.517969661861731e-7 +Bls12_381_G1_multiScalarMul/21/21,8.686137577309382e-4,8.683705360374326e-4,8.690514729472171e-4,1.0365305564754837e-6,6.15324072934707e-7,1.7554645846499009e-6 +Bls12_381_G1_multiScalarMul/22/22,8.91652773561559e-4,8.91448841424083e-4,8.919251447254486e-4,8.003760296748043e-7,5.948851969272322e-7,1.1100316085161068e-6 +Bls12_381_G1_multiScalarMul/23/23,9.294873328615929e-4,9.2931706336974e-4,9.29674543066649e-4,6.225406051789035e-7,4.744164895701269e-7,8.695237190578588e-7 +Bls12_381_G1_multiScalarMul/24/24,9.517388775125774e-4,9.51297780087541e-4,9.521482216169379e-4,1.3722719341729154e-6,1.062307342501858e-6,1.7843971621271001e-6 +Bls12_381_G1_multiScalarMul/25/25,9.886064604005137e-4,9.882251183807264e-4,9.897265063364012e-4,1.8798264902284367e-6,6.736369822886704e-7,3.814951405763071e-6 +Bls12_381_G1_multiScalarMul/26/26,1.0107695436644823e-3,1.0105299581864577e-3,1.0111683184415275e-3,9.824869954193735e-7,6.273786628516054e-7,1.789759844703243e-6 +Bls12_381_G1_multiScalarMul/27/27,1.0481752477344507e-3,1.0477770452434242e-3,1.0488436059663702e-3,1.70119074982601e-6,1.1033927625372998e-6,2.421859397722192e-6 +Bls12_381_G1_multiScalarMul/28/28,1.071199845880856e-3,1.0708432481182537e-3,1.0720804641719981e-3,1.6595833959304896e-6,8.543899072576939e-7,2.9475871714734805e-6 +Bls12_381_G1_multiScalarMul/29/29,1.1091453942723057e-3,1.1088806422385156e-3,1.1094556190265087e-3,9.884003711358195e-7,8.097303732520417e-7,1.3599340574873413e-6 +Bls12_381_G1_multiScalarMul/30/30,1.1316695694102287e-3,1.1314082924647447e-3,1.1319750321409226e-3,9.66367104215988e-7,7.685686878341102e-7,1.204378285010742e-6 +Bls12_381_G1_multiScalarMul/31/31,1.1706362298123296e-3,1.1701248243111372e-3,1.1713912110155227e-3,2.1219139874861063e-6,1.5567879843419155e-6,2.916931910163364e-6 +Bls12_381_G1_multiScalarMul/32/32,1.2183054885742289e-3,1.2178167501590653e-3,1.2191423331752846e-3,2.082314742656685e-6,1.3954922622922078e-6,3.3606861800964793e-6 +Bls12_381_G1_multiScalarMul/33/33,1.25554775700385e-3,1.2553212908295874e-3,1.256064024330601e-3,1.103995478961421e-6,6.577553035929982e-7,1.960982872144134e-6 +Bls12_381_G1_multiScalarMul/34/34,1.2814120185183533e-3,1.2811113200601465e-3,1.2817386977410077e-3,1.066328231240918e-6,8.498751061674896e-7,1.3581581158462333e-6 +Bls12_381_G1_multiScalarMul/35/35,1.3147784280299476e-3,1.3142019737646283e-3,1.3159148898431248e-3,2.7821602645732677e-6,1.2576600123958567e-6,4.71910870274486e-6 +Bls12_381_G1_multiScalarMul/36/36,1.3219048104980895e-3,1.3213844160889154e-3,1.3233093194833564e-3,2.6731627087817e-6,1.1691449038920677e-6,4.595666907784908e-6 +Bls12_381_G1_multiScalarMul/37/37,1.3589352301097773e-3,1.3587799204790097e-3,1.3590865392381088e-3,5.239660989144622e-7,4.210132126501093e-7,7.044936055207908e-7 +Bls12_381_G1_multiScalarMul/38/38,1.3842305731809087e-3,1.3838013940827385e-3,1.3851882129520007e-3,2.140116379547782e-6,1.1344089830602969e-6,4.3500220741287305e-6 +Bls12_381_G1_multiScalarMul/39/39,1.4193844818012396e-3,1.4188890128645811e-3,1.4206267802236144e-3,2.384279344480344e-6,1.286298194419277e-6,4.088466911461954e-6 +Bls12_381_G1_multiScalarMul/40/40,1.4275969257372889e-3,1.4266990139967814e-3,1.4296056424476227e-3,4.36532975493508e-6,2.6378910656369093e-6,7.81360464614563e-6 +Bls12_381_G1_multiScalarMul/41/41,1.4662734042718765e-3,1.4655915349289289e-3,1.4670583531661572e-3,2.5114188995059114e-6,2.0097342160937628e-6,3.247155614235915e-6 +Bls12_381_G1_multiScalarMul/42/42,1.4944060105751547e-3,1.493879150367226e-3,1.4952135866693312e-3,2.1205348113616285e-6,1.5093258926943527e-6,2.962889746140889e-6 +Bls12_381_G1_multiScalarMul/43/43,1.5276593205735154e-3,1.5273658668217916e-3,1.5279331130431386e-3,9.74498489934415e-7,7.482627424771116e-7,1.420616015176624e-6 +Bls12_381_G1_multiScalarMul/44/44,1.5353847806862466e-3,1.5346147866390108e-3,1.5363954193265963e-3,2.814562457758291e-6,2.1143530632424383e-6,3.821045577572284e-6 +Bls12_381_G1_multiScalarMul/45/45,1.5694620743296511e-3,1.5687635390181445e-3,1.57029874920667e-3,2.507144487167149e-6,2.0785255381527325e-6,3.0811759778156036e-6 +Bls12_381_G1_multiScalarMul/46/46,1.5907223707740364e-3,1.5893800235731621e-3,1.592471840103437e-3,5.178470382170926e-6,3.88044580623702e-6,6.694012070239517e-6 +Bls12_381_G1_multiScalarMul/47/47,1.628661974360063e-3,1.6283512846939465e-3,1.6291669828813618e-3,1.3671525674743757e-6,9.627490393739244e-7,2.0277210680304897e-6 +Bls12_381_G1_multiScalarMul/48/48,1.6361548091125416e-3,1.6357926793118167e-3,1.6366869716805837e-3,1.442057725476356e-6,1.0667638215275559e-6,2.1942788690677544e-6 +Bls12_381_G1_multiScalarMul/49/49,1.6779864698862684e-3,1.6774419144888844e-3,1.678564301607901e-3,1.9536763807617875e-6,1.5861735530685062e-6,2.9241156321278288e-6 +Bls12_381_G1_multiScalarMul/50/50,1.7052634275253997e-3,1.7041895762385994e-3,1.706524687220049e-3,3.84152102882327e-6,2.956410364369988e-6,4.951832103647607e-6 +Bls12_381_G1_multiScalarMul/51/51,1.7406739448052255e-3,1.739741519600114e-3,1.743488273211799e-3,4.901730860712033e-6,1.681687713060746e-6,9.63314624934489e-6 +Bls12_381_G1_multiScalarMul/52/52,1.7493504703501312e-3,1.7485291809717686e-3,1.7506247910129787e-3,3.6153633132872805e-6,2.6479825651733657e-6,5.832623352761088e-6 +Bls12_381_G1_multiScalarMul/53/53,1.7868267249247544e-3,1.786050505290007e-3,1.7882000160916365e-3,3.3230153222471118e-6,2.3257047340548217e-6,5.4135122168717275e-6 +Bls12_381_G1_multiScalarMul/54/54,1.8119093305955243e-3,1.8112017731004542e-3,1.8128745438316246e-3,2.9582354520945714e-6,2.0538396464527634e-6,4.974892599302226e-6 +Bls12_381_G1_multiScalarMul/55/55,1.84471674435397e-3,1.8442599600963505e-3,1.8452634559156386e-3,1.7601881093901428e-6,1.4750625737533917e-6,2.210525678689879e-6 +Bls12_381_G1_multiScalarMul/56/56,1.8550924625942802e-3,1.8544531007068019e-3,1.8564385668508347e-3,2.9780016999383592e-6,1.8191076732735432e-6,5.031379898838522e-6 +Bls12_381_G1_multiScalarMul/57/57,1.8950408145264643e-3,1.8939992827596826e-3,1.8961977234850831e-3,3.706120655598944e-6,2.9949347749033603e-6,4.641731171151639e-6 +Bls12_381_G1_multiScalarMul/58/58,1.9214190162986646e-3,1.9205644658902652e-3,1.9227436492195735e-3,3.7919868436730406e-6,2.5151125481564216e-6,5.528965031038841e-6 +Bls12_381_G1_multiScalarMul/59/59,1.95611884939017e-3,1.9555311058998062e-3,1.9567680207463758e-3,2.0724783716238652e-6,1.7915625799228621e-6,2.6388010558596374e-6 +Bls12_381_G1_multiScalarMul/60/60,1.9594365520224813e-3,1.958943767917802e-3,1.9600328304991543e-3,1.8565912278242626e-6,1.3182944308809232e-6,3.0498262686954687e-6 +Bls12_381_G1_multiScalarMul/61/61,1.9978785940453596e-3,1.9970364354546e-3,1.9988044814993563e-3,2.814765620751774e-6,2.215278427132277e-6,3.9079749949813176e-6 +Bls12_381_G1_multiScalarMul/62/62,2.025163972129198e-3,2.024292907473527e-3,2.026477198808721e-3,3.4328117679417816e-6,2.424532695157738e-6,4.901533766106334e-6 +Bls12_381_G1_multiScalarMul/63/63,2.0586979562927845e-3,2.057984455859352e-3,2.059909135640746e-3,3.1733556435024334e-6,1.9174464587367093e-6,5.2504225730683016e-6 +Bls12_381_G1_multiScalarMul/64/64,2.0900368436079005e-3,2.088028375590593e-3,2.0984775655780315e-3,1.1646874789686276e-5,3.4252094381705674e-6,2.554205960853732e-5 +Bls12_381_G1_multiScalarMul/65/65,1.8968147378605645e-3,1.8955310391900796e-3,1.898278206886905e-3,4.680707702478362e-6,3.6933847226616885e-6,6.782185825195487e-6 +Bls12_381_G1_multiScalarMul/66/66,1.915527316948408e-3,1.9151048085532891e-3,1.916079596378419e-3,1.652232700882608e-6,1.268984752321262e-6,2.218302657360697e-6 +Bls12_381_G1_multiScalarMul/67/67,1.939873715995447e-3,1.9390300141714943e-3,1.9415345431927143e-3,3.909637666223789e-6,2.4669716449410535e-6,6.3729495513604696e-6 +Bls12_381_G1_multiScalarMul/68/68,1.963955860876783e-3,1.9634908135732973e-3,1.9647235096952164e-3,1.9301982657436205e-6,1.331287045500568e-6,3.069218630466695e-6 +Bls12_381_G1_multiScalarMul/69/69,1.981736462216709e-3,1.9812744529486425e-3,1.982304257342455e-3,1.7179723192754665e-6,1.2576978196442669e-6,2.585535309310991e-6 +Bls12_381_G1_multiScalarMul/70/70,2.015096024360793e-3,2.013930296536576e-3,2.016550975850134e-3,4.183586924132327e-6,2.9592834069943323e-6,5.903222403671096e-6 +Bls12_381_G1_multiScalarMul/71/71,2.039593310853405e-3,2.039230558943095e-3,2.040135103696278e-3,1.517677057313753e-6,1.246493361769726e-6,1.8411731331069727e-6 +Bls12_381_G1_multiScalarMul/72/72,2.058111599882653e-3,2.057193666273917e-3,2.0594723408391942e-3,3.5844251775633503e-6,2.7202401005013457e-6,5.864305886696207e-6 +Bls12_381_G1_multiScalarMul/73/73,2.0934159227994436e-3,2.0906201835026532e-3,2.095693684947171e-3,8.491298188831756e-6,7.241167338179682e-6,1.0176406230578143e-5 +Bls12_381_G1_multiScalarMul/74/74,2.1291335834122513e-3,2.1278241958452133e-3,2.1299943701228743e-3,3.7951510816769475e-6,2.9761746545534362e-6,5.135763083938416e-6 +Bls12_381_G1_multiScalarMul/75/75,2.1496696746573056e-3,2.148587264452237e-3,2.1520893411774615e-3,5.214017226179326e-6,2.831700993722389e-6,9.897946072389741e-6 +Bls12_381_G1_multiScalarMul/76/76,2.1791297355152578e-3,2.1763917538151966e-3,2.1862885859611804e-3,1.3564060446508161e-5,5.983327115746122e-6,2.4308866464862185e-5 +Bls12_381_G1_multiScalarMul/77/77,2.181325091429973e-3,2.1807942464757432e-3,2.1818133665519207e-3,1.7039353205909792e-6,1.3786145694127499e-6,2.27968640731267e-6 +Bls12_381_G1_multiScalarMul/78/78,2.2165097719499824e-3,2.213684889701067e-3,2.219024702852442e-3,9.476092692961542e-6,6.898527736606062e-6,1.3202270738128961e-5 +Bls12_381_G1_multiScalarMul/79/79,2.2220017642692208e-3,2.221452887745163e-3,2.2226621102249605e-3,1.9668594276026276e-6,1.6059114512897864e-6,2.54873438507269e-6 +Bls12_381_G1_multiScalarMul/80/80,2.2649145692548805e-3,2.264315257045781e-3,2.2659321574184485e-3,2.6476167211476292e-6,1.8114591949521001e-6,4.5100102111080466e-6 +Bls12_381_G1_multiScalarMul/81/81,2.2815568928021565e-3,2.2809268030696116e-3,2.282682684357514e-3,2.6571578380668003e-6,1.7065827732222851e-6,4.487951031499547e-6 +Bls12_381_G1_multiScalarMul/82/82,2.310620963737306e-3,2.3090927285613193e-3,2.3126689982238035e-3,5.977435209471239e-6,4.4804403698017714e-6,8.09057887928092e-6 +Bls12_381_G1_multiScalarMul/83/83,2.336733472141597e-3,2.3360361666493012e-3,2.337632382036757e-3,2.560471483733304e-6,1.920620453068812e-6,3.7021660444619836e-6 +Bls12_381_G1_multiScalarMul/84/84,2.373268168042132e-3,2.371319876892892e-3,2.3766426567644805e-3,8.021527609000714e-6,4.830364162650037e-6,1.252095716980909e-5 +Bls12_381_G1_multiScalarMul/85/85,2.384876078524913e-3,2.383959246461071e-3,2.3867334229422466e-3,4.094196151783379e-6,2.3902100912772977e-6,6.961154738344854e-6 +Bls12_381_G1_multiScalarMul/86/86,2.410565039227443e-3,2.4084234057296094e-3,2.412268328550986e-3,6.65915218385595e-6,4.329988822432703e-6,1.0326826016055168e-5 +Bls12_381_G1_multiScalarMul/87/87,2.4297666625285345e-3,2.4270653907625746e-3,2.432196481389161e-3,8.58024905300566e-6,7.109703139729458e-6,1.0051366987525497e-5 +Bls12_381_G1_multiScalarMul/88/88,2.460570343151193e-3,2.459544035208346e-3,2.4615274058159917e-3,3.5198413136176365e-6,2.8384817517665127e-6,4.815807097623251e-6 +Bls12_381_G1_multiScalarMul/89/89,2.489853458509472e-3,2.48760518697685e-3,2.491311540051355e-3,6.19046891378905e-6,4.307330671671395e-6,7.986452835536224e-6 +Bls12_381_G1_multiScalarMul/90/90,2.518729619807173e-3,2.5175955675903593e-3,2.5197557395444242e-3,3.6740724105737384e-6,3.011297773639394e-6,4.579753037221892e-6 +Bls12_381_G1_multiScalarMul/91/91,2.507346287557815e-3,2.5048432606199636e-3,2.5101409467740204e-3,9.127067962491492e-6,7.736890525902875e-6,1.0224347243298884e-5 +Bls12_381_G1_multiScalarMul/92/92,2.5623659852219262e-3,2.5612024891175753e-3,2.564829446827521e-3,5.6507070170772565e-6,3.2998574451510087e-6,9.57583819470183e-6 +Bls12_381_G1_multiScalarMul/93/93,2.5847869535442504e-3,2.5837480732719756e-3,2.5860413313409e-3,3.848008008883357e-6,3.135969999546864e-6,4.874051925178418e-6 +Bls12_381_G1_multiScalarMul/94/94,2.6234813638524954e-3,2.6221188936467322e-3,2.627015683950028e-3,6.9065042519955485e-6,3.5404891910020863e-6,1.266990728387938e-5 +Bls12_381_G1_multiScalarMul/95/95,2.642628219940988e-3,2.641768011136227e-3,2.6442054118635916e-3,3.6007375940600177e-6,2.2125834942189697e-6,6.234015624110293e-6 +Bls12_381_G1_multiScalarMul/96/96,2.6601519782021863e-3,2.6585725995916932e-3,2.6631507793169816e-3,7.137222035771094e-6,4.623560832534806e-6,1.2950373021381417e-5 +Bls12_381_G1_multiScalarMul/97/97,2.681023460582192e-3,2.679568015031102e-3,2.683278541155578e-3,5.991522440852137e-6,3.858505228846451e-6,8.60021764374252e-6 +Bls12_381_G1_multiScalarMul/98/98,2.7083684530633586e-3,2.70727640883435e-3,2.7110584196105647e-3,5.013062986030381e-6,2.3597699562053853e-6,1.002284515969446e-5 +Bls12_381_G1_multiScalarMul/99/99,2.7213371259787855e-3,2.720704088882147e-3,2.722244079978909e-3,2.444787958433492e-6,1.793699194794548e-6,3.7994420578130953e-6 +Bls12_381_G1_multiScalarMul/100/100,2.7642727676665296e-3,2.763395576301587e-3,2.7675024929907544e-3,4.726547836308982e-6,1.8913959977112497e-6,1.0025613006686808e-5 +Bls12_381_G2_multiScalarMul/1/1,1.6266495442804972e-4,1.6264736086074068e-4,1.6270124805713648e-4,7.793865350083726e-8,4.635475091813956e-8,1.4247066440608091e-7 +Bls12_381_G2_multiScalarMul/2/2,3.543638522088684e-4,3.541772068342348e-4,3.5485931188723925e-4,9.360391344324354e-7,3.4976363756994914e-7,1.8211931894900913e-6 +Bls12_381_G2_multiScalarMul/3/3,4.47702794969825e-4,4.475045705500375e-4,4.478850505015342e-4,6.493823174661071e-7,3.5878763258263287e-7,1.0803507174684568e-6 +Bls12_381_G2_multiScalarMul/4/4,5.420723557652644e-4,5.417274673810824e-4,5.426125367479333e-4,1.4301753976362207e-6,9.988141199987564e-7,2.267296520674632e-6 +Bls12_381_G2_multiScalarMul/5/5,6.370512849618329e-4,6.36900784787239e-4,6.37202712666071e-4,5.292403814549932e-7,4.022430073091077e-7,7.556842750685239e-7 +Bls12_381_G2_multiScalarMul/6/6,7.310526489754525e-4,7.30629670999753e-4,7.317446144730351e-4,1.8119026166925256e-6,1.1454709674089216e-6,3.3632913939344345e-6 +Bls12_381_G2_multiScalarMul/7/7,8.236776396240537e-4,8.233271514827839e-4,8.241067273174465e-4,1.3657308675882766e-6,1.0410102352442255e-6,1.83210797347741e-6 +Bls12_381_G2_multiScalarMul/8/8,9.197543555033109e-4,9.189658738224084e-4,9.209830008370004e-4,3.3412724036424652e-6,2.3248417111070747e-6,5.070176355554298e-6 +Bls12_381_G2_multiScalarMul/9/9,1.011991406751168e-3,1.0117382842987513e-3,1.012512156595354e-3,1.1429892811506008e-6,7.64572284352035e-7,1.824620728201617e-6 +Bls12_381_G2_multiScalarMul/10/10,1.109394930774612e-3,1.1087682317862343e-3,1.1115776119988174e-3,3.4944409285465694e-6,1.0503647842087067e-6,7.149880658627584e-6 +Bls12_381_G2_multiScalarMul/11/11,1.2023934491440338e-3,1.202171934481395e-3,1.2026423197250766e-3,7.922161025400925e-7,6.258416318073706e-7,1.029606114863458e-6 +Bls12_381_G2_multiScalarMul/12/12,1.2963025275871496e-3,1.2952163686698916e-3,1.2983463505741011e-3,4.960268500618734e-6,2.845337116066531e-6,9.687158836086103e-6 +Bls12_381_G2_multiScalarMul/13/13,1.3869285962502872e-3,1.3866231292243125e-3,1.3872893550098244e-3,1.1726919062774188e-6,8.791906263916984e-7,1.5913921990012086e-6 +Bls12_381_G2_multiScalarMul/14/14,1.4823956781971994e-3,1.4815973050589385e-3,1.4842137535372652e-3,3.760848566094728e-6,2.472183908899497e-6,6.4465275732684205e-6 +Bls12_381_G2_multiScalarMul/15/15,1.574445631700049e-3,1.574063788581931e-3,1.5749578982368424e-3,1.443263633319882e-6,1.0628032736563463e-6,2.1565979694667185e-6 +Bls12_381_G2_multiScalarMul/16/16,1.5000875796284717e-3,1.4994665426513504e-3,1.5014717203342867e-3,2.802372121079838e-6,1.7676048441935653e-6,4.644089354729122e-6 +Bls12_381_G2_multiScalarMul/17/17,1.5940905703219718e-3,1.5936217521556593e-3,1.5945282467814278e-3,1.547468548627245e-6,1.1967489868918594e-6,2.082313772097416e-6 +Bls12_381_G2_multiScalarMul/18/18,1.6481937447323397e-3,1.6471788901492087e-3,1.6502528733967521e-3,4.67746155264807e-6,2.5560426788421386e-6,8.493562555710135e-6 +Bls12_381_G2_multiScalarMul/19/19,1.7408620063694292e-3,1.7403685953485991e-3,1.7416086573762834e-3,2.034339176777199e-6,1.5411497874186401e-6,2.888074021221646e-6 +Bls12_381_G2_multiScalarMul/20/20,1.7983360168952664e-3,1.7968063959178204e-3,1.8007319622437476e-3,6.701452941660098e-6,3.915890097926392e-6,1.1565951790899295e-5 +Bls12_381_G2_multiScalarMul/21/21,1.8948751419094719e-3,1.8943849272806152e-3,1.8954945505194202e-3,1.8264677812158936e-6,1.5180676580123575e-6,2.3043238795090236e-6 +Bls12_381_G2_multiScalarMul/22/22,1.9483638492318052e-3,1.9468479306608071e-3,1.952898337552636e-3,8.246725685061966e-6,2.916390890917488e-6,1.6554460898097785e-5 +Bls12_381_G2_multiScalarMul/23/23,2.0441566797094976e-3,2.0436200484617298e-3,2.0448120935495366e-3,1.9807680962425035e-6,1.4047597581205637e-6,2.861374149657612e-6 +Bls12_381_G2_multiScalarMul/24/24,2.0976111797810742e-3,2.0969141362790775e-3,2.0983042002160226e-3,2.294409781298406e-6,1.7816482691771947e-6,3.2363169164003804e-6 +Bls12_381_G2_multiScalarMul/25/25,2.1916934430134647e-3,2.1911766683971054e-3,2.192454586070339e-3,2.0791512216562315e-6,1.5171229138063835e-6,2.812518408756342e-6 +Bls12_381_G2_multiScalarMul/26/26,2.2452874242475463e-3,2.2438224649193378e-3,2.248020575104657e-3,6.546744756250407e-6,4.224171258471438e-6,1.1357661995132573e-5 +Bls12_381_G2_multiScalarMul/27/27,2.3342313432099604e-3,2.3334417036587492e-3,2.335903802244924e-3,3.7924501525196913e-6,2.084116468653706e-6,6.745286115407234e-6 +Bls12_381_G2_multiScalarMul/28/28,2.3924196934986424e-3,2.3905980952149135e-3,2.39744572554579e-3,9.270395166568168e-6,3.857502451986574e-6,1.8266974876360255e-5 +Bls12_381_G2_multiScalarMul/29/29,2.4921574096234654e-3,2.4911465295363233e-3,2.4951214940058244e-3,5.209897620887097e-6,2.3932366963378704e-6,1.007979235143704e-5 +Bls12_381_G2_multiScalarMul/30/30,2.5442112572946624e-3,2.5431826880834667e-3,2.5479216241766365e-3,5.7374902589030385e-6,2.166916577225313e-6,1.24589648550128e-5 +Bls12_381_G2_multiScalarMul/31/31,2.6387551082366705e-3,2.6380466280120883e-3,2.6396291501284983e-3,2.5285910565402825e-6,2.0132127254936795e-6,3.4207259760745164e-6 +Bls12_381_G2_multiScalarMul/32/32,2.5150931462186196e-3,2.513387917297599e-3,2.5181977065017046e-3,7.657009385145557e-6,4.5131093648664805e-6,1.3678490989164753e-5 +Bls12_381_G2_multiScalarMul/33/33,3.0889519233376545e-3,3.0883882511648234e-3,3.089672507460859e-3,2.0979675388899346e-6,1.603912694016453e-6,3.0603682324660857e-6 +Bls12_381_G2_multiScalarMul/34/34,3.16771726298734e-3,3.16501045273763e-3,3.172197179196162e-3,1.0825021580641719e-5,6.671829453430046e-6,1.8892794609350383e-5 +Bls12_381_G2_multiScalarMul/35/35,3.2525975758965855e-3,3.251923568635943e-3,3.2534974414252724e-3,2.3923622222660625e-6,1.771511114169158e-6,3.613237863752478e-6 +Bls12_381_G2_multiScalarMul/36/36,3.336138244007564e-3,3.333789111955089e-3,3.344298373821e-3,1.3359645865766898e-5,3.2128822247268738e-6,2.7638521011789944e-5 +Bls12_381_G2_multiScalarMul/37/37,3.4191138605455746e-3,3.4179135859041592e-3,3.4233605791000876e-3,6.592098823336916e-6,2.5157731785295883e-6,1.3141627481895897e-5 +Bls12_381_G2_multiScalarMul/38/38,3.4883584083644226e-3,3.4862131678210493e-3,3.4925344207942677e-3,9.623236210916872e-6,5.191214954965976e-6,1.7597405473000066e-5 +Bls12_381_G2_multiScalarMul/39/39,3.530386408142463e-3,3.5295959082416793e-3,3.531411239014294e-3,2.79677085673492e-6,2.1274732913274754e-6,3.925571150385237e-6 +Bls12_381_G2_multiScalarMul/40/40,3.6147002382323538e-3,3.611572624230025e-3,3.6292011188412323e-3,1.7990113412185996e-5,2.845513840934602e-6,4.043993566101094e-5 +Bls12_381_G2_multiScalarMul/41/41,3.672723290652948e-3,3.6718602367145966e-3,3.673688181816288e-3,2.84241014465167e-6,2.3021696308807956e-6,3.7655879313695054e-6 +Bls12_381_G2_multiScalarMul/42/42,3.793747136886243e-3,3.78926839608175e-3,3.809348971725428e-3,2.269174801044769e-5,4.7237643544819555e-6,4.9663768681186095e-5 +Bls12_381_G2_multiScalarMul/43/43,3.877862027839689e-3,3.876819161298888e-3,3.8794572953528964e-3,4.162065327624179e-6,3.2714009413120982e-6,5.1550470389566275e-6 +Bls12_381_G2_multiScalarMul/44/44,3.965116399895544e-3,3.962804992549213e-3,3.97345386215166e-3,1.3112609308794646e-5,1.8812805162759533e-6,2.7437540345266834e-5 +Bls12_381_G2_multiScalarMul/45/45,4.004527665871219e-3,4.003216183025186e-3,4.00656406563525e-3,5.2564769639065946e-6,2.696936689436533e-6,7.823236463877045e-6 +Bls12_381_G2_multiScalarMul/46/46,4.076804027301204e-3,4.074764849350912e-3,4.082954370562564e-3,1.0195134478551572e-5,3.59758066050906e-6,2.02607321633781e-5 +Bls12_381_G2_multiScalarMul/47/47,4.167774429892586e-3,4.1666246852367335e-3,4.169331500283441e-3,4.095651022675052e-6,3.1833448207887804e-6,5.089866484578962e-6 +Bls12_381_G2_multiScalarMul/48/48,4.2249981616795705e-3,4.222778156184377e-3,4.226612496226903e-3,5.7784805597787715e-6,4.4339723066230185e-6,7.3377180823161815e-6 +Bls12_381_G2_multiScalarMul/49/49,4.3524164098415665e-3,4.351263723172645e-3,4.353648896076485e-3,3.7577346495739375e-6,3.092141280492094e-6,4.52320031610404e-6 +Bls12_381_G2_multiScalarMul/50/50,4.343123429888507e-3,4.341239145934485e-3,4.345694580031099e-3,7.032494846534855e-6,5.430307563910816e-6,1.0261289957428346e-5 +Bls12_381_G2_multiScalarMul/51/51,4.484856489477111e-3,4.481774784858851e-3,4.487312713793393e-3,8.158820364283e-6,6.798014601558509e-6,1.086960763925229e-5 +Bls12_381_G2_multiScalarMul/52/52,4.546562051796544e-3,4.5455748661040974e-3,4.548037932926745e-3,3.6580687673211806e-6,2.8901424834133615e-6,5.219822997121614e-6 +Bls12_381_G2_multiScalarMul/53/53,4.654474034299822e-3,4.65318130717014e-3,4.655917064534823e-3,4.116466278137667e-6,3.166891661793465e-6,5.567941155062992e-6 +Bls12_381_G2_multiScalarMul/54/54,4.721927123629685e-3,4.72071287904244e-3,4.723138528981887e-3,3.94193309418702e-6,3.113913371425901e-6,5.136276379939376e-6 +Bls12_381_G2_multiScalarMul/55/55,4.795039804834155e-3,4.793771853613166e-3,4.796041252525426e-3,3.523502774916879e-6,2.8612449092910447e-6,4.464716550457647e-6 +Bls12_381_G2_multiScalarMul/56/56,4.864016888196152e-3,4.862934237209827e-3,4.865878015473469e-3,4.339172192062833e-6,3.120561122208654e-6,7.091594219853984e-6 +Bls12_381_G2_multiScalarMul/57/57,4.930026691468103e-3,4.928660811034607e-3,4.93184431837138e-3,4.92694965505342e-6,3.631274655946987e-6,6.916774799932921e-6 +Bls12_381_G2_multiScalarMul/58/58,4.999478205962443e-3,4.996476656269146e-3,5.002509748355277e-3,9.65312271848907e-6,8.212314993018033e-6,1.121977177338798e-5 +Bls12_381_G2_multiScalarMul/59/59,5.109930645097379e-3,5.108695300209485e-3,5.111720735214837e-3,4.307666456047917e-6,3.2036925396243358e-6,7.010008721447832e-6 +Bls12_381_G2_multiScalarMul/60/60,5.182636587074396e-3,5.1812215576612815e-3,5.184867458236281e-3,5.045266958501895e-6,3.3630808719106254e-6,7.598293873580799e-6 +Bls12_381_G2_multiScalarMul/61/61,5.261201467559662e-3,5.259483119610097e-3,5.2651003452464235e-3,6.794062799442452e-6,3.965079449462158e-6,1.2745803244159386e-5 +Bls12_381_G2_multiScalarMul/62/62,5.355085149782543e-3,5.353521974098854e-3,5.3568364980710005e-3,5.127106845655141e-6,3.956280257430231e-6,6.764557833667277e-6 +Bls12_381_G2_multiScalarMul/63/63,5.404870448491742e-3,5.401124837066587e-3,5.407497875504651e-3,8.934660522629549e-6,6.290321430881255e-6,1.2732030907646999e-5 +Bls12_381_G2_multiScalarMul/64/64,4.8782659702195615e-3,4.876660673660171e-3,4.8804522014555e-3,5.830661634910927e-6,3.955325665036216e-6,9.38894371358523e-6 +Bls12_381_G2_multiScalarMul/65/65,4.9061548862185346e-3,4.904813116841975e-3,4.9086495754739915e-3,5.295424246670201e-6,3.7451476035762403e-6,8.334611829514347e-6 +Bls12_381_G2_multiScalarMul/66/66,4.967076866858588e-3,4.96587704975757e-3,4.970208209096129e-3,5.500738791485448e-6,2.7782883129256445e-6,1.0490016182322088e-5 +Bls12_381_G2_multiScalarMul/67/67,5.0384188004806525e-3,5.036297660856063e-3,5.040874280488966e-3,7.20767347691469e-6,5.18593994354578e-6,1.1000885848108839e-5 +Bls12_381_G2_multiScalarMul/68/68,5.082679596088205e-3,5.081788191855941e-3,5.083677026915687e-3,2.9879915262955836e-6,2.402250840802348e-6,3.7388441162211205e-6 +Bls12_381_G2_multiScalarMul/69/69,5.131805217231941e-3,5.129945152668336e-3,5.134860292773551e-3,7.121015258734736e-6,4.754387036952524e-6,1.0407485911539298e-5 +Bls12_381_G2_multiScalarMul/70/70,5.223131098010917e-3,5.220270707999523e-3,5.226515783222153e-3,9.515319707834862e-6,7.924704664502419e-6,1.197266014225403e-5 +Bls12_381_G2_multiScalarMul/71/71,5.2882851289316885e-3,5.286944845429294e-3,5.2901838154393414e-3,4.850407193371409e-6,3.951323934404944e-6,6.909977742394703e-6 +Bls12_381_G2_multiScalarMul/72/72,5.31973147751225e-3,5.318376432387295e-3,5.32119875028863e-3,4.277946466566538e-6,3.32076690250808e-6,5.635737244144887e-6 +Bls12_381_G2_multiScalarMul/73/73,5.415258160623588e-3,5.413782714872596e-3,5.416918547393203e-3,4.874528900097905e-6,4.170514576006458e-6,5.848559988534025e-6 +Bls12_381_G2_multiScalarMul/74/74,5.504234496008557e-3,5.500576962955019e-3,5.508481864691515e-3,1.1590261990431737e-5,7.963644443790475e-6,2.0109944098147845e-5 +Bls12_381_G2_multiScalarMul/75/75,5.564079990869667e-3,5.562681956747252e-3,5.56567336402758e-3,4.352958051265566e-6,3.4422969438156352e-6,6.286896453598817e-6 +Bls12_381_G2_multiScalarMul/76/76,5.636188875483629e-3,5.63517382713922e-3,5.637553743099741e-3,3.670518446053137e-6,2.6204373559816722e-6,5.576211218482488e-6 +Bls12_381_G2_multiScalarMul/77/77,5.653980663508052e-3,5.652296820298524e-3,5.657670797268361e-3,7.080543955082813e-6,3.7855994178883683e-6,1.2879875104746403e-5 +Bls12_381_G2_multiScalarMul/78/78,5.740407480489808e-3,5.7391493805168635e-3,5.7418065167963e-3,3.904427361041286e-6,3.074226799333372e-6,5.442029866027754e-6 +Bls12_381_G2_multiScalarMul/79/79,5.751010900543999e-3,5.748323596643336e-3,5.754728295889315e-3,9.270531833024517e-6,6.035547009683968e-6,1.4379971767424256e-5 +Bls12_381_G2_multiScalarMul/80/80,5.858800364486109e-3,5.857269600819101e-3,5.860372363714095e-3,4.878855487808653e-6,3.7581767493947793e-6,6.996843420054578e-6 +Bls12_381_G2_multiScalarMul/81/81,5.896817994473183e-3,5.894063205963552e-3,5.902366128185444e-3,1.1536253196991757e-5,6.383910727541163e-6,2.0982102749864474e-5 +Bls12_381_G2_multiScalarMul/82/82,5.954935473178033e-3,5.953063910957776e-3,5.957530288931881e-3,6.253389324766823e-6,4.779351132702418e-6,7.979956410106285e-6 +Bls12_381_G2_multiScalarMul/83/83,6.0161468367483225e-3,6.013693044072133e-3,6.02177468728205e-3,1.0835798229125257e-5,6.207595030876202e-6,1.9548081431230584e-5 +Bls12_381_G2_multiScalarMul/84/84,6.094614704088679e-3,6.092574358893842e-3,6.0971100378228475e-3,6.666176870479611e-6,5.145944335262237e-6,8.274826825353507e-6 +Bls12_381_G2_multiScalarMul/85/85,6.1380376895836565e-3,6.133725428191463e-3,6.145329879147275e-3,1.626622922741078e-5,1.0821722335694483e-5,2.700730631296616e-5 +Bls12_381_G2_multiScalarMul/86/86,6.2140860516838245e-3,6.212851863373451e-3,6.215546358212723e-3,4.0395006569626435e-6,3.346822769756149e-6,4.7839437803151336e-6 +Bls12_381_G2_multiScalarMul/87/87,6.27302455453059e-3,6.270885529060964e-3,6.275809157451918e-3,6.999595649144767e-6,4.947819532780126e-6,1.0251538631768462e-5 +Bls12_381_G2_multiScalarMul/88/88,6.3404523682942995e-3,6.338680115532713e-3,6.3420519237891515e-3,5.208923709646363e-6,4.108671865132737e-6,6.370714767856116e-6 +Bls12_381_G2_multiScalarMul/89/89,6.410017615442629e-3,6.406159123069732e-3,6.41315635661642e-3,1.0622224787961102e-5,7.696172865576866e-6,1.3963076368862973e-5 +Bls12_381_G2_multiScalarMul/90/90,6.481791869329977e-3,6.479839995502555e-3,6.484276415426917e-3,6.258729255672214e-6,4.848352706810262e-6,7.988412553980431e-6 +Bls12_381_G2_multiScalarMul/91/91,6.475168018503552e-3,6.470179709488667e-3,6.483048340856914e-3,1.7646142713249933e-5,1.3097969794456097e-5,2.6957602312106938e-5 +Bls12_381_G2_multiScalarMul/92/92,6.569285931833285e-3,6.566882844069322e-3,6.574172843329704e-3,9.752702509029438e-6,5.6501870652183995e-6,1.6741066006979055e-5 +Bls12_381_G2_multiScalarMul/93/93,6.629457299321055e-3,6.625183482996535e-3,6.638841711503604e-3,1.7538389603216873e-5,1.0528950637309035e-5,3.0379658274480686e-5 +Bls12_381_G2_multiScalarMul/94/94,6.7320607492387515e-3,6.730167903973191e-3,6.736598035759103e-3,8.15218783569633e-6,3.741189882233103e-6,1.6185222568739163e-5 +Bls12_381_G2_multiScalarMul/95/95,6.801145393237103e-3,6.796607904593793e-3,6.8137432062137055e-3,1.9691935909923513e-5,7.536520887751789e-6,3.768941248607555e-5 +Bls12_381_G2_multiScalarMul/96/96,6.821360358060845e-3,6.816810519501433e-3,6.829564504014655e-3,1.6752380908242913e-5,1.0237675196995415e-5,3.083226102494789e-5 +Bls12_381_G2_multiScalarMul/97/97,6.90522012785712e-3,6.901544208299667e-3,6.918761450372084e-3,1.7088371694161855e-5,5.773286197099474e-6,3.643360035316389e-5 +Bls12_381_G2_multiScalarMul/98/98,6.9597205589059085e-3,6.9554579231546464e-3,6.963825444927238e-3,1.230537047747648e-5,9.828399035508776e-6,1.581113740579338e-5 +Bls12_381_G2_multiScalarMul/99/99,6.998605748330429e-3,6.993956045528542e-3,7.003564931628933e-3,1.3941888558415054e-5,1.1848281516892752e-5,1.8598404587423643e-5 +Bls12_381_G2_multiScalarMul/100/100,7.090569654857228e-3,7.08876305884669e-3,7.093035056145744e-3,6.187076669186285e-6,4.689206191622249e-6,8.297705725121281e-6 +LookupCoin/4/4/0,1.1987809246529645e-6,1.1980799694260653e-6,1.199507988172571e-6,2.4107745567835586e-9,2.0584370079307666e-9,2.875392436193467e-9 +LookupCoin/4/4/310,1.2142647691242684e-6,1.2131420571175932e-6,1.2155824079867558e-6,4.0706586084594835e-9,3.341022693427462e-9,5.065716418773158e-9 +LookupCoin/4/4/10010,1.2248007161821862e-6,1.2239051860618773e-6,1.2258178843052394e-6,3.4507929939399797e-9,2.7438893641041726e-9,4.037935320134895e-9 +LookupCoin/4/4/310,1.227249583287171e-6,1.2256517429394646e-6,1.228820138823975e-6,5.135902136033977e-9,4.602249434367064e-9,5.923087021439266e-9 +LookupCoin/4/4/10010,1.2443322171758413e-6,1.2427942185459095e-6,1.245357233115194e-6,4.477283860902663e-9,3.3486755939797695e-9,6.223685793289658e-9 +LookupCoin/4/4/1550,1.2454774811827858e-6,1.24344192850786e-6,1.2470198844553666e-6,6.122793215314405e-9,5.177658728098016e-9,7.799865926329944e-9 +LookupCoin/4/4/50050,1.2571864815375906e-6,1.2564138179154984e-6,1.2579616575806e-6,2.763962545250128e-9,2.377982103186773e-9,3.4290535732906835e-9 +LookupCoin/4/4/3100,1.2439256389929855e-6,1.2432284142565402e-6,1.2447917189730735e-6,2.6963459263387795e-9,2.3388804770411354e-9,3.1487019272388267e-9 +LookupCoin/4/4/100100,1.2614380048646346e-6,1.2607020697810519e-6,1.2622035022217295e-6,2.6041139838164562e-9,2.1634799046250406e-9,3.2905483922706815e-9 +LookupCoin/4/4/15500,1.2817013390502208e-6,1.2805655390473332e-6,1.2826202692983273e-6,3.4355071748599705e-9,2.7556274311754177e-9,4.333780868629672e-9 +LookupCoin/4/4/500500,1.2886652966188255e-6,1.287822313888798e-6,1.2893947030051335e-6,2.4996056527806103e-9,2.0027954951844944e-9,3.51778389213686e-9 +LookupCoin/4/4/31000,1.290122000714343e-6,1.288856340927497e-6,1.2912200541102332e-6,3.7314630573669714e-9,3.1415172863968466e-9,4.4094407974448845e-9 +LookupCoin/4/4/1001000,1.2850523205112054e-6,1.2841146835669193e-6,1.2862444714691543e-6,3.495083997499569e-9,2.7213906501859453e-9,5.135209308347153e-9 +LookupCoin/4/4/1,1.2257006912313622e-6,1.2252367955480791e-6,1.2261868546628844e-6,1.7280071454745501e-9,1.4188404395459067e-9,2.155107450125363e-9 +LookupCoin/4/4/3100,1.2647764517950342e-6,1.2641033185328018e-6,1.2654168552708808e-6,2.2224938263044665e-9,1.8474168055405267e-9,2.7240972942539672e-9 +LookupCoin/4/4/10100,1.2509813815980665e-6,1.2493589833326004e-6,1.2523719298666614e-6,4.852971270116405e-9,4.224063533334953e-9,5.761730062786258e-9 +LookupCoin/4/4/100100,1.272100065961152e-6,1.2713779399535466e-6,1.2729916263321848e-6,2.6442781870170232e-9,2.2315274992244496e-9,3.3894908114610666e-9 +LookupCoin/4/4/1000100,1.2622451455213246e-6,1.2614409542043105e-6,1.2628884167008598e-6,2.4284367212124195e-9,1.952886495004267e-9,3.058594015650686e-9 +LookupCoin/4/4/1,1.2120959773067779e-6,1.2111098168941214e-6,1.2130451144150161e-6,3.340332155521285e-9,2.854400739916875e-9,3.884696635679422e-9 +LookupCoin/4/4/1,1.2202197166189542e-6,1.2192613245401622e-6,1.2212645347977496e-6,3.2388832596863558e-9,2.7203964537861694e-9,3.900896078940326e-9 +LookupCoin/4/4/1,1.2235044799553622e-6,1.2228494680423523e-6,1.2243029181572994e-6,2.418188553655573e-9,1.9596997508446255e-9,3.3537589604273597e-9 +LookupCoin/4/4/124,1.2186676257033273e-6,1.2173292994061867e-6,1.2200318248936087e-6,4.796332197760777e-9,4.009498878734066e-9,6.027489021903283e-9 +LookupCoin/4/4/372,1.2346285723771364e-6,1.2336953254200625e-6,1.235714013792257e-6,3.425255360445383e-9,2.7589262620900956e-9,4.040351857619523e-9 +LookupCoin/4/4/651,1.2372953539593385e-6,1.2362630975860024e-6,1.2383763132577293e-6,3.523259668004743e-9,2.939076484410285e-9,4.317741226544648e-9 +LookupCoin/4/4/0,1.1938943959277518e-6,1.1931943214717257e-6,1.1945778725918846e-6,2.3739978189645768e-9,1.8545949559429995e-9,3.332219238927099e-9 +LookupCoin/4/4/2002,1.2197197605216406e-6,1.2187965672790472e-6,1.2206041280398874e-6,2.9336631903150676e-9,2.4616168455718915e-9,3.632414054858564e-9 +LookupCoin/4/4/4004,1.2251163407493166e-6,1.223376349490241e-6,1.2269137473156499e-6,6.08770401676884e-9,5.158185169323526e-9,7.03140495193674e-9 +LookupCoin/4/4/0,1.1868541548864574e-6,1.185793573842222e-6,1.187690566882342e-6,3.316928649716189e-9,2.732913986532151e-9,4.129135287141955e-9 +LookupCoin/4/4/0,1.1898164242411212e-6,1.1888025275796023e-6,1.1906360315586723e-6,3.105666969872855e-9,2.5406724407764428e-9,4.0336345504799915e-9 +LookupCoin/4/4/10001,1.2150661212171984e-6,1.2143604950573222e-6,1.215820874653369e-6,2.38481675610348e-9,1.9162066170306435e-9,3.0006760018374973e-9 +LookupCoin/4/4/5066270,1.277826580439173e-6,1.2767570441421777e-6,1.2789518483325532e-6,3.5436542776320486e-9,2.858524102842415e-9,4.587631601537296e-9 +LookupCoin/4/4/1292907,1.2677688678187691e-6,1.266718345792965e-6,1.2688009027816102e-6,3.447161199023977e-9,2.8551687550492393e-9,4.1145424069515494e-9 +LookupCoin/4/4/4030899,1.2814323262321796e-6,1.2806641039935756e-6,1.2821530318509303e-6,2.5390170765500563e-9,2.024519511273767e-9,3.2720719989230043e-9 +LookupCoin/4/4/5040432,1.2701222097077116e-6,1.2680642236901763e-6,1.272211683356216e-6,6.785163423685793e-9,5.5778440287708566e-9,8.32836503873299e-9 +LookupCoin/4/4/4561038,1.2744320740219546e-6,1.2732745959940393e-6,1.2753878614609515e-6,3.4966375499144543e-9,2.6380710490775692e-9,5.15651621189535e-9 +LookupCoin/4/4/5375788,1.29023827085883e-6,1.289131346302382e-6,1.2913186917094856e-6,3.6521304151635797e-9,3.077484480052455e-9,4.449439367331406e-9 +LookupCoin/4/4/1262300,1.2539033480175535e-6,1.2526689596121973e-6,1.2556306027786345e-6,4.813588884658454e-9,4.0753081448679886e-9,6.013391116763802e-9 +LookupCoin/4/4/779712,1.2752127020007219e-6,1.2733455510509096e-6,1.276421301457468e-6,4.960204372531049e-9,3.78185565884019e-9,7.938310069673206e-9 +LookupCoin/4/4/1148823,1.257069697085679e-6,1.2550281877305862e-6,1.258357677798816e-6,5.2692097950519294e-9,3.607430925786029e-9,7.84256990197175e-9 +LookupCoin/4/4/7565554,1.2718862218212706e-6,1.270595772895692e-6,1.273500171319768e-6,4.7205100970096915e-9,3.9399955033716265e-9,5.636316687102632e-9 +LookupCoin/4/4/1892372,1.2798022142401478e-6,1.2787601377188223e-6,1.2806492883730673e-6,3.240518096537139e-9,2.6845102219159927e-9,4.024692073232961e-9 +LookupCoin/4/4/3962952,1.2700930008680598e-6,1.269264255671348e-6,1.2709391336121646e-6,2.874679403151091e-9,2.3225902454617737e-9,3.70494574418947e-9 +LookupCoin/4/4/4322668,1.289884201590555e-6,1.2884415967028401e-6,1.2913737248356338e-6,4.801444154073013e-9,3.916001043141595e-9,5.9023486667443996e-9 +LookupCoin/4/4/2970000,1.2784087871552185e-6,1.2767249782735827e-6,1.279942350107124e-6,5.300756075447827e-9,4.125409905431318e-9,7.91576575586899e-9 +LookupCoin/4/4/1902626,1.2825938062683246e-6,1.2812887257240548e-6,1.2840488079301932e-6,4.539085547891917e-9,3.7003355816408288e-9,5.8304818844362325e-9 +LookupCoin/4/4/2058224,1.2674138822348226e-6,1.266517177438222e-6,1.268307129660272e-6,2.920592770603687e-9,2.475360696644196e-9,3.5087547273771266e-9 +LookupCoin/4/4/3287578,1.279789833294665e-6,1.2785676940878397e-6,1.2812666317707647e-6,4.396660300354464e-9,3.659512262281134e-9,5.305430420746576e-9 +LookupCoin/4/4/745890,1.2585346454916983e-6,1.2568337444249753e-6,1.2601251297939e-6,5.430356191272733e-9,4.633445845065433e-9,6.319836603491019e-9 +LookupCoin/4/4/4002026,1.2838087012363595e-6,1.2825086945447733e-6,1.2850242229140597e-6,4.306704983324547e-9,3.5205722930442468e-9,5.654297611220834e-9 +LookupCoin/4/4/1679601,1.26357751253574e-6,1.262826291623019e-6,1.2643169242412846e-6,2.4774181681520444e-9,2.060368542544128e-9,3.039629576081113e-9 +LookupCoin/4/4/6480027,1.2801980877278831e-6,1.2771485096511817e-6,1.2820170540550525e-6,7.943334159431303e-9,5.772244703375927e-9,1.1917062311991287e-8 +LookupCoin/4/4/4498896,1.231625663105949e-6,1.2297170084115537e-6,1.2332704356430894e-6,6.124111331433371e-9,5.385841935470476e-9,7.003288835706173e-9 +LookupCoin/4/4/1674756,1.2735333599690776e-6,1.2710191575535196e-6,1.2756334354586257e-6,7.879868389245381e-9,6.978600463987998e-9,9.154593296359008e-9 +LookupCoin/4/4/2876381,1.261443514778358e-6,1.260767224170065e-6,1.2622450911016386e-6,2.462597798861482e-9,1.9676438830362255e-9,3.096918170975184e-9 +LookupCoin/4/4/6444328,1.2817975648175746e-6,1.2807178055257148e-6,1.2828396916268854e-6,3.5823180401646896e-9,2.8738062669432795e-9,4.531443495722488e-9 +LookupCoin/4/4/375724,1.245765227573596e-6,1.2444678099280414e-6,1.2468631348220374e-6,3.914327458436205e-9,3.338118939061562e-9,4.747447778986924e-9 +LookupCoin/4/4/126540,1.2603295320670344e-6,1.2576543706100949e-6,1.2622416729797346e-6,7.814043532055153e-9,5.869724250780736e-9,1.201854001602634e-8 +LookupCoin/4/4/4706835,1.2659166931421738e-6,1.264223718258494e-6,1.2671110254567974e-6,4.65608823434229e-9,3.141554343089209e-9,6.784674488291999e-9 +LookupCoin/4/4/5364324,1.2701935393151057e-6,1.269043098380611e-6,1.2712397968982748e-6,3.781423003012787e-9,3.1820832804639213e-9,4.755630255677031e-9 +LookupCoin/4/4/1455168,1.2704388582488929e-6,1.269687317776098e-6,1.2711188680637336e-6,2.396816947915933e-9,1.9853818496761954e-9,2.993679944959491e-9 +LookupCoin/4/4/3889776,1.2802125381646228e-6,1.2791239574618982e-6,1.2813999258216065e-6,3.80345065781175e-9,3.149123607025695e-9,4.804823325650835e-9 +LookupCoin/4/4/686750,1.2599963410745547e-6,1.2588914981747105e-6,1.2611105471132294e-6,3.785014969177361e-9,3.147206549401517e-9,4.767167393088846e-9 +LookupCoin/4/4/1963648,1.299818184369183e-6,1.298617040985033e-6,1.301036825644262e-6,4.176587526215176e-9,3.4330381937143528e-9,5.270136974581143e-9 +LookupCoin/4/4/8659209,1.2924287795535367e-6,1.2912655254935138e-6,1.2935332916752233e-6,3.759717198495328e-9,2.8703928008557797e-9,5.27586315684352e-9 +LookupCoin/4/4/2789190,1.2755127933170805e-6,1.2737087407368222e-6,1.2768607596541763e-6,4.963059723596741e-9,3.5158859551543468e-9,6.981879743504883e-9 +LookupCoin/4/4/5625406,1.2959874699702527e-6,1.2950226907122984e-6,1.2970082683444309e-6,3.3391304669998987e-9,2.7941306761813028e-9,4.1386386528375054e-9 +LookupCoin/4/4/1957722,1.2690376232270707e-6,1.2666937311835606e-6,1.2709293087375226e-6,7.103182645095991e-9,4.915885369868955e-9,9.981731048934394e-9 +LookupCoin/4/4/4775708,1.2932987757200833e-6,1.2923933431135412e-6,1.2940935275990051e-6,2.785537307928441e-9,2.3087374360113047e-9,3.4830510090053497e-9 +LookupCoin/4/4/7862841,1.2779049515065047e-6,1.276878213735431e-6,1.279210034062878e-6,3.6895466028508537e-9,3.058034377334638e-9,5.074895055983018e-9 +LookupCoin/4/4/4343103,1.2947015952690554e-6,1.293526049558432e-6,1.2959020546237318e-6,3.840676655557911e-9,3.2213319774607096e-9,4.915737391178833e-9 +LookupCoin/4/4/2628828,1.2576228670548757e-6,1.255184660863472e-6,1.2591729099493177e-6,6.6657091577461195e-9,4.479936777639809e-9,1.0930469098408585e-8 +LookupCoin/4/4/6801147,1.273344935956418e-6,1.2717381856314266e-6,1.2747350340827408e-6,4.964830713393079e-9,4.139696967925825e-9,5.688607530322684e-9 +LookupCoin/4/4/2259715,1.2733626425487013e-6,1.2725687215373529e-6,1.2742045289295303e-6,2.753786442176939e-9,2.2271683907574778e-9,3.6442018276317194e-9 +LookupCoin/4/4/1311960,1.2643513046710382e-6,1.262048535540152e-6,1.2664285395243078e-6,7.211269768344391e-9,6.0887352623941e-9,9.266004580584638e-9 +LookupCoin/4/4/4656600,1.2784770014839777e-6,1.2763424508746477e-6,1.2808613423153377e-6,7.700463816731205e-9,6.8360128237785615e-9,8.690659514605894e-9 +LookupCoin/4/4/1093578,1.2716722138984615e-6,1.2700426000027498e-6,1.2729495582483995e-6,4.8324792890281395e-9,3.958125416800441e-9,6.067383126695396e-9 +LookupCoin/4/4/2868166,1.2775526844976142e-6,1.2753876524451476e-6,1.279449788038799e-6,7.1015328750516004e-9,5.800878613555848e-9,8.76070508863944e-9 +LookupCoin/4/4/2485840,1.2606233541272532e-6,1.2584118705398867e-6,1.2628177461824179e-6,7.2734790619610975e-9,6.412289956484719e-9,8.592412278530262e-9 +LookupCoin/4/4/453354,1.2491237152866404e-6,1.2474513872251372e-6,1.2509309497843268e-6,5.972396719405774e-9,4.80908506645763e-9,7.707294223227184e-9 +LookupCoin/4/4/2631636,1.275835347391731e-6,1.274031323751365e-6,1.2770603929417775e-6,4.848121178368409e-9,3.575817370976392e-9,6.803022453212725e-9 +LookupCoin/1/1/1,1.2062193447359163e-6,1.204720572905251e-6,1.2085664510346082e-6,6.3895396673973984e-9,3.5237401780642824e-9,9.865319076861485e-9 +LookupCoin/1/4/310,1.2477282934661902e-6,1.2457165309461458e-6,1.2500730188409636e-6,7.50234974399736e-9,6.484893665257567e-9,9.090423319721542e-9 +LookupCoin/1/125/10010,1.2364898735039994e-6,1.2339360373470795e-6,1.2388935255579768e-6,8.358163277644683e-9,6.037899233171248e-9,1.2510441623475233e-8 +LookupCoin/1/2500/200010,1.2374699372558117e-6,1.2359148176434845e-6,1.23888079346438e-6,5.061076021241142e-9,4.194002526091644e-9,6.3986008003463075e-9 +LookupCoin/1/1/170,1.2344447450763024e-6,1.2330377959532651e-6,1.2361615688816788e-6,5.196922828874984e-9,3.64700211256897e-9,8.416421668371051e-9 +LookupCoin/1/4/2635,1.2435117760278765e-6,1.2422284752759498e-6,1.2447536719288215e-6,4.408433001343926e-9,3.677681442162629e-9,5.438399421854307e-9 +LookupCoin/1/125/79079,1.2573268594938636e-6,1.2551516899720538e-6,1.2599712779688385e-6,7.80382576748386e-9,4.997720015443988e-9,1.3924166794552906e-8 +LookupCoin/1/2500/1660083,1.2484602746854446e-6,1.247815712373976e-6,1.2491265511584914e-6,2.34795048068606e-9,1.8921582415414914e-9,3.0112347635990135e-9 +LookupCoin/4/1/3100,1.2423704587658755e-6,1.2407630626791196e-6,1.2439468322394299e-6,5.373034335462937e-9,4.7566006320427445e-9,6.301317405621589e-9 +LookupCoin/4/4/3100,1.2525392523923255e-6,1.251729706388684e-6,1.253521581527334e-6,2.914692348843169e-9,2.5332203917450785e-9,3.6522269496455272e-9 +LookupCoin/4/125/100100,1.260774655999151e-6,1.258804266021221e-6,1.2665097440576978e-6,9.852196327494622e-9,4.304536400104611e-9,2.0258395020026988e-8 +LookupCoin/4/2500/2000100,1.2643632216987251e-6,1.2630032246538064e-6,1.2656822810057662e-6,4.334257923244687e-9,3.457742541748888e-9,5.22087199050318e-9 +LookupCoin/13/1/10100,1.2624070567558792e-6,1.2606154235219343e-6,1.2640424050493419e-6,5.657152523515489e-9,4.561599956711443e-9,7.417663438396113e-9 +LookupCoin/13/4/10100,1.2514256046427844e-6,1.2505411221705368e-6,1.25220945382555e-6,2.7559177095290204e-9,2.2419249567489397e-9,3.6490013282809864e-9 +LookupCoin/13/125/100100,1.2516682174012342e-6,1.2494080668363907e-6,1.25599113162234e-6,1.0356156217694294e-8,5.347239956327251e-9,1.845529845521035e-8 +LookupCoin/13/2500/2000100,1.2513709932311224e-6,1.2499746607215296e-6,1.2527092313776355e-6,4.4801455294860196e-9,3.800152944697293e-9,5.2497237732200065e-9 +LookupCoin/125/1/100100,1.2566103108676568e-6,1.255628700812506e-6,1.2575111947018028e-6,3.2302262628515648e-9,2.791524531422057e-9,3.8143780305339686e-9 +LookupCoin/125/4/100100,1.2514828459336215e-6,1.2477222292612055e-6,1.254612459913698e-6,1.1357087989549857e-8,9.45455176911453e-9,1.383532734188531e-8 +LookupCoin/125/125/100100,1.2510536713395532e-6,1.2486776378617943e-6,1.253130098221779e-6,7.604087462788487e-9,6.681597085163331e-9,9.422041323534413e-9 +LookupCoin/125/2500/2000100,1.257567022561272e-6,1.2568076079972548e-6,1.2586232567348466e-6,3.16296838231096e-9,2.6942744714791043e-9,4.065265294010724e-9 +LookupCoin/1250/1/1000100,1.2437022703562684e-6,1.2426624497194861e-6,1.2448352355537035e-6,3.6639170247051537e-9,3.0754055871693162e-9,4.6664050139976854e-9 +LookupCoin/1250/4/1000100,1.2552913141875582e-6,1.2538565802582663e-6,1.2564437487245099e-6,4.248705024921862e-9,3.469885621142994e-9,5.850796247354429e-9 +LookupCoin/1250/125/1000100,1.2527903228863225e-6,1.2518855914459804e-6,1.2537844352544552e-6,3.2593544529421823e-9,2.742839194604889e-9,3.855959694739642e-9 +LookupCoin/1250/2500/2000100,1.244355189731791e-6,1.2437611615642397e-6,1.2450840154318082e-6,2.114101048001732e-9,1.8593202860339957e-9,2.4700062670136815e-9 +LookupCoin/2500/1/2000100,1.2616953743537094e-6,1.2607823671479182e-6,1.2625869674557756e-6,2.995673224252523e-9,2.5848501095906772e-9,3.497831620701429e-9 +LookupCoin/2500/4/2000100,1.2324862369243195e-6,1.231432022400554e-6,1.2338560076276956e-6,4.090214148756135e-9,3.220166680385365e-9,5.312793659204946e-9 +LookupCoin/2500/125/2000100,1.2501426989566735e-6,1.2490513642391722e-6,1.2511800621045136e-6,3.5565143042767577e-9,2.9193085819710178e-9,4.317790069989673e-9 +LookupCoin/2500/2500/2000100,1.2684506473527835e-6,1.2663866623438072e-6,1.2700234602016789e-6,6.255223338613385e-9,5.122911802979287e-9,8.695620223015002e-9 +LookupCoin/2500/1/20001,1.2205950702764077e-6,1.2194837679049681e-6,1.2215739595305359e-6,3.5885412220455425e-9,3.041070733950513e-9,4.345775209121243e-9 +LookupCoin/1/2500/20001,1.225552033705855e-6,1.224475993667657e-6,1.2267310935149546e-6,3.870212721701195e-9,3.1775642399066607e-9,4.993592546496145e-9 +LookupCoin/1250/1250/10001,1.2131187397265325e-6,1.2115373232538786e-6,1.2147049505409275e-6,5.283426708698358e-9,4.755641727910896e-9,5.863281683071315e-9 +LookupCoin/1/1/98,1.2501521377877466e-6,1.2495341913932788e-6,1.2507217872067047e-6,1.9895907484626213e-9,1.4706491314737957e-9,3.3031274098784845e-9 +LookupCoin/1/1/1,1.2075501958236993e-6,1.2068021890272933e-6,1.208262129306143e-6,2.4058069615692213e-9,2.0194049677111022e-9,2.8733377667621385e-9 +LookupCoin/1895/2345/15963058,1.2803196379252948e-6,1.2781771197173325e-6,1.2824991274173064e-6,7.762986271918989e-9,6.828295807122626e-9,8.860257555658608e-9 +LookupCoin/370/2076/12038625,1.280187988079581e-6,1.2788960629861599e-6,1.2812234664338074e-6,3.6888829156735294e-9,3.005689382197591e-9,4.531610661491176e-9 +LookupCoin/2265/757/15420120,1.2794228186796374e-6,1.2775800846507617e-6,1.2806995495549277e-6,5.042315540484943e-9,3.2890802919642043e-9,7.1587364600981135e-9 +LookupCoin/709/489/10818411,1.2926044931678004e-6,1.2910920599573055e-6,1.2938738364742565e-6,4.59334649311881e-9,3.834567590327339e-9,5.643568309075777e-9 +LookupCoin/1974/1712/7151511,1.2618735333861445e-6,1.2602185905997524e-6,1.2632714749891885e-6,5.303975479948274e-9,4.335998165513941e-9,7.595794971707872e-9 +LookupCoin/2249/2078/18765656,1.2768198259782786e-6,1.2760612499536146e-6,1.2776866455140164e-6,2.782660538142238e-9,2.2964653023942013e-9,3.3936086904482942e-9 +LookupCoin/1902/2110/25016160,1.2800125082778773e-6,1.2782090687092827e-6,1.2813538547667959e-6,5.2249049550227564e-9,3.726430052955547e-9,8.966757032776342e-9 +LookupCoin/344/276/2585868,1.2748221163951422e-6,1.2736786979195662e-6,1.2758810964221625e-6,3.5967301348288155e-9,2.9547496393505218e-9,4.371301981521861e-9 +LookupCoin/1815/2039/32405983,1.2881442260618426e-6,1.2846214351971028e-6,1.290809590793673e-6,9.782581561579647e-9,7.975572864826726e-9,1.2664604408656405e-8 +LookupCoin/2407/1150/14459754,1.261742711763931e-6,1.260490055540015e-6,1.262856050041063e-6,3.916552884020715e-9,3.1311750666188257e-9,5.139741809384566e-9 +LookupCoin/51/53/403370,1.2690691201019735e-6,1.2666972707436046e-6,1.2719904736100445e-6,8.644027945417467e-9,6.895220410010281e-9,1.0643318074188051e-8 +LookupCoin/114/2185/15518688,1.2734454001566559e-6,1.2714482679541691e-6,1.2754859090015847e-6,7.129261241642667e-9,6.113117766803054e-9,8.385862555340417e-9 +LookupCoin/1930/184/11964450,1.2646806726004963e-6,1.2619186472531779e-6,1.266631620388074e-6,7.81500116526586e-9,5.318924791154326e-9,1.2112131735135537e-8 +LookupCoin/1661/1441/18361252,1.2793428921774997e-6,1.2773290456115479e-6,1.2816965978336147e-6,6.9161326406910465e-9,5.860419402064908e-9,8.104524793474994e-9 +LookupCoin/1079/1519/10120950,1.2176172342733113e-6,1.215354493542573e-6,1.219484840382208e-6,6.576382648263217e-9,4.955915665560883e-9,9.834786651184058e-9 +LookupCoin/1583/878/18323361,1.273901063799558e-6,1.2724958995911544e-6,1.2752668463417309e-6,4.382471116625853e-9,3.7191484251445385e-9,5.1011845508551176e-9 +LookupCoin/1750/2264/9958850,1.2792231288620218e-6,1.2773527430679643e-6,1.2809795453721968e-6,6.563524166291678e-9,5.620592207284027e-9,7.797812255973995e-9 +LookupCoin/2277/146/14590215,1.2736997031304613e-6,1.2729404628754282e-6,1.274678589065324e-6,2.803802651941421e-9,2.397116093816526e-9,3.337932466090993e-9 +LookupCoin/434/1476/9160680,1.2950377927217072e-6,1.292177950010784e-6,1.2971424929530197e-6,8.517874522069e-9,6.978396259287523e-9,1.0606971559804377e-8 +LookupCoin/1600/323/16538892,1.2748475569688066e-6,1.2739374353277782e-6,1.2757741071194235e-6,3.009126866839188e-9,2.5215172882163673e-9,3.6210540961781523e-9 +LookupCoin/1278/2268/25393200,1.2748429228153157e-6,1.2731909498703963e-6,1.2767655913677555e-6,5.8759116310050834e-9,5.136063002980486e-9,6.93144062101209e-9 +LookupCoin/2037/2155/12391965,1.286507969537781e-6,1.2851082842137748e-6,1.2879782385199171e-6,4.656354491627198e-9,3.924392590758368e-9,5.7189333877099e-9 +LookupCoin/698/2337/24505212,1.3004041448864844e-6,1.2990036884776086e-6,1.302198653199329e-6,5.342213005092348e-9,4.446898938496697e-9,6.400925016937013e-9 +LookupCoin/2083/2136/16163356,1.2764223683796965e-6,1.2747326749110076e-6,1.278022885417272e-6,5.193619740804341e-9,4.18253795872677e-9,6.50739439434995e-9 +LookupCoin/671/776/6029316,1.2915448262587781e-6,1.290620114288026e-6,1.292449612633099e-6,3.1655151644047537e-9,2.650509570099081e-9,4.201734900482966e-9 +LookupCoin/59/2345/34989265,1.288189387415324e-6,1.2857572996775002e-6,1.2894313736155252e-6,5.77855506267552e-9,3.286634406761636e-9,9.23067395758222e-9 +LookupCoin/900/2286/14536575,1.2448490575673767e-6,1.2436205509277125e-6,1.2461113424391198e-6,4.214766252418104e-9,3.5105664402150484e-9,5.402356168004765e-9 +LookupCoin/832/999/2603762,1.2469669931453683e-6,1.245833580412049e-6,1.2481197787736745e-6,3.835242006275528e-9,3.1092729510819287e-9,5.04970050588965e-9 +LookupCoin/1680/1508/22826065,1.2880012317351417e-6,1.2868962639461852e-6,1.289267171137826e-6,4.1157409135944946e-9,3.4279524178612484e-9,5.041552368721841e-9 +LookupCoin/1002/1135/6899280,1.2615340362439734e-6,1.2596000174105259e-6,1.2631098592873918e-6,5.794501833559887e-9,4.562340482651247e-9,7.436081363681221e-9 +LookupCoin/1359/1152/11261320,1.2817921429788798e-6,1.280692690514904e-6,1.282766878523355e-6,3.260336727262534e-9,2.686850069925233e-9,4.0389013073466375e-9 +LookupCoin/1479/1854/13803006,1.2740944860786948e-6,1.272017359375449e-6,1.275593228992704e-6,6.013280935327777e-9,4.97075917451662e-9,8.14866656090185e-9 +LookupCoin/1228/1674/4136274,1.2804318087322261e-6,1.2793348926092004e-6,1.281654185953536e-6,3.624950116338036e-9,2.9043725188905854e-9,4.939386088033429e-9 +LookupCoin/657/1400/17092726,1.281053127582082e-6,1.2791792176585762e-6,1.2829306152492005e-6,6.308782440142078e-9,5.0754542799941174e-9,7.739057463022068e-9 +LookupCoin/2273/210/18379980,1.280677680587168e-6,1.2788447475995189e-6,1.282026514602082e-6,5.306289383708538e-9,3.7157331580635896e-9,7.348475104890475e-9 +LookupCoin/2379/373/14176605,1.2663163225985433e-6,1.2639302078289512e-6,1.2683386698387479e-6,7.23990316849903e-9,6.1218650310142794e-9,8.597931932342572e-9 +LookupCoin/2027/609/23188880,1.295105567032933e-6,1.2940425166399068e-6,1.2961731866357902e-6,3.728919832353806e-9,3.274942293144146e-9,4.328517923189467e-9 +LookupCoin/1863/1686/28971432,1.2825169420362135e-6,1.2804928385281182e-6,1.2845252525717386e-6,7.275604141359334e-9,6.057458607922365e-9,8.691833143851719e-9 +LookupCoin/52/1791/22792666,1.281709793395133e-6,1.2801005292324194e-6,1.283403098669843e-6,5.266251041537131e-9,4.52760161581891e-9,6.151824896588823e-9 +LookupCoin/2352/1129/26569604,1.2778269348736196e-6,1.2757465332763327e-6,1.2796725671718388e-6,6.6653617265910815e-9,5.072710668827788e-9,1.0249419563026495e-8 +LookupCoin/1246/573/6110997,1.2793683625071125e-6,1.277896122360298e-6,1.2809199696787995e-6,4.968435244913596e-9,4.259098678716503e-9,5.959230769465271e-9 +LookupCoin/310/1554/15670447,1.2762542093004263e-6,1.274810442212931e-6,1.2776051488945713e-6,4.816180265316213e-9,4.167931733864282e-9,5.830428336731485e-9 +LookupCoin/1294/1547/16509584,1.2773846030504825e-6,1.2763117660169196e-6,1.2783798666693647e-6,3.465517844763897e-9,2.884712446351482e-9,4.119128215253205e-9 +LookupCoin/1129/448/6962901,1.2807023889182653e-6,1.279431567712355e-6,1.2822567656222109e-6,4.7306819714227345e-9,3.88206505602893e-9,5.757701461919527e-9 +LookupCoin/1589/1186/9012099,1.259328193086861e-6,1.2582289028982644e-6,1.2603655232997637e-6,3.731909085159e-9,3.1385094267051278e-9,4.5413734210007086e-9 +LookupCoin/1625/1893/22423821,1.268217566328228e-6,1.2661110426900448e-6,1.270600590015182e-6,7.536873955700692e-9,6.4829438363242555e-9,8.636468990921138e-9 +LookupCoin/9/1946/18177584,1.2958286550753203e-6,1.2942435964656242e-6,1.2972844012060394e-6,5.074835798824309e-9,3.862947517569473e-9,7.113544720904308e-9 +LookupCoin/2003/828/10528425,1.2660119891220907e-6,1.265114808268792e-6,1.2669678059247464e-6,3.0961043223970374e-9,2.602134311717419e-9,3.727819682601455e-9 +LookupCoin/876/2425/24813879,1.2695039120707998e-6,1.2683998534998996e-6,1.2710728327069194e-6,4.522253022851903e-9,3.241285459336524e-9,7.041325855313811e-9 +LookupCoin/1656/1408/10424602,1.2722888624293668e-6,1.2707823387853345e-6,1.273713506724683e-6,4.962874014529833e-9,4.1673847114882446e-9,5.865926525726256e-9 +ValueContains/310/31,1.150224079634047e-6,1.1484029171593576e-6,1.1520655872900477e-6,6.005570260918549e-9,4.862342923346793e-9,7.521077913330694e-9 +ValueContains/310/0,1.06384320106322e-6,1.062191515033955e-6,1.0654378642108599e-6,5.509382275152861e-9,4.581027672568637e-9,6.9098851874577475e-9 +ValueContains/310/310,1.7619305168090704e-6,1.7586779792752773e-6,1.7652600884404835e-6,1.130839096873276e-8,9.41898501836534e-9,1.4108118237577274e-8 +ValueContains/3100/0,1.0705970595310977e-6,1.0696262985135277e-6,1.0713713385821135e-6,2.872487380202136e-9,2.4019278496237887e-9,3.6053075163534896e-9 +ValueContains/3100/0,1.0657043929147226e-6,1.0642775083128504e-6,1.0671113447204667e-6,4.743608263663756e-9,3.889703167539578e-9,5.989574559564032e-9 +ValueContains/3100/3100,1.1894146744057842e-5,1.1871084222520173e-5,1.191767193116453e-5,7.663599053135675e-8,6.613215443182404e-8,9.643739250799068e-8 +ValueContains/31000/0,1.0677156355522858e-6,1.0654259909394951e-6,1.0698616098158728e-6,7.893785110339014e-9,6.182586930187335e-9,1.016832064207399e-8 +ValueContains/31000/0,1.0676225905277226e-6,1.0666709296050532e-6,1.0684853389377288e-6,2.8139786554644567e-9,2.2748535065168243e-9,3.7035014342306457e-9 +ValueContains/31000/0,1.0689765323263212e-6,1.0677305291841052e-6,1.0702146129018692e-6,4.153616760933364e-9,3.294918839189322e-9,5.552405671833423e-9 +ValueContains/31000/31000,1.3989070972469196e-4,1.3961275529108828e-4,1.4014140206640736e-4,8.671153993656169e-7,7.6414975418358e-7,9.882067921741445e-7 +ValueContains/1/1,1.1103542267638899e-6,1.1091545938139845e-6,1.1115909737856854e-6,4.205783682685009e-9,3.5546448746111783e-9,5.62531694174738e-9 +ValueContains/3100/0,1.0710438033081753e-6,1.0704010953841335e-6,1.0718462620934376e-6,2.488484444011733e-9,2.0557877847046803e-9,3.0489873474860437e-9 +ValueContains/100100/0,1.0645328169031105e-6,1.0622162475708715e-6,1.066656853367623e-6,7.602979479271493e-9,6.4343569983388315e-9,9.00929760184189e-9 +ValueContains/1000100/0,1.066009615081739e-6,1.0644317487918624e-6,1.0674781132396028e-6,5.059237602185728e-9,4.298984305788049e-9,5.899498444881504e-9 +ValueContains/1/0,1.0707510664994408e-6,1.0688014263040615e-6,1.0744053224110398e-6,8.653290657117377e-9,5.716417744402521e-9,1.4758666889717379e-8 +ValueContains/651/6510,1.8768293331625005e-5,1.8735623037201094e-5,1.8834433602150336e-5,1.479036964808042e-7,8.682086466352637e-8,2.6347552785518823e-7 +ValueContains/6002/6002,1.2977825325783861e-6,1.295350415288182e-6,1.3000088661210938e-6,7.269569584734367e-9,4.743744781624348e-9,1.0786484439189123e-8 +ValueContains/0/0,1.0658809918087003e-6,1.064642141097276e-6,1.0670292955565495e-6,4.374952858028444e-9,3.608067388398209e-9,5.251828914098139e-9 +ValueContains/0/0,1.0559905086366154e-6,1.0532986959513952e-6,1.05962723226345e-6,1.0680616302731096e-8,8.108403376724673e-9,1.6991111459695734e-8 +ValueContains/310/0,1.0716910600781161e-6,1.0706227908410502e-6,1.072598412217162e-6,3.2668191835731764e-9,2.88482953898635e-9,3.851011348259737e-9 +ValueContains/3100/0,1.065442367224129e-6,1.0639547859810193e-6,1.0687240823022984e-6,7.274364500262141e-9,3.739654571820177e-9,1.4891287855036637e-8 +ValueContains/31000/0,1.067519833120599e-6,1.0670093260065182e-6,1.068122613480877e-6,1.866640161684788e-9,1.4687606205704114e-9,2.368675885581133e-9 +ValueContains/1388240/1131480,5.830377894608075e-4,5.821675362234542e-4,5.841232073966954e-4,3.369025104679992e-6,2.834202732795799e-6,4.046879330172387e-6 +ValueContains/1230323/564167,6.957637639708246e-5,6.955956916495848e-5,6.959694875467544e-5,6.312446495406844e-8,4.809150972110265e-8,9.619774963274347e-8 +ValueContains/4035324/2503148,2.4917818695306486e-4,2.488740279681662e-4,2.504652388499471e-4,1.7966337495919435e-6,3.3382868647699937e-7,4.077061376227551e-6 +ValueContains/4797225/1867905,1.1298833376394714e-4,1.129045361082674e-4,1.1307031864043225e-4,2.854406184222403e-7,2.391807868462668e-7,3.5618050652586186e-7 +ValueContains/10835055/9374274,1.5335386801324598e-3,1.5318350982017343e-3,1.5379264227913564e-3,8.543138429232696e-6,3.908796093951306e-6,1.5229404241807767e-5 +ValueContains/12920960/975284,7.787465365647193e-5,7.78420278708246e-5,7.792727123487767e-5,1.3934696167567474e-7,1.0577024852677797e-7,2.0650866021535924e-7 +ValueContains/4708200/3670800,3.2189371844861713e-4,3.2150494682355317e-4,3.231951907590193e-4,2.1279453801609014e-6,6.057641810259562e-7,4.770434654200116e-6 +ValueContains/5032730/2914202,4.4632291921110087e-4,4.459043462632429e-4,4.475786076834567e-4,2.320167134598466e-6,8.420951551137534e-7,4.246168716058968e-6 +ValueContains/2774306/2038766,2.0218706694471707e-4,2.019965715302176e-4,2.028792056625027e-4,1.1025374870853495e-6,3.513069810941506e-7,2.4451455148839037e-6 +ValueContains/4020059/3892243,5.906132100414774e-4,5.903243585569346e-4,5.913624956317791e-4,1.470087000916268e-6,6.975667267168607e-7,2.65762554322302e-6 +ValueContains/4886109/3662556,3.2147460519542283e-4,3.213241376324112e-4,3.217071380767817e-4,5.938081388368038e-7,3.9546371750080744e-7,1.0364500615543388e-6 +ValueContains/5235852/1199292,1.372392804691373e-4,1.3720117227167361e-4,1.3729818364340758e-4,1.6202421861255058e-7,9.12126479788811e-8,2.5458418247796685e-7 +ValueContains/2945850/1345990,7.977577086502939e-5,7.975265920392309e-5,7.980776844774855e-5,9.408103233206765e-8,6.939296252705069e-8,1.4176818513985068e-7 +ValueContains/980343/549990,1.3848510081532306e-4,1.3836134411876637e-4,1.386279615391105e-4,4.397023092391429e-7,3.5175845858049713e-7,5.311761295383437e-7 +ValueContains/4713406/3666582,3.184150609185994e-4,3.1827502634776004e-4,3.1857087934551574e-4,4.960888019016048e-7,3.9488356265782485e-7,6.234062993995696e-7 +ValueContains/4392192/174838,1.9185488022869813e-5,1.917432377290978e-5,1.9196127357667117e-5,3.668720069998244e-8,3.146128801545269e-8,4.6060045380628914e-8 +ValueContains/5993043/1393056,1.3698697007419702e-4,1.3694169384738768e-4,1.3703898844114826e-4,1.6315053698114676e-7,1.2765054957267603e-7,2.4922858841547223e-7 +ValueContains/2841216/258944,4.4569751518569055e-5,4.455853857311547e-5,4.458634102791225e-5,4.4622445698346663e-8,3.3782123234928744e-8,6.043866835102693e-8 +ValueContains/16889220/6440265,9.630807665046082e-4,9.626643496364997e-4,9.638691403644825e-4,1.969808428789295e-6,1.4020089798171394e-6,3.2323864058579634e-6 +ValueContains/3416075/179400,2.1114615681243928e-5,2.110543246119949e-5,2.1123974058483687e-5,3.1805446389729774e-8,2.5908251759538914e-8,4.22730124319113e-8 +ValueContains/10474516/6931665,9.064818915605667e-4,9.05987443309439e-4,9.072612704764007e-4,2.036234445019851e-6,1.4482572524718826e-6,2.820824620618682e-6 +ValueContains/23280000/14317200,2.6943367275251776e-3,2.6935838951761227e-3,2.6954131081267352e-3,2.858873305393497e-6,1.8261059946685073e-6,4.911560735731439e-6 +ValueContains/17607912/400589,2.509700334064018e-5,2.5090201730613753e-5,2.5105845387826096e-5,2.4304443668200548e-8,1.9937384758448563e-8,3.1795332354781644e-8 +ValueContains/18476472/2509380,1.595515446835561e-4,1.5948902551541017e-4,1.5969817373887767e-4,3.14792644619481e-7,1.589795748224896e-7,5.329421866453197e-7 +ValueContains/2276082/130528,8.041209938911082e-6,8.036901279192637e-6,8.044849043957893e-6,1.2820036444411411e-8,1.0776473394324325e-8,1.5535420296847403e-8 +ValueContains/3930056/2725737,3.1776002333520296e-4,3.1739194817070323e-4,3.179661744289935e-4,9.513836575001647e-7,5.650491562578674e-7,1.5340286373147029e-6 +ValueContains/3598356/380092,3.4536686380287794e-5,3.4399022056096784e-5,3.469292924889314e-5,4.806422245761377e-7,4.1350889124018223e-7,5.141444004997678e-7 +ValueContains/12169248/10889424,1.9602809428612435e-3,1.959506477247854e-3,1.9612077354371504e-3,2.937546561276068e-6,2.317477571806379e-6,4.106702668950206e-6 +ValueContains/142848/72416,1.614800770779478e-5,1.612640184397839e-5,1.6165503144045665e-5,6.261322158873831e-8,5.358060856632499e-8,7.382795473265937e-8 +ValueContains/28446/20658,7.336275590839956e-5,7.317459349934284e-5,7.357110721408839e-5,6.919130313477668e-7,6.130125155079317e-7,8.055478060102782e-7 +ValueContains/4093319/1247625,1.9056177958026678e-4,1.9051540553801757e-4,1.9062486788885537e-4,1.814675437951522e-7,1.3510555555817223e-7,2.66118650443016e-7 +ValueContains/12390235/7859709,1.2939251469556306e-3,1.2933431902760165e-3,1.294682410466329e-3,2.193951997280829e-6,1.6794123785165327e-6,2.835225981249992e-6 +ValueContains/6129818/4066035,6.062322109240712e-4,6.056020612027894e-4,6.074113543857627e-4,2.7384695691856397e-6,1.625285264130118e-6,4.472293627737563e-6 +ValueContains/1657800/1530702,3.6554774539165115e-4,3.653782969910462e-4,3.658347842664113e-4,8.17317508543419e-7,4.893817089973439e-7,1.2591133108369015e-6 +ValueContains/3304800/910440,1.4289209811072542e-4,1.4272768310138654e-4,1.430164460749529e-4,4.743737818229538e-7,3.692018891019297e-7,6.635150006708321e-7 +ValueContains/15869112/9918608,1.966922026999833e-3,1.965532162311767e-3,1.9684557580459637e-3,4.886900380572334e-6,3.8114339023972606e-6,6.5043272023058915e-6 +ValueContains/1535940/1437408,1.675079192369487e-4,1.6743898345902722e-4,1.675974683410271e-4,2.621316159867751e-7,2.0779990830234897e-7,4.0570627069547474e-7 +ValueContains/19866756/18316004,3.433782972066689e-3,3.431825291604356e-3,3.4371936732783457e-3,7.942605267700316e-6,4.4658213648082326e-6,1.543699282200521e-5 +ValueContains/2767554/101535,7.370376782582864e-6,7.367301893150696e-6,7.373809574781905e-6,1.1399966273118639e-8,9.46164017266115e-9,1.528392137629673e-8 +ValueContains/6418466/4957062,7.712746413388413e-4,7.705837930356645e-4,7.72257699804622e-4,2.691519911527554e-6,1.908409434797522e-6,3.620458138777805e-6 +ValueContains/3595660/2643280,5.897573926490326e-4,5.894703531110593e-4,5.901217699060191e-4,1.063906555408471e-6,8.012659689797687e-7,1.400088770302344e-6 +ValueContains/19078421/11705351,2.1984832793282365e-3,2.1976878588428382e-3,2.1994700112280448e-3,2.9207560746456993e-6,2.25976489043177e-6,4.385016227957237e-6 +ValueContains/2078188/690368,1.6287475493861336e-4,1.6277688884120615e-4,1.62957700148916e-4,3.0162048245436194e-7,2.560271912897383e-7,3.572126881676112e-7 +ValueContains/9108300/2616575,2.5582738803681283e-4,2.556821249609247e-4,2.560011799020167e-4,5.270886608887014e-7,4.213315620704924e-7,6.986846618352393e-7 +ValueContains/6916158/368406,3.802286624021897e-5,3.80151539227574e-5,3.8030383790436226e-5,2.629032044731183e-8,2.201626061128466e-8,3.195811927303817e-8 +ValueContains/8999515/5208710,8.056136157809999e-4,8.051642952842769e-4,8.065927838704155e-4,1.9952438976326107e-6,1.3453298416225953e-6,3.350980804138213e-6 +ValueContains/3590204/1011148,1.0520207337524529e-4,1.0517766716611235e-4,1.0523286251531954e-4,9.108695273412249e-8,6.679970571243264e-8,1.437262741780023e-7 +ValueContains/8618405/1525841,1.3447990003810246e-4,1.34435364937348e-4,1.345662890706284e-4,1.9738886556091444e-7,1.247201488379852e-7,3.4329718865165016e-7 +ValueContains/1090566/676218,3.652853539745162e-4,3.6521368175826543e-4,3.65390955680254e-4,3.044283349559993e-7,2.0695871997905786e-7,4.2463426025938833e-7 +ValueContains/17998150/4896483,5.460585925365607e-4,5.455005274479362e-4,5.46969339199242e-4,2.3611739251008407e-6,1.6155650868680277e-6,3.914730201986467e-6 +ValueContains/4799844/2492436,1.716249294942824e-4,1.7156983053522086e-4,1.7170664969734048e-4,2.3100847784072545e-7,1.6075694098077668e-7,3.441386203411614e-7 +ValueContains/1984837/245685,2.8775986614012295e-5,2.8704105825927887e-5,2.888419479974047e-5,2.891212852817797e-7,2.0878208775377933e-7,3.570018596709635e-7 +ValueContains/2142174/75164,1.3258165336340797e-5,1.3247097446542808e-5,1.3274550072140676e-5,4.469849048208671e-8,2.98946888580418e-8,6.098090781938885e-8 +ValueContains/14913261/8624418,1.5338686319268332e-3,1.5331670660293957e-3,1.5357364274093583e-3,3.656842792549137e-6,1.7468799923239558e-6,6.908436014702568e-6 +ValueContains/1707401/1316703,1.0862070605606819e-4,1.0860062436163804e-4,1.0866147173040616e-4,9.194726055446758e-8,5.269977898019595e-8,1.6790017195090266e-7 +ValueContains/4980024/1591128,1.3112143079769268e-4,1.3106926433345794e-4,1.3118613286673027e-4,1.9444865449562152e-7,1.4586150234421572e-7,2.6503330569164106e-7 +ValueContains/12956460/10548000,1.957508654239913e-3,1.95677647570763e-3,1.9583060351476274e-3,2.562461652561229e-6,1.9438229299769547e-6,3.602066047576493e-6 +ValueContains/8217775/5729209,1.0698956920126381e-3,1.0687585732563776e-3,1.0715867872757533e-3,4.868050250114949e-6,3.4296121068493134e-6,7.228146110756961e-6 +ValueContains/7272552/1557528,2.022156255589961e-4,2.0213498541107506e-4,2.022869607648368e-4,2.53115688383433e-7,1.9725970108425334e-7,3.691933219173594e-7 +ValueContains/10713400/2240361,1.812366193284897e-4,1.8116235779877508e-4,1.813766927053128e-4,3.332839427048048e-7,1.612596811539039e-7,5.703943676029055e-7 +ValueContains/963590/240480,2.4903560578250308e-5,2.489362059974177e-5,2.4915891216710552e-5,3.661956008621002e-8,2.9660121160896844e-8,4.8637963844660726e-8 +ValueContains/2394639/1603701,2.859391048819322e-4,2.8576317224094007e-4,2.862141624524469e-4,7.468778052987474e-7,4.7542197032452347e-7,1.287212303358601e-6 +ValueContains/11033220/7677912,1.631541304212993e-3,1.6308410706675916e-3,1.6326555517465176e-3,2.914717684729703e-6,1.874019892893764e-6,4.933954966466973e-6 +ValueContains/491009/179958,6.889524112989753e-5,6.882464026662156e-5,6.897513676503781e-5,2.4796183246476124e-7,2.2431121147365143e-7,2.700409630551564e-7 +ValueContains/11084414/8896750,1.4232107805540568e-3,1.4225235585870345e-3,1.4243043895285736e-3,2.765726490585935e-6,1.711780295744547e-6,4.266028265120588e-6 +ValueContains/271467/172980,2.3894128756798898e-4,2.3877636199911618e-4,2.3910103920611503e-4,5.639201789091078e-7,4.84146265106951e-7,6.505974886269501e-7 +ValueContains/40089/14857,2.0954979970178162e-5,2.0917315871604934e-5,2.1000604057377935e-5,1.3379340441460844e-7,1.1198361996558905e-7,1.5957093576177045e-7 +ValueContains/1200337/1125892,2.339006505113107e-4,2.3366650649583206e-4,2.3418223480905142e-4,8.337769259963321e-7,6.576979972783795e-7,1.2112979799509469e-6 +ValueContains/1838826/428238,9.653993911295394e-5,9.648059017078725e-5,9.661753189516794e-5,2.2395968970038456e-7,1.5411237607620095e-7,3.3927380681589213e-7 +ValueContains/13389200/4701435,5.285062717968509e-4,5.279808745318598e-4,5.294051455991618e-4,2.3074935466244204e-6,1.5036910408140082e-6,3.6691863871758815e-6 +ValueContains/1360924/490784,6.47162531082863e-5,6.470281894065016e-5,6.473263563193671e-5,4.84700294875406e-8,3.856698702898866e-8,6.351389790864793e-8 +ValueContains/7060235/1710410,1.1332567192810901e-4,1.1326013541582326e-4,1.1345067846458714e-4,2.9390185807507663e-7,1.859520264861708e-7,4.5224611836576073e-7 +ValueContains/7168728/2925342,2.3019958166231518e-4,2.3005209069534727e-4,2.3028836665561712e-4,3.925922320298606e-7,2.704538532702406e-7,6.412876014677384e-7 +ValueContains/3062696/1755572,1.4265677665455828e-4,1.425505538475746e-4,1.4304286573034607e-4,6.32558480895347e-7,2.3363813145649228e-7,1.2681246047672563e-6 +ValueContains/11969680/6332685,9.617240714933561e-4,9.611633517332247e-4,9.623093765333572e-4,2.0511425912438474e-6,1.6481397327727508e-6,2.8499370524871487e-6 +ValueContains/12699336/2423394,2.031868348925432e-4,2.0306625300929392e-4,2.034224470500471e-4,5.943785919606138e-7,3.7321236608462653e-7,9.84547111295116e-7 +ValueContains/12861500/8116375,1.3066861599144667e-3,1.3056968758639396e-3,1.307842903177105e-3,3.6527969418481483e-6,2.8884249963033977e-6,4.5825585672189005e-6 +ValueContains/20953377/15412274,2.90334709367055e-3,2.9006281181731207e-3,2.909060092516673e-3,1.2912355593307847e-5,6.47157975795324e-6,2.2357280960906057e-5 +ValueContains/7975503/3657069,5.031441153067773e-4,5.009936984129138e-4,5.04852475034121e-4,6.607943723273288e-6,5.57902102994008e-6,7.3936978355426465e-6 +ValueContains/8992218/912254,6.007525093072982e-5,6.004279292609082e-5,6.013039079988352e-5,1.3889958907855164e-7,8.54974566307128e-8,2.1970939936341664e-7 +ValueContains/116157/96173,9.175802716744137e-6,9.166092411893076e-6,9.188875187795383e-6,3.897604192065501e-8,2.952711146139307e-8,5.281903213223849e-8 +ValueContains/5366844/1303239,7.892804244199633e-5,7.888257342229591e-5,7.898322612015493e-5,1.7485088997300327e-7,1.4493882112906774e-7,2.2651537843986237e-7 +ValueContains/14277360/5654400,7.593722407604015e-4,7.58819151047441e-4,7.603205576715492e-4,2.3443319112155012e-6,1.654684408460267e-6,3.634371237506103e-6 +ValueContains/2778300/1994220,3.865455187892309e-4,3.862213776945122e-4,3.8734584942507036e-4,1.631389705385232e-6,7.419321061731839e-7,3.1389138468626554e-6 +ValueContains/2625714/1714804,2.2752714411573664e-4,2.2748011187241212e-4,2.2759856575259196e-4,1.964998717496885e-7,1.219909353824142e-7,3.747787287802566e-7 +ValueContains/3694722/1318710,1.1303820545854332e-4,1.1294941990435116e-4,1.132438432832616e-4,4.206203474210641e-7,2.2367360602305687e-7,7.565624356871839e-7 +ValueContains/6103626/4472940,6.649648364049148e-4,6.642859692890245e-4,6.662788577883692e-4,3.1023889137297782e-6,1.8653117644462426e-6,5.4753211265038996e-6 +ValueContains/10497826/9042142,2.039619603141005e-3,2.0382483819400316e-3,2.042269702048698e-3,6.047705510960005e-6,3.755850538337618e-6,1.0035148338055982e-5 +ValueContains/1960059/1455077,1.1222745901610427e-4,1.1219456665476382e-4,1.1225918423301758e-4,1.0674095875053205e-7,9.045417886847991e-8,1.2991122074798892e-7 +ValueContains/2096406/150858,2.663133880325886e-5,2.6620253179459178e-5,2.6650375062978732e-5,4.743218932646712e-8,3.308943823306096e-8,6.909814199182092e-8 +ValueContains/12989004/5392182,6.886762998329002e-4,6.879156013965011e-4,6.897338691186196e-4,2.8565415615684417e-6,2.0936482685871293e-6,3.824954796850235e-6 +ValueContains/642390/173964,3.071113180708838e-5,3.067057367187396e-5,3.080765445618444e-5,2.006366456375042e-7,8.853559204569966e-8,3.8568429886307546e-7 +ValueContains/115482/27512,9.064147361675596e-5,9.051128570298819e-5,9.076600350655485e-5,4.360960850239288e-7,3.6452723098708387e-7,5.263913215392148e-7 +ValueContains/1328176/1141482,5.035514198409748e-4,5.032739606692311e-4,5.043542802297387e-4,1.4546264394098652e-6,6.335811471276296e-7,2.9006992241714765e-6 +ValueContains/7806181/100413,6.5512674297340936e-6,6.545302453209767e-6,6.563307233192391e-6,2.6380763024944244e-8,1.0592452441477217e-8,4.314270025865915e-8 +ValueContains/4788828/917676,1.503257594000041e-4,1.501594977377007e-4,1.5093315389857768e-4,9.360293386563395e-7,2.1254033773254456e-7,1.9290513829692186e-6 +ValueContains/5688024/263720,3.428285525167467e-5,3.427291719885072e-5,3.4297396798349265e-5,4.0382747853099325e-8,2.828644276513103e-8,6.248144683887384e-8 +ValueContains/6878420/3657938,6.592213508033889e-4,6.579409944279702e-4,6.61782605276198e-4,5.969530361920488e-6,3.3639617412526817e-6,1.056368392720555e-5 +ValueContains/19772224/4693360,5.019688315456157e-4,5.015567800541507e-4,5.026393294589733e-4,1.7682410268291807e-6,1.2422627569658219e-6,2.9274257767392108e-6 +ValueContains/6070955/3682305,4.5444711174498444e-4,4.539127267159825e-4,4.5536546997632376e-4,2.507300024949188e-6,1.454923133744795e-6,4.735308195468392e-6 +ValueData/0,8.583750684602916e-7,8.574665326043169e-7,8.593672673392311e-7,3.019532432241858e-9,2.525918801783744e-9,3.859878670706656e-9 +ValueData/310,8.622479689638347e-7,8.605672500396664e-7,8.648103017078753e-7,7.2690624608328786e-9,4.4613311775058174e-9,1.1985519761994768e-8 +ValueData/10010,8.679760570564036e-7,8.668919948859114e-7,8.688166572496762e-7,3.1436494074630504e-9,2.566988136838245e-9,3.859414335066352e-9 +ValueData/3100,8.651895304168579e-7,8.635567660820601e-7,8.68377293177932e-7,7.274978664063257e-9,4.00234479276707e-9,1.4126856409467756e-8 +ValueData/100100,8.669687589120348e-7,8.662696968005817e-7,8.677207774562702e-7,2.4328432559031664e-9,1.9818699647829177e-9,3.0084405929015068e-9 +ValueData/15500,8.620033290605479e-7,8.601017323033926e-7,8.64180231502215e-7,6.763766111300699e-9,5.473388596201153e-9,9.635853378707712e-9 +ValueData/500500,8.635517053593947e-7,8.625977813772622e-7,8.649292359253146e-7,3.872697426125699e-9,2.792966849032069e-9,7.201534792722501e-9 +ValueData/31000,8.651401887855943e-7,8.639573884016736e-7,8.671683404631164e-7,5.280922858119043e-9,3.203545718908386e-9,8.838853650342515e-9 +ValueData/1001000,8.686553559118597e-7,8.675512954191544e-7,8.698302057020482e-7,3.840040039265437e-9,3.3491324591863146e-9,4.606771014371211e-9 +ValueData/155000,8.633407657769235e-7,8.618473001994409e-7,8.659534728681274e-7,6.611926139611169e-9,3.965784474535508e-9,1.1796783950969659e-8 +ValueData/5005000,8.631610151530661e-7,8.62274699473225e-7,8.640843164043536e-7,3.1099003950571255e-9,2.4495893986312256e-9,4.123981446351906e-9 +ValueData/310000,8.624200507884241e-7,8.609144115467483e-7,8.640998456654391e-7,5.902359879858976e-9,4.798806862784285e-9,7.449559516496736e-9 +ValueData/10010000,8.617479489888499e-7,8.606856134681744e-7,8.632181644655082e-7,4.030719816077838e-9,3.1770701284302586e-9,5.258502071830932e-9 +ValueData/1,8.647281489320198e-7,8.630751278496909e-7,8.67717131597178e-7,7.475927221927825e-9,5.077563259036573e-9,1.2136672154558073e-8 +ValueData/31000,8.629482948630209e-7,8.618572645147149e-7,8.641970717600778e-7,4.036352013481435e-9,3.352360167330728e-9,5.030758305594242e-9 +ValueData/101000,8.642502711189975e-7,8.627574939708884e-7,8.677897321999737e-7,7.445541564282644e-9,4.285778092966304e-9,1.3798148237347443e-8 +ValueData/1001000,8.605807510105824e-7,8.595344575208356e-7,8.615716881169933e-7,3.4595517684568643e-9,2.8025622473994713e-9,4.617901156410846e-9 +ValueData/10001000,8.674760232551506e-7,8.65435156888973e-7,8.697780749953191e-7,7.293398231168419e-9,5.639873294500882e-9,1.0632486186487765e-8 +ValueData/1,8.628976109415359e-7,8.620633617102623e-7,8.636945055998371e-7,2.6436319220489336e-9,2.1577225430059305e-9,3.506243700016569e-9 +ValueData/1,8.658590429703182e-7,8.644805715449798e-7,8.671149054232529e-7,4.591967319687212e-9,3.392322890780751e-9,6.35394360044245e-9 +ValueData/1,8.62546537252087e-7,8.618076159297699e-7,8.632137753826199e-7,2.5034929311122895e-9,2.102436684275761e-9,3.216445598585178e-9 +ValueData/372,8.683318818570483e-7,8.667003545889679e-7,8.70711336141621e-7,6.324326624146734e-9,4.6436052173446084e-9,1.0302026162313797e-8 +ValueData/4464,8.649420667261587e-7,8.635976923126619e-7,8.663944821563864e-7,4.600199974975949e-9,3.6276915069870168e-9,6.342595914111486e-9 +ValueData/13671,8.621836066399538e-7,8.607545537631805e-7,8.639339465634156e-7,5.2894406678342995e-9,4.168378763242659e-9,7.552867529600776e-9 +ValueData/0,8.638839976642206e-7,8.622204912920894e-7,8.651359212702882e-7,4.6891676548751464e-9,3.7126557081964195e-9,6.833536396058405e-9 +ValueData/4004,8.687755701430774e-7,8.672040203903232e-7,8.698451743757732e-7,4.2749448478967725e-9,3.2764390996553346e-9,6.0852194132612024e-9 +ValueData/12012,8.626351380748289e-7,8.619028110455171e-7,8.6342430858083e-7,2.5748797720203776e-9,2.2648193161178535e-9,2.980620786944366e-9 +ValueData/0,8.633110769610172e-7,8.617934220363606e-7,8.659554148224579e-7,6.4618838033455365e-9,3.779736756099013e-9,1.1565819589841476e-8 +ValueData/0,8.717315273377249e-7,8.708462397323893e-7,8.727126362599277e-7,3.181469333554735e-9,2.6674612273499665e-9,4.021223672036579e-9 +ValueData/10001,8.682085604933698e-7,8.666907150939007e-7,8.697904543716352e-7,5.243826692680096e-9,4.350649370956428e-9,6.732689911204806e-9 +ValueData/2046773080,8.799061388020214e-7,8.792008028668604e-7,8.805626279053824e-7,2.2448106084562397e-9,1.9192179398398734e-9,2.7574601080049884e-9 +ValueData/212036748,8.817248518792184e-7,8.795805571093361e-7,8.841449629848211e-7,7.636509263682473e-9,6.304100924668804e-9,9.926381322050969e-9 +ValueData/842457891,8.846468399992824e-7,8.838726386882992e-7,8.854096299615428e-7,2.7405636928139936e-9,2.1634872449587907e-9,3.6214082931513867e-9 +ValueData/1265148432,8.775353471252502e-7,8.760186615094953e-7,8.787750555869387e-7,4.6510511746278936e-9,3.845323090587232e-9,6.428244290483821e-9 +ValueData/2079833328,8.871245102652917e-7,8.860994536790355e-7,8.880843358761959e-7,3.3896386011608883e-9,2.8845323562804078e-9,4.09624979941731e-9 +ValueData/333298856,8.763892754185485e-7,8.739233907783042e-7,8.783794665611568e-7,7.499928087631522e-9,5.57455881688526e-9,1.029714184751263e-8 +ValueData/194394200,8.758213993809808e-7,8.746616705724959e-7,8.770892192315209e-7,4.013306501018826e-9,3.4471099412729444e-9,4.760978234465088e-9 +ValueData/15594240,8.811059911832802e-7,8.797285463074717e-7,8.821858388885495e-7,4.231510270129174e-9,3.3224181335611978e-9,5.2776184173331745e-9 +ValueData/60887619,8.789218890659444e-7,8.778770750557923e-7,8.798066083748263e-7,3.3974148594250846e-9,2.9602513800304063e-9,3.91669753021462e-9 +ValueData/2368018402,8.766056945044401e-7,8.758465798328167e-7,8.77412439428283e-7,2.72174093839264e-9,2.2897807958991373e-9,3.3094397737258205e-9 +ValueData/478770116,8.824026191875146e-7,8.808969302178395e-7,8.835399806964488e-7,4.508845007523353e-9,3.335594839761039e-9,6.254914196480365e-9 +ValueData/1264181688,8.787092821676913e-7,8.775732104368867e-7,8.796549448400194e-7,3.309352242996296e-9,2.700318858307644e-9,3.996434015821737e-9 +ValueData/1486997792,8.855538404912347e-7,8.847650817010667e-7,8.862626916551618e-7,2.4243766982415683e-9,2.0534210316307303e-9,3.1014469095585945e-9 +ValueData/754380000,8.829660520397515e-7,8.813596863617722e-7,8.84493256111861e-7,5.6759422408998424e-9,4.775962911936064e-9,7.173472522901001e-9 +ValueData/542248410,8.848080315721519e-7,8.837155509922712e-7,8.858404379782492e-7,3.4113979775436517e-9,2.7709230329262894e-9,4.743294292970642e-9 +ValueData/240812208,8.82248245860847e-7,8.812235930097226e-7,8.831529718131394e-7,3.180157673301647e-9,2.804635756518382e-9,3.6562581384899457e-9 +ValueData/1430096430,8.831487351515866e-7,8.820109304068219e-7,8.843526457363097e-7,3.6796192478390113e-9,3.1453052830625004e-9,4.7694007939063e-9 +ValueData/40278060,8.887025823082332e-7,8.872861240982155e-7,8.899998293333394e-7,4.853953192000954e-9,4.0609242299469125e-9,5.965475937336031e-9 +ValueData/276139794,8.825935312234712e-7,8.815053325968616e-7,8.836463647300298e-7,3.740457881690753e-9,3.1694277739274094e-9,4.5045410443279354e-9 +ValueData/312405786,8.824801235655492e-7,8.810210499022529e-7,8.841640612966216e-7,5.247345792945051e-9,4.436751497574306e-9,6.263104631517754e-9 +ValueData/1289525373,8.789978180702858e-7,8.778567142989118e-7,8.801401207130893e-7,4.043223492385461e-9,3.3763030958322775e-9,4.983444956059326e-9 +ValueData/31492272,8.778572169491559e-7,8.761117425713348e-7,8.793492858631854e-7,5.272561585385543e-9,4.014663708583722e-9,7.276583163572152e-9 +ValueData/107184384,8.818378465988198e-7,8.809639623213274e-7,8.826669948563791e-7,3.004108398303013e-9,2.307779411352837e-9,3.852753761540837e-9 +ValueData/583905343,8.83828961604512e-7,8.818390644300958e-7,8.858609853324564e-7,6.581776541916642e-9,5.525618961692241e-9,7.97206751105742e-9 +ValueData/683098768,8.842559877704424e-7,8.826761640209831e-7,8.85398361920786e-7,4.671661852922675e-9,3.2234518102792736e-9,6.73891428029885e-9 +ValueData/18410476,8.807037356543371e-7,8.793896060399384e-7,8.822257921510808e-7,4.8501666794017144e-9,4.2471701844937496e-9,5.670458663849601e-9 +ValueData/23916060,8.784479084982687e-7,8.766470055807582e-7,8.796172901151588e-7,4.965995853960267e-9,3.6568614959707447e-9,6.8046482484269464e-9 +ValueData/1670926425,8.802093694529347e-7,8.784855781664408e-7,8.819685642539668e-7,5.523024556050195e-9,4.780765359440556e-9,6.473837976773515e-9 +ValueData/2204737164,8.751495378477806e-7,8.730528129770386e-7,8.767493601276111e-7,6.114803054956147e-9,4.713082615951264e-9,8.098771046739599e-9 +ValueData/331778304,8.848479366350919e-7,8.830743194512606e-7,8.869154398087849e-7,6.459236715926961e-9,5.694915311090601e-9,7.561013169713219e-9 +ValueData/11669328,8.841498121049638e-7,8.820410227786969e-7,8.857082001678627e-7,6.315449976254246e-9,4.589904519494843e-9,9.761196251911394e-9 +ValueData/69361750,8.845614323955318e-7,8.838609791243484e-7,8.851799955248878e-7,2.1639440482291287e-9,1.7518769438720122e-9,2.91661512776194e-9 +ValueData/66764032,8.804368945296171e-7,8.79024386297518e-7,8.819560810956152e-7,4.818506753070799e-9,4.078572328116291e-9,6.212185532793539e-9 +ValueData/2138824623,8.80788899955889e-7,8.794034491353684e-7,8.816824626465143e-7,3.5978812373689384e-9,2.7164081389282516e-9,5.145775669625586e-9 +ValueData/16735140,8.797893430418764e-7,8.779381583077851e-7,8.813413792971062e-7,5.570848939066517e-9,4.33314545524839e-9,7.191812944622222e-9 +ValueData/1912638040,8.81436773516627e-7,8.791460884856874e-7,8.838183849482439e-7,8.086677428227584e-9,6.863754700072674e-9,9.856846678501969e-9 +ValueData/416994786,8.790534159083372e-7,8.778542707284947e-7,8.806118527978725e-7,4.623282713701018e-9,3.692048697315199e-9,5.906247473388641e-9 +ValueData/1017225804,8.798898782710196e-7,8.785709040670462e-7,8.808448061951191e-7,3.580364013549222e-9,2.553151270070911e-9,5.160336164174102e-9 +ValueData/2303812413,8.853526422356704e-7,8.838839220225055e-7,8.864222933504421e-7,4.192930185092394e-9,3.3648720443019316e-9,5.638918598200019e-9 +ValueData/1550487771,8.893305795100219e-7,8.882044946857695e-7,8.905424814684701e-7,3.87085888728535e-9,3.3395650069478923e-9,4.6165101262819735e-9 +ValueData/557311536,8.795485409813151e-7,8.782372933480821e-7,8.807655026552791e-7,4.325070519418052e-9,3.5778737630018756e-9,5.451801213353196e-9 +ValueData/2632043889,8.818464237778249e-7,8.804411487573649e-7,8.837489882043619e-7,5.6849069044596965e-9,4.711346822750629e-9,6.837227978367089e-9 +ValueData/456462430,8.806541307195791e-7,8.790288892137052e-7,8.827440373022262e-7,6.14916657970514e-9,4.280603951726165e-9,1.0130355044661883e-8 +ValueData/394899960,8.808575223784704e-7,8.791850589358605e-7,8.827145376292514e-7,6.063752828887917e-9,5.074441594133893e-9,7.516666228118109e-9 +ValueData/2207228400,8.816810012488357e-7,8.798575201362776e-7,8.833856758051505e-7,6.056053763776328e-9,5.048248860538733e-9,7.70975767919364e-9 +ValueData/177159636,8.800849996021792e-7,8.787426385316129e-7,8.814600638305174e-7,4.373109959334574e-9,3.832763985306158e-9,5.205320572615689e-9 +ValueData/1339433522,8.8369697936304e-7,8.813462536764825e-7,8.872230576671357e-7,9.725150233244383e-9,6.7087681434698835e-9,1.6078748268940058e-8 +ValueData/300786640,8.818663093090303e-7,8.809416039998047e-7,8.830678482922842e-7,3.4575472984454566e-9,2.828033139291388e-9,4.658949749047596e-9 +ValueData/15867390,8.835614201246594e-7,8.826618631111632e-7,8.845275141042677e-7,3.3869367863197277e-9,2.813445505198861e-9,4.331455729538697e-9 +ValueData/692120268,8.832376503612247e-7,8.819562124491105e-7,8.84722434553226e-7,4.818378781933753e-9,4.004457571672129e-9,5.814914746474962e-9 +UnValueData/4,9.068421423883069e-7,9.061851879315348e-7,9.075469372063723e-7,2.3716507105819652e-9,1.984981132077256e-9,2.910120402091428e-9 +UnValueData/146,2.9053981872376373e-6,2.9011623792897847e-6,2.9094564963237254e-6,1.41087031722094e-8,1.1888875739712734e-8,1.684538919437561e-8 +UnValueData/1477,2.907111413865943e-6,2.9040351426743376e-6,2.9107160438364092e-6,1.1722585169505525e-8,1.0239625213678274e-8,1.3533701087446573e-8 +UnValueData/1424,1.959057274947463e-5,1.9584082643210964e-5,1.9599699159862095e-5,2.7663350371587914e-8,1.998773073048335e-8,4.518875236145975e-8 +UnValueData/14734,1.9530668905760955e-5,1.951921165483708e-5,1.9541567915562188e-5,3.781919240040988e-8,3.3077890275871535e-8,4.419280781957179e-8 +UnValueData/7104,9.655933642292642e-5,9.653139723454666e-5,9.658943571528039e-5,1.0030607319282723e-7,7.988801564224824e-8,1.2919696335077385e-7 +UnValueData/73654,9.584704253047986e-5,9.578387454994725e-5,9.592021181429972e-5,2.298477743663809e-7,1.9824512203122537e-7,2.7625798128862695e-7 +UnValueData/14204,1.9539873295628687e-4,1.953129313131433e-4,1.9547535630241525e-4,2.878289571323345e-7,2.3950686541812354e-7,3.669177852270458e-7 +UnValueData/147304,1.93966071639084e-4,1.9383708601387238e-4,1.9409713066233938e-4,4.364766920954256e-7,3.6711989177859925e-7,5.529617642161011e-7 +UnValueData/71004,1.1330109053186875e-3,1.1221081458933117e-3,1.1404336363814711e-3,2.8998910958958856e-5,2.533149833057745e-5,3.6442361282690845e-5 +UnValueData/736504,1.0916397816359352e-3,1.0889953921723629e-3,1.096596068415768e-3,1.1552661496214139e-5,5.941820435510034e-6,1.8388129989159933e-5 +UnValueData/142004,2.477771794323466e-3,2.4694298869129072e-3,2.4990196172122964e-3,3.9179072105422557e-5,2.028957489738693e-5,6.98673025622596e-5 +UnValueData/1473004,2.4601048481371355e-3,2.4502083290617567e-3,2.4813366173195416e-3,4.4844819826607744e-5,2.061743345585051e-5,7.180641490025408e-5 +UnValueData/23,1.3049032491374263e-6,1.3031286663478204e-6,1.3071530087461587e-6,6.570290203634116e-9,5.436206142884675e-9,7.993355508172386e-9 +UnValueData/14204,1.946569963557336e-4,1.9450583005103632e-4,1.9484030254448623e-4,5.261890092257365e-7,3.869223921703829e-7,7.086335871840278e-7 +UnValueData/24104,1.9495938063596527e-4,1.9488872545065825e-4,1.9506189336538642e-4,2.751536681324497e-7,2.18786289415935e-7,3.566909955074637e-7 +UnValueData/147304,1.948521636948272e-4,1.9456742487488558e-4,1.9587441255395857e-4,1.6446144902511552e-6,2.8362401483757646e-7,3.468789690953717e-6 +UnValueData/1384804,1.9521958382787111e-4,1.9517200204708117e-4,1.952707562669848e-4,1.6704652042495765e-7,1.3902808007457288e-7,2.2348042922625153e-7 +UnValueData/23,1.3052076954454706e-6,1.3035432771074695e-6,1.3082312923546576e-6,7.803860530317902e-9,4.711306614460252e-9,1.3487953164312609e-8 +UnValueData/23,1.3090297713192198e-6,1.3074075434157618e-6,1.3106717219773248e-6,5.446584556746961e-9,4.822819115074655e-9,6.235147687747254e-9 +UnValueData/23,1.311386557650879e-6,1.3088097018827555e-6,1.318287998798856e-6,1.3791990291854225e-8,6.311566356543765e-9,2.6689878350957732e-8 +UnValueData/196,3.382253929834435e-6,3.3795791241429007e-6,3.3851415479600903e-6,9.13658293127138e-9,7.703123817753193e-9,1.0991138050387187e-8 +UnValueData/2020,2.769565193646776e-5,2.7677945960578738e-5,2.7709181695998228e-5,4.956861112358337e-8,4.172359040001151e-8,5.96667485220342e-8 +UnValueData/5989,8.78085379449701e-5,8.778680857966858e-5,8.783528126893412e-5,8.119635179360278e-8,6.54034652565772e-8,1.0519581251380834e-7 +UnValueData/4,8.965831917220561e-7,8.948946698968546e-7,8.975403269391364e-7,3.978636354308552e-9,2.5987193605874843e-9,7.418045188187781e-9 +UnValueData/806,1.8966673571113277e-6,1.8949694196063312e-6,1.8981767711669928e-6,5.574189488354453e-9,4.691170079282188e-9,6.656525613718971e-9 +UnValueData/2011,3.344681350987945e-6,3.3431182788229923e-6,3.3463257102325986e-6,5.210658433772258e-9,4.358519179727488e-9,6.217635254393469e-9 +UnValueData/4,8.974299954678173e-7,8.959739565868861e-7,8.989408107594033e-7,4.982089757543563e-9,4.365105929330059e-9,5.718492070203431e-9 +UnValueData/4,9.033425126442837e-7,9.020432332067919e-7,9.063245352883466e-7,6.327583302498122e-9,3.2921135915017722e-9,1.2572453341446008e-8 +UnValueData/2521,1.3118266500716435e-6,1.3102686939287234e-6,1.3133088924617764e-6,5.006353386537573e-9,4.332272366330288e-9,5.895966419360369e-9 +UnValueData/114871409,0.10230505891494138,0.10058317513688018,0.1060228517330769,3.9575937235628664e-3,1.706012930590348e-3,6.337289958860899e-3 +UnValueData/7955480,1.059066568250036e-2,1.054941025225458e-2,1.066469347657569e-2,1.4679691606051868e-4,7.389838990047171e-5,2.262859181130299e-4 +UnValueData/106506417,3.917322197078474e-2,3.881943096081982e-2,3.9712471356661255e-2,9.042729147858443e-4,5.544791072843227e-4,1.308271556527119e-3 +UnValueData/133276873,6.741456710439037e-2,6.701763781806142e-2,6.816392717958127e-2,9.078776424407558e-4,2.815588758165663e-4,1.3521281422263936e-3 +UnValueData/149948764,9.55795649538881e-2,9.491136615231101e-2,9.670401054124038e-2,1.3827573370439122e-3,3.006590766389777e-4,1.7950013442465046e-3 +UnValueData/42684588,1.3889494518145267e-2,1.381745397196657e-2,1.4011565751498796e-2,2.4574506577860144e-4,1.546708243977333e-4,3.622194317290015e-4 +UnValueData/2328330,1.7326415313575014e-2,1.724567491226159e-2,1.7460563129391007e-2,2.4275882922429468e-4,1.6242407349935e-4,3.5579022994900096e-4 +UnValueData/1817236,3.865449638314245e-3,3.8509280349554734e-3,3.8911741896913103e-3,5.8295468960910656e-5,3.389961966563605e-5,9.564524858489304e-5 +UnValueData/5018602,1.5891421680943685e-3,1.5851306547804945e-3,1.6003460257286524e-3,2.0521513321048193e-5,1.1261232038182564e-5,3.745105940473335e-5 +UnValueData/298760976,0.11766399265782508,0.11564502278841766,0.1206492872326635,3.732029898764641e-3,2.0403676296774716e-3,5.893750786666082e-3 +UnValueData/61509608,6.0072692947197005e-2,5.964346627794168e-2,6.098620435515281e-2,1.0841719945671922e-3,4.035311641393299e-4,1.7142900966794275e-3 +UnValueData/148895716,6.846849368629207e-2,6.811004588534393e-2,6.90899393872007e-2,7.924890688677503e-4,4.422023058021328e-4,1.0826088099082309e-3 +UnValueData/187844113,8.633297566867744e-2,8.563077018518622e-2,8.740873092785477e-2,1.5681982014464574e-3,9.956656284170928e-4,1.9664579627141957e-3 +UnValueData/96560479,8.770143541766123e-2,8.717671918475793e-2,8.832345825309554e-2,9.760061846602834e-4,6.064344582901466e-4,1.4253389015221323e-3 +UnValueData/5750026,0.10621549403032114,0.10489735715140505,0.10826498204497276,2.7426436165770727e-3,1.9944064160961456e-3,3.3512016431393467e-3 +UnValueData/30569413,1.524956531653715e-2,1.5194020764744331e-2,1.5347827184350507e-2,1.7769511596496746e-4,1.0563131021824827e-4,2.704359805582908e-4 +UnValueData/50809742,0.173982669152066,0.17140015408928905,0.17786427413043723,4.497340793485504e-3,2.5847689502076937e-3,6.169008569130326e-3 +UnValueData/1357928,1.263916227803773e-3,1.2617772876837034e-3,1.2681803026916147e-3,9.761145025447326e-6,4.496233328702742e-6,1.7261333861755356e-5 +UnValueData/14682800,1.79078948324892e-2,1.7763709491000097e-2,1.8097800251242215e-2,4.0319671438415647e-4,3.331163869988835e-4,4.923810804524641e-4 +UnValueData/35229121,1.3747346986933686e-2,1.3686864398855775e-2,1.3827945906666876e-2,1.7003271753283423e-4,1.2209423987234437e-4,2.2591384882888379e-4 +UnValueData/76705843,7.926317495781751e-2,7.860985664384705e-2,8.01817899538825e-2,1.3416947365746988e-3,1.0023044305621205e-3,1.8301638796914843e-3 +UnValueData/2587834,1.0072654491918435e-3,1.006579665272486e-3,1.007918925387012e-3,2.4207415639179877e-6,2.0102539711100953e-6,3.109838767548292e-6 +UnValueData/13586134,4.3119579343260115e-3,4.299409219863996e-3,4.334282567032606e-3,5.248090508033591e-5,3.434124112779327e-5,7.88640397177202e-5 +UnValueData/65975004,2.086420145344267e-2,2.0723782770528217e-2,2.105179817385415e-2,3.723693542529308e-4,2.808698420265533e-4,4.973768407227705e-4 +UnValueData/86182573,2.7016138464276727e-2,2.6838813843668572e-2,2.7321639495573508e-2,4.94126432140938e-4,3.0545446453326047e-4,7.035530617835902e-4 +UnValueData/2202211,1.0083952425196518e-3,1.0074714840597537e-3,1.009350773723672e-3,3.2321764164667094e-6,2.326334966866852e-6,4.919550979849351e-6 +UnValueData/3626914,2.340661469725662e-2,2.325101441219348e-2,2.3599846081283526e-2,3.898602954368183e-4,3.1165357117876927e-4,4.877970278032597e-4 +UnValueData/210747884,7.666129932339702e-2,7.568121474679737e-2,7.74360370099367e-2,1.5723035737500244e-3,1.0643488402185951e-3,2.4860264919901553e-3 +UnValueData/279233266,0.15765267788293155,0.15265699509835365,0.1616267102064096,6.747794309759976e-3,3.3005427832788095e-3,1.0563488348119952e-2 +UnValueData/16616604,2.2555180938968182e-2,2.2366449410268073e-2,2.2760927396947996e-2,4.343505767591083e-4,3.0134831172842725e-4,6.684628228788499e-4 +UnValueData/1759604,6.871022698594183e-4,6.865251517819906e-4,6.876065820641521e-4,1.7576441565825255e-6,1.4225349192904165e-6,2.4124859130789056e-6 +UnValueData/8817504,3.660277346543132e-3,3.650840296025303e-3,3.676240838505098e-3,3.76614550435916e-5,2.59139591619614e-5,5.4328584851303237e-5 +UnValueData/8690724,8.495466347728154e-3,8.462949503605741e-3,8.543558245591977e-3,1.0109925449702793e-4,7.579850045069569e-5,1.4692845224440897e-4 +UnValueData/269407217,9.773407785408364e-2,9.647709665704203e-2,9.949821337229675e-2,2.4081049713073057e-3,1.9146099373921828e-3,3.021067724304747e-3 +UnValueData/2347534,6.565488314749383e-4,6.561091736415499e-4,6.568947216249377e-4,1.3397100185705023e-6,1.0417283899960786e-6,1.749216169723167e-6 +UnValueData/241997912,0.10299819983382638,0.10126023418639624,0.10516212606240832,3.1767174399700455e-3,2.015755310872373e-3,4.747485988133599e-3 +UnValueData/16206322,4.412175649838896e-2,4.384531305185683e-2,4.457355014969472e-2,6.750426038807096e-4,4.350987200721451e-4,1.0522920720509913e-3 +UnValueData/75211182,7.876843805210518e-2,7.784845081719732e-2,7.970574629544798e-2,1.6062835723028406e-3,1.29859849475821e-3,1.983599687129346e-3 +UnValueData/259779678,0.12150476825190708,0.12016215596425657,0.12267757131485268,1.9738532269128633e-3,1.4481775998724114e-3,2.604093798204616e-3 +UnValueData/196591531,0.10164275914003557,9.94190867461356e-2,0.10327495369219224,3.179082870929967e-3,2.2198253875588573e-3,3.7089635026842033e-3 +UnValueData/27275076,2.2996221114788298e-2,2.2849392289812063e-2,2.3206296322648732e-2,4.057237645367218e-4,2.594701360594864e-4,6.179159594195236e-4 +UnValueData/331610230,0.1171365568365824,0.11489116091979668,0.12029999292766054,3.91535831852172e-3,2.7972016546109098e-3,5.008812554304281e-3 +UnValueData/21224754,2.63530527376584e-2,2.6136459742041068e-2,2.656662110838686e-2,4.671014484644755e-4,3.776654235679501e-4,5.893222572907877e-4 +UnValueData/50641504,4.849716296275775e-2,4.79671129815398e-2,4.9104121905264406e-2,1.0509414776559748e-3,8.284674155887278e-4,1.3301064799037486e-3 +UnValueData/278609244,0.1137901517429522,0.11170282214131605,0.11637218942854642,3.49374511357859e-3,2.2884030916294575e-3,4.906859579362178e-3 +UnValueData/22452206,9.870166622796498e-3,9.825475612238323e-3,9.904329596564173e-3,1.0178622841891616e-4,7.314005343534361e-5,1.4808184908100952e-4 +UnValueData/92714696,0.17159821468715866,0.16569243465505895,0.17883632250928455,9.627202022390665e-3,4.858150670255226e-3,1.4862449007653556e-2 +UnValueData/22287115,1.3370951614584556e-2,1.3290041733088198e-2,1.3418783818341185e-2,1.5541067658567622e-4,9.75270219091354e-5,2.4039724813167723e-4 +UnValueData/2008654,5.493689912123631e-4,5.491444016020693e-4,5.496271868811518e-4,8.62199502496023e-7,6.974190917911312e-7,1.1903651550599839e-6 +UnValueData/21066567,4.760839045584599e-2,4.687811097533973e-2,4.8757656406249024e-2,1.7906345575714306e-3,8.154148988534519e-4,2.550632242102737e-3 From d9ab436a7a987300ba411ea490ab84100fce478a Mon Sep 17 00:00:00 2001 From: Yura Date: Thu, 2 Oct 2025 11:43:16 +0200 Subject: [PATCH 06/17] feat: add Logarithmic wrapper for modeling logarithmic complexity Add a new Logarithmic newtype wrapper in ExMemoryUsage that transforms size measures logarithmically. This enables linear cost models to effectively capture O(log n) runtime behavior by measuring log(size) instead of size directly. The wrapper computes max(1, floor(log2(size) + 1)) from any wrapped ExMemoryUsage instance, making it composable with existing size measures like ValueOuterOrMaxInner for operations with logarithmic complexity. This infrastructure supports proper costing of Value builtins like lookupCoin which has O(log max(m, k)) complexity. --- .../Evaluation/Machine/ExMemoryUsage.hs | 24 +++++++++++++++++++ 1 file changed, 24 insertions(+) diff --git a/plutus-core/plutus-core/src/PlutusCore/Evaluation/Machine/ExMemoryUsage.hs b/plutus-core/plutus-core/src/PlutusCore/Evaluation/Machine/ExMemoryUsage.hs index 101082a296f..84d1b59dc5e 100644 --- a/plutus-core/plutus-core/src/PlutusCore/Evaluation/Machine/ExMemoryUsage.hs +++ b/plutus-core/plutus-core/src/PlutusCore/Evaluation/Machine/ExMemoryUsage.hs @@ -14,6 +14,7 @@ module PlutusCore.Evaluation.Machine.ExMemoryUsage , IntegerCostedLiterally(..) , ValueTotalSize(..) , ValueOuterOrMaxInner(..) + , Logarithmic(..) ) where import PlutusCore.Crypto.BLS12_381.G1 as BLS12_381.G1 @@ -391,6 +392,29 @@ instance ExMemoryUsage ValueOuterOrMaxInner where where size = Map.size (Value.unpack v) `max` Value.maxInnerSize v +{-| A wrapper that applies a logarithmic transformation to another size measure. +This is useful for modeling operations with logarithmic complexity, where the cost +depends on log(n) where n is the size measure from the wrapped newtype. + +For example, @Logarithmic ValueOuterOrMaxInner@ can be used to model operations +that are O(log max(m, k)) where m is the number of policies and k is the max tokens +per policy. + +The memory usage is calculated as: @max 1 (floor (log2 size + 1))@ where size comes +from the wrapped newtype's ExMemoryUsage instance. +-} +newtype Logarithmic n = Logarithmic { unLogarithmic :: n } + +instance ExMemoryUsage n => ExMemoryUsage (Logarithmic n) where + memoryUsage (Logarithmic wrapped) = + case memoryUsage wrapped of + CostRose size _ -> + let sizeInteger :: Integer + sizeInteger = fromSatInt size + logSize = I# (integerLog2# sizeInteger) + in singletonRose $ max 1 (fromIntegral (logSize + 1)) + {-# INLINE memoryUsage #-} + {- Note [Costing constant-size types] The memory usage of each of the BLS12-381 types is constant, so we may be able to optimise things a little by ensuring that we don't re-compute the size of From 9da1a936e9755d4b984d24b97d7f646fd2509022 Mon Sep 17 00:00:00 2001 From: Yura Date: Thu, 2 Oct 2025 11:43:28 +0200 Subject: [PATCH 07/17] refactor: simplify Value benchmarks with Cardano-compliant constraints Refactor the Value benchmarking suite to use Cardano-compliant key sizes (32-byte max) and leverage the new Logarithmic wrapper for accurate modeling of logarithmic operations. Key changes: - Apply Logarithmic wrapper to lookupCoin and valueContains benchmarks for proper O(log n) cost modeling - Consolidate key generators from 4 functions to 2, eliminating duplication - Remove obsolete key size parameters throughout (keys always maxKeyLen) - Extract withSearchKeys pattern to eliminate repetitive code - Simplify test generation by removing arbitrary key size variations - Clean up lookupCoinArgs structure for better readability The refactoring reduces the module from 359 to 298 lines while improving clarity and ensuring all generated Values comply with Cardano's 32-byte key length limit. --- .../budgeting-bench/Benchmarks/Values.hs | 268 ++++++------------ 1 file changed, 83 insertions(+), 185 deletions(-) diff --git a/plutus-core/cost-model/budgeting-bench/Benchmarks/Values.hs b/plutus-core/cost-model/budgeting-bench/Benchmarks/Values.hs index ad1b8e56fbc..87a58f467dd 100644 --- a/plutus-core/cost-model/budgeting-bench/Benchmarks/Values.hs +++ b/plutus-core/cost-model/budgeting-bench/Benchmarks/Values.hs @@ -8,13 +8,12 @@ import Prelude import Common import Control.Monad (replicateM) -import Control.Monad.State.Strict (State) import Criterion.Main (Benchmark) import Data.ByteString (ByteString) -import Data.ByteString qualified as BS import PlutusCore (DefaultFun (LookupCoin, UnValueData, ValueContains, ValueData)) -import PlutusCore.Evaluation.Machine.ExMemoryUsage (ValueOuterOrMaxInner (..), ValueTotalSize (..)) -import PlutusCore.Value (Value) +import PlutusCore.Evaluation.Machine.ExMemoryUsage (Logarithmic (..), ValueOuterOrMaxInner (..), + ValueTotalSize (..)) +import PlutusCore.Value (K, Value) import PlutusCore.Value qualified as Value import System.Random.Stateful (StatefulGen, StdGen, runStateGen_, uniformByteStringM, uniformRM) @@ -35,114 +34,67 @@ makeBenchmarks gen = lookupCoinBenchmark :: StdGen -> Benchmark lookupCoinBenchmark gen = createThreeTermBuiltinBenchElementwiseWithWrappers - (id, id, ValueOuterOrMaxInner) -- Wrap Value argument to report outer/max inner size + (id, id, Logarithmic . ValueOuterOrMaxInner) -- Wrap Value argument to report outer/max inner size LookupCoin -- the builtin fun [] -- no type arguments needed (monomorphic builtin) (lookupCoinArgs gen) -- the argument combos to generate benchmarks for lookupCoinArgs :: StdGen -> [(ByteString, ByteString, Value)] lookupCoinArgs gen = runStateGen_ gen $ \(g :: g) -> do - let - -- Use common test values and add search keys - testValues = generateTestValues gen - - -- Also include additional random tests specific to lookupCoin - additionalTests = runStateGen_ gen $ \g' -> do - let keySizes = [0, 1, 30, 100, 1_000, 10_000, 20_000] - sequence $ - concat - [ -- Key size impact tests with large keys - [ generateLookupTest g' policySize tokenSize 100 10 - | policySize <- keySizes - , tokenSize <- [0, 30, 1_000, 20_000] - ] - , -- Budget-constrained tests (at 30KB limit) - [ generateBudgetTest g' policySize tokenSize 30_000 - | (policySize, tokenSize) <- - [ (20_000, 1) -- Huge policy, tiny token - , (1, 20_000) -- Tiny policy, huge token - , (10_000, 10_000) -- Both large - , (1, 1) -- Both tiny (max entries) - , (0, 0) -- Empty keys (pathological) - ] - ] - , -- Additional random tests for parameter spread - replicate 50 (generateRandomLookupTest g') + -- Add search keys to common test values + let testValues = generateTestValues gen + commonWithKeys <- mapM (withSearchKeys g . pure) testValues + + -- Additional tests specific to lookupCoin + let valueSizes = [(100, 10), (500, 20), (1_000, 50), (2_000, 100)] + additionalTests <- + sequence $ + concat + [ -- Value size tests (number of policies × tokens per policy) + [ generateLookupTest g numPolicies tokensPerPolicy + | (numPolicies, tokensPerPolicy) <- valueSizes ] - - -- Add search keys to common test values - - -- Add search keys to a value for lookup testing - -- Generates random keys that may or may not exist in the value - addSearchKeysToValue :: Value -> State StdGen (ByteString, ByteString, Value) - addSearchKeysToValue value = do - -- Generate search keys with varying sizes (mostly 30 bytes for consistency) - let keySize = 30 -- Standard key size used in most tests - searchPolicyId <- generatePolicyId keySize g - searchTokenName <- generateTokenName keySize g - pure (searchPolicyId, searchTokenName, value) - - commonWithKeys <- sequence [addSearchKeysToValue value | value <- testValues] + , -- Budget-constrained tests (at 30KB limit) + [generateBudgetTest g 30_000] + , -- Additional random tests for parameter spread + replicate 50 (generateRandomLookupTest g) + ] pure $ commonWithKeys ++ additionalTests +-- | Add random search keys to a Value (keys may or may not exist in the Value) +withSearchKeys :: (StatefulGen g m) => g -> m Value -> m (ByteString, ByteString, Value) +withSearchKeys g genValue = do + value <- genValue + key1 <- generateKeyBS g + key2 <- generateKeyBS g + pure (key1, key2, value) + -- | Generate lookup test with specified parameters generateLookupTest :: (StatefulGen g m) => g - -> Int -- Policy ID byte size - -> Int -- Token name byte size -> Int -- Number of policies -> Int -- Tokens per policy -> m (ByteString, ByteString, Value) -generateLookupTest - g - policyIdBytes - tokenNameBytes - numPolicies - tokensPerPolicy = do - value <- - generateConstrainedValue - numPolicies - tokensPerPolicy - policyIdBytes - tokenNameBytes - g - -- Generate lookup keys (may or may not exist in value) - searchPolicyId <- generatePolicyId policyIdBytes g - searchTokenName <- generateTokenName tokenNameBytes g - pure (searchPolicyId, searchTokenName, value) +generateLookupTest g numPolicies tokensPerPolicy = + withSearchKeys g (generateConstrainedValue numPolicies tokensPerPolicy g) -- | Generate budget-constrained test generateBudgetTest :: (StatefulGen g m) => g - -> Int -- Policy ID byte size - -> Int -- Token name byte size -> Int -- Total budget -> m (ByteString, ByteString, Value) -generateBudgetTest g policyIdBytes tokenNameBytes budget = do - value <- generateValueWithBudget policyIdBytes tokenNameBytes budget g - searchPolicyId <- generatePolicyId policyIdBytes g - searchTokenName <- generateTokenName tokenNameBytes g - pure (searchPolicyId, searchTokenName, value) +generateBudgetTest g budget = + withSearchKeys g (generateValueWithBudget budget g) -- | Generate random lookup test with varied parameters for better spread generateRandomLookupTest :: (StatefulGen g m) => g -> m (ByteString, ByteString, Value) generateRandomLookupTest g = do - policyIdBytes <- uniformRM (0, 20_000) g -- 0-20KB policy ID - tokenNameBytes <- uniformRM (0, 20_000) g -- 0-20KB token name - numPolicies <- uniformRM (1, 2_000) g -- 1-2000 policies - tokensPerPolicy <- uniformRM (1, 1_000) g -- 1-1000 tokens per policy - - -- Generate value with random parameters - value <- generateConstrainedValue numPolicies tokensPerPolicy policyIdBytes tokenNameBytes g - - -- Generate search keys - searchPolicyId <- uniformByteStringM policyIdBytes g - searchTokenName <- uniformByteStringM tokenNameBytes g - - pure (searchPolicyId, searchTokenName, value) + numPolicies <- uniformRM (1, 2_000) g + tokensPerPolicy <- uniformRM (1, 1_000) g + withSearchKeys g (generateConstrainedValue numPolicies tokensPerPolicy g) ---------------------------------------------------------------------------------------------------- -- ValueContains ----------------------------------------------------------------------------------- @@ -150,7 +102,7 @@ generateRandomLookupTest g = do valueContainsBenchmark :: StdGen -> Benchmark valueContainsBenchmark gen = createTwoTermBuiltinBenchElementwiseWithWrappers - (ValueOuterOrMaxInner, ValueTotalSize) + (Logarithmic . ValueOuterOrMaxInner, ValueTotalSize) -- Container: outer/maxInner, Contained: totalSize ValueContains -- the builtin fun [] -- no type arguments needed (monomorphic builtin) @@ -158,28 +110,19 @@ valueContainsBenchmark gen = valueContainsArgs :: StdGen -> [(Value, Value)] valueContainsArgs gen = runStateGen_ gen \g -> do - let - baseKeySizes = [0, 30, 1_000, 10_000] - baseValueSizes = [1, 10, 100, 1_000] - + let baseValueSizes = [1, 10, 100, 1_000] sequence $ concat - [ -- Standard key tests with varying value sizes (original Size-based tests) - [ generateContainsTest g containerSize containedSize 30 + [ -- Value size tests with varying sizes + [ generateContainsTest g containerSize containedSize | containerSize <- baseValueSizes , containedSize <- baseValueSizes , containedSize <= containerSize ] - , -- Key size impact tests - [ generateContainsTest g 100 10 keySize - | keySize <- baseKeySizes - ] , -- Budget-constrained tests - [ generateContainsBudgetTest g 30_000 keySize - | keySize <- [0, 30, 3_000, 20_000] - ] + [generateContainsBudgetTest g 30_000] , -- Edge cases - [ generateEmptyContainedTest g containerSize 30 + [ generateEmptyContainedTest g containerSize | containerSize <- [0, 10, 100, 1_000] ] , -- Random tests for parameter spread (100 combinations) @@ -190,13 +133,12 @@ valueContainsArgs gen = runStateGen_ gen \g -> do generateContainsTest :: (StatefulGen g m) => g - -> Int -- Container value size - -> Int -- Contained value size - -> Int -- Key byte size (for both policy and token) + -> Int -- Container value size (number of policies) + -> Int -- Contained value size (number of policies) -> m (Value, Value) -generateContainsTest g containerSize containedSize keySize = do +generateContainsTest g containerSize containedSize = do -- Generate container value - container <- generateConstrainedValue containerSize 10 keySize keySize g + container <- generateConstrainedValue containerSize 10 g -- Generate contained as subset of container (for true contains relationship) let containerList = Value.toList container @@ -215,10 +157,9 @@ generateContainsBudgetTest :: (StatefulGen g m) => g -> Int -- Total budget - -> Int -- Key size -> m (Value, Value) -generateContainsBudgetTest g budget keySize = do - container <- generateValueWithBudget keySize keySize budget g +generateContainsBudgetTest g budget = do + container <- generateValueWithBudget budget g -- Generate smaller contained value (subset) let containerList = Value.toList container containedEntries = take (length containerList `div` 2) containerList @@ -228,11 +169,10 @@ generateContainsBudgetTest g budget keySize = do generateEmptyContainedTest :: (StatefulGen g m) => g - -> Int -- Container size - -> Int -- Key size + -> Int -- Container size (number of policies) -> m (Value, Value) -generateEmptyContainedTest g containerSize keySize = do - container <- generateConstrainedValue containerSize 10 keySize keySize g +generateEmptyContainedTest g containerSize = do + container <- generateConstrainedValue containerSize 10 g pure (container, Value.empty) -- | Generate random valueContains test with varied parameters for better spread @@ -241,10 +181,9 @@ generateRandomContainsTest g = do -- Generate random parameters with good spread containerEntries <- uniformRM (1, 5_000) g -- 1-5000 container entries containedEntries <- uniformRM (1, containerEntries) g -- 1-container count - keyBytes <- uniformRM (1, 5_000) g -- 1-5000 byte keys - -- Generate container value with exact entry count - container <- generateRandomValueForContains containerEntries keyBytes g + -- Generate container value (1 token per policy for flat structure) + container <- generateConstrainedValue containerEntries 1 g -- Generate contained as subset of container entries let containerList = Value.toList container @@ -253,28 +192,6 @@ generateRandomContainsTest g = do pure (container, contained) --- | Generate Value for contains tests with exact entry count -generateRandomValueForContains - :: (StatefulGen g m) - => Int -- Entry count - -> Int -- Key byte size - -> g - -> m Value -generateRandomValueForContains entryCount keyBytes g = do - -- Generate policies and tokens with exact entry count - policyIds <- replicateM entryCount (uniformByteStringM keyBytes g) - tokenNames <- replicateM entryCount (uniformByteStringM keyBytes g) - - let - -- Create amounts (1 to 1000000) - amounts = [fromIntegral (1 + i `mod` 1_000_000) | i <- [0 .. entryCount - 1]] - - pure $ - Value.fromList - [ (policy, [(token, amount)]) - | (policy, token, amount) <- zip3 policyIds tokenNames amounts - ] - ---------------------------------------------------------------------------------------------------- -- ValueData --------------------------------------------------------------------------------------- @@ -296,57 +213,43 @@ generateTestValues :: StdGen -> [Value] generateTestValues gen = runStateGen_ gen \g -> do let baseValueSizes = [1, 10, 50, 100, 500, 1_000] - keySizes = [0, 30, 100, 1_000, 10_000] sequence $ concat - [ -- Empty value as edge case (first test cbase) + [ -- Empty value as edge case [pure Value.empty] - , -- Standard value sizes with varying key sizes - [ generateConstrainedValue valueSize 10 keySize keySize g - | valueSize <- baseValueSizes - , keySize <- [30, 1_000] - ] - , -- Key size impact tests (fixed value structure, varying key sizes) - [ generateConstrainedValue 100 10 keySize keySize g - | keySize <- keySizes + , -- Standard value sizes + [ generateConstrainedValue numPolicies 10 g + | numPolicies <- baseValueSizes ] , -- Budget-constrained tests - [ generateValueWithBudget keySize keySize budget g - | keySize <- [0, 30, 1_000, 10_000] - , budget <- [1_000, 10_000, 30_000] + [ generateValueWithBudget budget g + | budget <- [1_000, 10_000, 30_000] ] , -- Random tests for parameter spread (50 combinations) replicate 50 $ do numPolicies <- uniformRM (1, 1_000) g tokensPerPolicy <- uniformRM (1, 500) g - policyIdBytes <- uniformRM (0, 10_000) g - tokenNameBytes <- uniformRM (0, 10_000) g - generateConstrainedValue numPolicies tokensPerPolicy policyIdBytes tokenNameBytes g + generateConstrainedValue numPolicies tokensPerPolicy g ] --- | Generate constrained Value with total size budget +-- | Generate constrained Value generateConstrainedValue :: (StatefulGen g m) => Int -- Number of policies -> Int -- Number of tokens per policy - -> Int -- Policy ID byte length - -> Int -- Token name byte length -> g -> m Value -generateConstrainedValue numPolicies tokensPerPolicy policyIdBytes tokenNameBytes g = do - policyIds <- -- Generate policy IDs of specified size - replicateM numPolicies (generatePolicyId policyIdBytes g) - - tokenNames <- -- Generate token names of specified size - replicateM tokensPerPolicy (generateTokenName tokenNameBytes g) +generateConstrainedValue numPolicies tokensPerPolicy g = do + policyIds <- replicateM numPolicies (generateKey g) + tokenNames <- replicateM tokensPerPolicy (generateKey g) -- Generate positive quantities (1 to 1000000) let quantity :: Int -> Int -> Integer quantity policyIndex tokenIndex = fromIntegral (1 + (policyIndex * 1_000 + tokenIndex) `mod` 1_000_000) - nestedMap :: [(ByteString, [(ByteString, Integer)])] + nestedMap :: [(K, [(K, Integer)])] nestedMap = [ ( policyId , [ (tokenName, quantity policyIndex tokenIndex) @@ -360,40 +263,35 @@ generateConstrainedValue numPolicies tokensPerPolicy policyIdBytes tokenNameByte -- | Generate Value within total size budget generateValueWithBudget :: (StatefulGen g m) - => Int -- Policy ID byte length - -> Int -- Token name byte length - -> Int -- Target total size budget + => Int -- Target total size budget -> g -> m Value -generateValueWithBudget policyIdBytes tokenNameBytes budget g = do +generateValueWithBudget budget g = do let + keySize = Value.maxKeyLen overhead = 8 -- bytes per amount - -- Calculate maximum possible entries - bytesPerEntry = policyIdBytes + tokenNameBytes + overhead - maxEntries = - if bytesPerEntry > 0 - then min (budget `div` bytesPerEntry) budget - else budget -- Handle 0 case + -- Calculate maximum possible entries with fixed key sizes + bytesPerEntry = keySize + keySize + overhead -- policy + token + amount + maxEntries = budget `div` bytesPerEntry -- Simple distribution: try to balance policies and tokens numPolicies = max 1 (floor (sqrt (fromIntegral maxEntries :: Double))) tokensPerPolicy = if numPolicies > 0 then maxEntries `div` numPolicies else 0 - generateConstrainedValue numPolicies tokensPerPolicy policyIdBytes tokenNameBytes g + generateConstrainedValue numPolicies tokensPerPolicy g ---------------------------------------------------------------------------------------------------- -- Other Generators -------------------------------------------------------------------------------- --- | Generate policy ID of specified size -generatePolicyId :: (StatefulGen g m) => Int -> g -> m ByteString -generatePolicyId = generateByteString - --- | Generate token name of specified size -generateTokenName :: (StatefulGen g m) => Int -> g -> m ByteString -generateTokenName = generateByteString - --- | Generate ByteString of specified size -generateByteString :: (StatefulGen g m) => Int -> g -> m ByteString -generateByteString 0 _ = pure BS.empty -generateByteString l g = uniformByteStringM l g +-- | Generate random key (always maxKeyLen bytes for Cardano compliance) +generateKey :: (StatefulGen g m) => g -> m K +generateKey g = do + bs <- uniformByteStringM Value.maxKeyLen g + case Value.k bs of + Just key -> pure key + Nothing -> error "Internal error: maxKeyLen key should always be valid" + +-- | Generate random key as ByteString (for lookup arguments) +generateKeyBS :: (StatefulGen g m) => g -> m ByteString +generateKeyBS = uniformByteStringM Value.maxKeyLen From 609cfa39074b3a4bb6b718b4697eb8187eba8d18 Mon Sep 17 00:00:00 2001 From: Yura Lazaryev Date: Wed, 8 Oct 2025 12:13:48 +0200 Subject: [PATCH 08/17] refactor: simplify Value builtin cost models with improved documentation Simplify the R model definitions for Value-related builtins by replacing custom linear model implementation with standard linearInY wrapper for valueContains. This maintains the same statistical behavior while improving code maintainability. Add inline comments documenting the parameter wrapping strategy used for each model (Logarithmic wrapping for lookupCoin/valueContains, ValueTotalSize for contains operand, unwrapped for valueData/unValueData). Clean up formatting inconsistencies in model definitions. --- plutus-core/cost-model/data/models.R | 24 ++++++++++-------------- 1 file changed, 10 insertions(+), 14 deletions(-) diff --git a/plutus-core/cost-model/data/models.R b/plutus-core/cost-model/data/models.R index 802a2db11b1..1593d0d76b4 100644 --- a/plutus-core/cost-model/data/models.R +++ b/plutus-core/cost-model/data/models.R @@ -806,7 +806,7 @@ modelFun <- function(path) { mk.result(m, "exp_mod_cost") } - dropListModel <- linearInX ("DropList") + dropListModel <- linearInX ("DropList") ## Arrays lengthOfArrayModel <- constantModel ("LengthOfArray") @@ -814,21 +814,17 @@ modelFun <- function(path) { indexArrayModel <- constantModel ("IndexArray") ## Values - lookupCoinModel <- linearInZ ("LookupCoin") - ## ValueContains is O(n₂ × log max(m₁, k₁)) where n₂ is the total size of the second Value - ## We model this as linear in the sum of sizes, which is conservative - valueContainsModel <- { - fname <- "ValueContains" - filtered <- data %>% - filter.and.check.nonempty(fname) %>% - discard.upper.outliers() - m <- lm(t ~ I(x_mem + y_mem), filtered) - mk.result(m, "added_sizes") - } + # Z wrapped with `Logarithmic . ValueOuterOrMaxInner` + lookupCoinModel <- linearInZ ("LookupCoin") + + # X wrapped with `Logarithmic . ValueOuterOrMaxInner` + # Y wrapped with `ValueTotalSize` + valueContainsModel <- linearInY("ValueContains") - valueDataModel <- constantModel ("ValueData") - unValueDataModel <- linearInX ("UnValueData") + # Sizes of parameters are used as is (unwrapped): + valueDataModel <- constantModel ("ValueData") + unValueDataModel <- linearInX ("UnValueData") ##### Models to be returned to Haskell ##### From f9712363a95dbb23d4a440c1c38a60e0e8c17214 Mon Sep 17 00:00:00 2001 From: Yura Lazaryev Date: Thu, 9 Oct 2025 11:22:22 +0200 Subject: [PATCH 09/17] feat: update benchmark data for Value builtins Refreshed benchmarking data for lookupCoin, valueContains, valueData, and unValueData with improved statistical coverage and sampling. This data serves as the foundation for the refined cost model parameters applied in the subsequent commit. --- .../cost-model/data/benching-conway.csv | 795 ++++++++---------- 1 file changed, 350 insertions(+), 445 deletions(-) diff --git a/plutus-core/cost-model/data/benching-conway.csv b/plutus-core/cost-model/data/benching-conway.csv index 876f5af946f..82ec7c52650 100644 --- a/plutus-core/cost-model/data/benching-conway.csv +++ b/plutus-core/cost-model/data/benching-conway.csv @@ -12294,448 +12294,353 @@ Bls12_381_G2_multiScalarMul/97/97,6.90522012785712e-3,6.901544208299667e-3,6.918 Bls12_381_G2_multiScalarMul/98/98,6.9597205589059085e-3,6.9554579231546464e-3,6.963825444927238e-3,1.230537047747648e-5,9.828399035508776e-6,1.581113740579338e-5 Bls12_381_G2_multiScalarMul/99/99,6.998605748330429e-3,6.993956045528542e-3,7.003564931628933e-3,1.3941888558415054e-5,1.1848281516892752e-5,1.8598404587423643e-5 Bls12_381_G2_multiScalarMul/100/100,7.090569654857228e-3,7.08876305884669e-3,7.093035056145744e-3,6.187076669186285e-6,4.689206191622249e-6,8.297705725121281e-6 -LookupCoin/4/4/0,1.1987809246529645e-6,1.1980799694260653e-6,1.199507988172571e-6,2.4107745567835586e-9,2.0584370079307666e-9,2.875392436193467e-9 -LookupCoin/4/4/310,1.2142647691242684e-6,1.2131420571175932e-6,1.2155824079867558e-6,4.0706586084594835e-9,3.341022693427462e-9,5.065716418773158e-9 -LookupCoin/4/4/10010,1.2248007161821862e-6,1.2239051860618773e-6,1.2258178843052394e-6,3.4507929939399797e-9,2.7438893641041726e-9,4.037935320134895e-9 -LookupCoin/4/4/310,1.227249583287171e-6,1.2256517429394646e-6,1.228820138823975e-6,5.135902136033977e-9,4.602249434367064e-9,5.923087021439266e-9 -LookupCoin/4/4/10010,1.2443322171758413e-6,1.2427942185459095e-6,1.245357233115194e-6,4.477283860902663e-9,3.3486755939797695e-9,6.223685793289658e-9 -LookupCoin/4/4/1550,1.2454774811827858e-6,1.24344192850786e-6,1.2470198844553666e-6,6.122793215314405e-9,5.177658728098016e-9,7.799865926329944e-9 -LookupCoin/4/4/50050,1.2571864815375906e-6,1.2564138179154984e-6,1.2579616575806e-6,2.763962545250128e-9,2.377982103186773e-9,3.4290535732906835e-9 -LookupCoin/4/4/3100,1.2439256389929855e-6,1.2432284142565402e-6,1.2447917189730735e-6,2.6963459263387795e-9,2.3388804770411354e-9,3.1487019272388267e-9 -LookupCoin/4/4/100100,1.2614380048646346e-6,1.2607020697810519e-6,1.2622035022217295e-6,2.6041139838164562e-9,2.1634799046250406e-9,3.2905483922706815e-9 -LookupCoin/4/4/15500,1.2817013390502208e-6,1.2805655390473332e-6,1.2826202692983273e-6,3.4355071748599705e-9,2.7556274311754177e-9,4.333780868629672e-9 -LookupCoin/4/4/500500,1.2886652966188255e-6,1.287822313888798e-6,1.2893947030051335e-6,2.4996056527806103e-9,2.0027954951844944e-9,3.51778389213686e-9 -LookupCoin/4/4/31000,1.290122000714343e-6,1.288856340927497e-6,1.2912200541102332e-6,3.7314630573669714e-9,3.1415172863968466e-9,4.4094407974448845e-9 -LookupCoin/4/4/1001000,1.2850523205112054e-6,1.2841146835669193e-6,1.2862444714691543e-6,3.495083997499569e-9,2.7213906501859453e-9,5.135209308347153e-9 -LookupCoin/4/4/1,1.2257006912313622e-6,1.2252367955480791e-6,1.2261868546628844e-6,1.7280071454745501e-9,1.4188404395459067e-9,2.155107450125363e-9 -LookupCoin/4/4/3100,1.2647764517950342e-6,1.2641033185328018e-6,1.2654168552708808e-6,2.2224938263044665e-9,1.8474168055405267e-9,2.7240972942539672e-9 -LookupCoin/4/4/10100,1.2509813815980665e-6,1.2493589833326004e-6,1.2523719298666614e-6,4.852971270116405e-9,4.224063533334953e-9,5.761730062786258e-9 -LookupCoin/4/4/100100,1.272100065961152e-6,1.2713779399535466e-6,1.2729916263321848e-6,2.6442781870170232e-9,2.2315274992244496e-9,3.3894908114610666e-9 -LookupCoin/4/4/1000100,1.2622451455213246e-6,1.2614409542043105e-6,1.2628884167008598e-6,2.4284367212124195e-9,1.952886495004267e-9,3.058594015650686e-9 -LookupCoin/4/4/1,1.2120959773067779e-6,1.2111098168941214e-6,1.2130451144150161e-6,3.340332155521285e-9,2.854400739916875e-9,3.884696635679422e-9 -LookupCoin/4/4/1,1.2202197166189542e-6,1.2192613245401622e-6,1.2212645347977496e-6,3.2388832596863558e-9,2.7203964537861694e-9,3.900896078940326e-9 -LookupCoin/4/4/1,1.2235044799553622e-6,1.2228494680423523e-6,1.2243029181572994e-6,2.418188553655573e-9,1.9596997508446255e-9,3.3537589604273597e-9 -LookupCoin/4/4/124,1.2186676257033273e-6,1.2173292994061867e-6,1.2200318248936087e-6,4.796332197760777e-9,4.009498878734066e-9,6.027489021903283e-9 -LookupCoin/4/4/372,1.2346285723771364e-6,1.2336953254200625e-6,1.235714013792257e-6,3.425255360445383e-9,2.7589262620900956e-9,4.040351857619523e-9 -LookupCoin/4/4/651,1.2372953539593385e-6,1.2362630975860024e-6,1.2383763132577293e-6,3.523259668004743e-9,2.939076484410285e-9,4.317741226544648e-9 -LookupCoin/4/4/0,1.1938943959277518e-6,1.1931943214717257e-6,1.1945778725918846e-6,2.3739978189645768e-9,1.8545949559429995e-9,3.332219238927099e-9 -LookupCoin/4/4/2002,1.2197197605216406e-6,1.2187965672790472e-6,1.2206041280398874e-6,2.9336631903150676e-9,2.4616168455718915e-9,3.632414054858564e-9 -LookupCoin/4/4/4004,1.2251163407493166e-6,1.223376349490241e-6,1.2269137473156499e-6,6.08770401676884e-9,5.158185169323526e-9,7.03140495193674e-9 -LookupCoin/4/4/0,1.1868541548864574e-6,1.185793573842222e-6,1.187690566882342e-6,3.316928649716189e-9,2.732913986532151e-9,4.129135287141955e-9 -LookupCoin/4/4/0,1.1898164242411212e-6,1.1888025275796023e-6,1.1906360315586723e-6,3.105666969872855e-9,2.5406724407764428e-9,4.0336345504799915e-9 -LookupCoin/4/4/10001,1.2150661212171984e-6,1.2143604950573222e-6,1.215820874653369e-6,2.38481675610348e-9,1.9162066170306435e-9,3.0006760018374973e-9 -LookupCoin/4/4/5066270,1.277826580439173e-6,1.2767570441421777e-6,1.2789518483325532e-6,3.5436542776320486e-9,2.858524102842415e-9,4.587631601537296e-9 -LookupCoin/4/4/1292907,1.2677688678187691e-6,1.266718345792965e-6,1.2688009027816102e-6,3.447161199023977e-9,2.8551687550492393e-9,4.1145424069515494e-9 -LookupCoin/4/4/4030899,1.2814323262321796e-6,1.2806641039935756e-6,1.2821530318509303e-6,2.5390170765500563e-9,2.024519511273767e-9,3.2720719989230043e-9 -LookupCoin/4/4/5040432,1.2701222097077116e-6,1.2680642236901763e-6,1.272211683356216e-6,6.785163423685793e-9,5.5778440287708566e-9,8.32836503873299e-9 -LookupCoin/4/4/4561038,1.2744320740219546e-6,1.2732745959940393e-6,1.2753878614609515e-6,3.4966375499144543e-9,2.6380710490775692e-9,5.15651621189535e-9 -LookupCoin/4/4/5375788,1.29023827085883e-6,1.289131346302382e-6,1.2913186917094856e-6,3.6521304151635797e-9,3.077484480052455e-9,4.449439367331406e-9 -LookupCoin/4/4/1262300,1.2539033480175535e-6,1.2526689596121973e-6,1.2556306027786345e-6,4.813588884658454e-9,4.0753081448679886e-9,6.013391116763802e-9 -LookupCoin/4/4/779712,1.2752127020007219e-6,1.2733455510509096e-6,1.276421301457468e-6,4.960204372531049e-9,3.78185565884019e-9,7.938310069673206e-9 -LookupCoin/4/4/1148823,1.257069697085679e-6,1.2550281877305862e-6,1.258357677798816e-6,5.2692097950519294e-9,3.607430925786029e-9,7.84256990197175e-9 -LookupCoin/4/4/7565554,1.2718862218212706e-6,1.270595772895692e-6,1.273500171319768e-6,4.7205100970096915e-9,3.9399955033716265e-9,5.636316687102632e-9 -LookupCoin/4/4/1892372,1.2798022142401478e-6,1.2787601377188223e-6,1.2806492883730673e-6,3.240518096537139e-9,2.6845102219159927e-9,4.024692073232961e-9 -LookupCoin/4/4/3962952,1.2700930008680598e-6,1.269264255671348e-6,1.2709391336121646e-6,2.874679403151091e-9,2.3225902454617737e-9,3.70494574418947e-9 -LookupCoin/4/4/4322668,1.289884201590555e-6,1.2884415967028401e-6,1.2913737248356338e-6,4.801444154073013e-9,3.916001043141595e-9,5.9023486667443996e-9 -LookupCoin/4/4/2970000,1.2784087871552185e-6,1.2767249782735827e-6,1.279942350107124e-6,5.300756075447827e-9,4.125409905431318e-9,7.91576575586899e-9 -LookupCoin/4/4/1902626,1.2825938062683246e-6,1.2812887257240548e-6,1.2840488079301932e-6,4.539085547891917e-9,3.7003355816408288e-9,5.8304818844362325e-9 -LookupCoin/4/4/2058224,1.2674138822348226e-6,1.266517177438222e-6,1.268307129660272e-6,2.920592770603687e-9,2.475360696644196e-9,3.5087547273771266e-9 -LookupCoin/4/4/3287578,1.279789833294665e-6,1.2785676940878397e-6,1.2812666317707647e-6,4.396660300354464e-9,3.659512262281134e-9,5.305430420746576e-9 -LookupCoin/4/4/745890,1.2585346454916983e-6,1.2568337444249753e-6,1.2601251297939e-6,5.430356191272733e-9,4.633445845065433e-9,6.319836603491019e-9 -LookupCoin/4/4/4002026,1.2838087012363595e-6,1.2825086945447733e-6,1.2850242229140597e-6,4.306704983324547e-9,3.5205722930442468e-9,5.654297611220834e-9 -LookupCoin/4/4/1679601,1.26357751253574e-6,1.262826291623019e-6,1.2643169242412846e-6,2.4774181681520444e-9,2.060368542544128e-9,3.039629576081113e-9 -LookupCoin/4/4/6480027,1.2801980877278831e-6,1.2771485096511817e-6,1.2820170540550525e-6,7.943334159431303e-9,5.772244703375927e-9,1.1917062311991287e-8 -LookupCoin/4/4/4498896,1.231625663105949e-6,1.2297170084115537e-6,1.2332704356430894e-6,6.124111331433371e-9,5.385841935470476e-9,7.003288835706173e-9 -LookupCoin/4/4/1674756,1.2735333599690776e-6,1.2710191575535196e-6,1.2756334354586257e-6,7.879868389245381e-9,6.978600463987998e-9,9.154593296359008e-9 -LookupCoin/4/4/2876381,1.261443514778358e-6,1.260767224170065e-6,1.2622450911016386e-6,2.462597798861482e-9,1.9676438830362255e-9,3.096918170975184e-9 -LookupCoin/4/4/6444328,1.2817975648175746e-6,1.2807178055257148e-6,1.2828396916268854e-6,3.5823180401646896e-9,2.8738062669432795e-9,4.531443495722488e-9 -LookupCoin/4/4/375724,1.245765227573596e-6,1.2444678099280414e-6,1.2468631348220374e-6,3.914327458436205e-9,3.338118939061562e-9,4.747447778986924e-9 -LookupCoin/4/4/126540,1.2603295320670344e-6,1.2576543706100949e-6,1.2622416729797346e-6,7.814043532055153e-9,5.869724250780736e-9,1.201854001602634e-8 -LookupCoin/4/4/4706835,1.2659166931421738e-6,1.264223718258494e-6,1.2671110254567974e-6,4.65608823434229e-9,3.141554343089209e-9,6.784674488291999e-9 -LookupCoin/4/4/5364324,1.2701935393151057e-6,1.269043098380611e-6,1.2712397968982748e-6,3.781423003012787e-9,3.1820832804639213e-9,4.755630255677031e-9 -LookupCoin/4/4/1455168,1.2704388582488929e-6,1.269687317776098e-6,1.2711188680637336e-6,2.396816947915933e-9,1.9853818496761954e-9,2.993679944959491e-9 -LookupCoin/4/4/3889776,1.2802125381646228e-6,1.2791239574618982e-6,1.2813999258216065e-6,3.80345065781175e-9,3.149123607025695e-9,4.804823325650835e-9 -LookupCoin/4/4/686750,1.2599963410745547e-6,1.2588914981747105e-6,1.2611105471132294e-6,3.785014969177361e-9,3.147206549401517e-9,4.767167393088846e-9 -LookupCoin/4/4/1963648,1.299818184369183e-6,1.298617040985033e-6,1.301036825644262e-6,4.176587526215176e-9,3.4330381937143528e-9,5.270136974581143e-9 -LookupCoin/4/4/8659209,1.2924287795535367e-6,1.2912655254935138e-6,1.2935332916752233e-6,3.759717198495328e-9,2.8703928008557797e-9,5.27586315684352e-9 -LookupCoin/4/4/2789190,1.2755127933170805e-6,1.2737087407368222e-6,1.2768607596541763e-6,4.963059723596741e-9,3.5158859551543468e-9,6.981879743504883e-9 -LookupCoin/4/4/5625406,1.2959874699702527e-6,1.2950226907122984e-6,1.2970082683444309e-6,3.3391304669998987e-9,2.7941306761813028e-9,4.1386386528375054e-9 -LookupCoin/4/4/1957722,1.2690376232270707e-6,1.2666937311835606e-6,1.2709293087375226e-6,7.103182645095991e-9,4.915885369868955e-9,9.981731048934394e-9 -LookupCoin/4/4/4775708,1.2932987757200833e-6,1.2923933431135412e-6,1.2940935275990051e-6,2.785537307928441e-9,2.3087374360113047e-9,3.4830510090053497e-9 -LookupCoin/4/4/7862841,1.2779049515065047e-6,1.276878213735431e-6,1.279210034062878e-6,3.6895466028508537e-9,3.058034377334638e-9,5.074895055983018e-9 -LookupCoin/4/4/4343103,1.2947015952690554e-6,1.293526049558432e-6,1.2959020546237318e-6,3.840676655557911e-9,3.2213319774607096e-9,4.915737391178833e-9 -LookupCoin/4/4/2628828,1.2576228670548757e-6,1.255184660863472e-6,1.2591729099493177e-6,6.6657091577461195e-9,4.479936777639809e-9,1.0930469098408585e-8 -LookupCoin/4/4/6801147,1.273344935956418e-6,1.2717381856314266e-6,1.2747350340827408e-6,4.964830713393079e-9,4.139696967925825e-9,5.688607530322684e-9 -LookupCoin/4/4/2259715,1.2733626425487013e-6,1.2725687215373529e-6,1.2742045289295303e-6,2.753786442176939e-9,2.2271683907574778e-9,3.6442018276317194e-9 -LookupCoin/4/4/1311960,1.2643513046710382e-6,1.262048535540152e-6,1.2664285395243078e-6,7.211269768344391e-9,6.0887352623941e-9,9.266004580584638e-9 -LookupCoin/4/4/4656600,1.2784770014839777e-6,1.2763424508746477e-6,1.2808613423153377e-6,7.700463816731205e-9,6.8360128237785615e-9,8.690659514605894e-9 -LookupCoin/4/4/1093578,1.2716722138984615e-6,1.2700426000027498e-6,1.2729495582483995e-6,4.8324792890281395e-9,3.958125416800441e-9,6.067383126695396e-9 -LookupCoin/4/4/2868166,1.2775526844976142e-6,1.2753876524451476e-6,1.279449788038799e-6,7.1015328750516004e-9,5.800878613555848e-9,8.76070508863944e-9 -LookupCoin/4/4/2485840,1.2606233541272532e-6,1.2584118705398867e-6,1.2628177461824179e-6,7.2734790619610975e-9,6.412289956484719e-9,8.592412278530262e-9 -LookupCoin/4/4/453354,1.2491237152866404e-6,1.2474513872251372e-6,1.2509309497843268e-6,5.972396719405774e-9,4.80908506645763e-9,7.707294223227184e-9 -LookupCoin/4/4/2631636,1.275835347391731e-6,1.274031323751365e-6,1.2770603929417775e-6,4.848121178368409e-9,3.575817370976392e-9,6.803022453212725e-9 -LookupCoin/1/1/1,1.2062193447359163e-6,1.204720572905251e-6,1.2085664510346082e-6,6.3895396673973984e-9,3.5237401780642824e-9,9.865319076861485e-9 -LookupCoin/1/4/310,1.2477282934661902e-6,1.2457165309461458e-6,1.2500730188409636e-6,7.50234974399736e-9,6.484893665257567e-9,9.090423319721542e-9 -LookupCoin/1/125/10010,1.2364898735039994e-6,1.2339360373470795e-6,1.2388935255579768e-6,8.358163277644683e-9,6.037899233171248e-9,1.2510441623475233e-8 -LookupCoin/1/2500/200010,1.2374699372558117e-6,1.2359148176434845e-6,1.23888079346438e-6,5.061076021241142e-9,4.194002526091644e-9,6.3986008003463075e-9 -LookupCoin/1/1/170,1.2344447450763024e-6,1.2330377959532651e-6,1.2361615688816788e-6,5.196922828874984e-9,3.64700211256897e-9,8.416421668371051e-9 -LookupCoin/1/4/2635,1.2435117760278765e-6,1.2422284752759498e-6,1.2447536719288215e-6,4.408433001343926e-9,3.677681442162629e-9,5.438399421854307e-9 -LookupCoin/1/125/79079,1.2573268594938636e-6,1.2551516899720538e-6,1.2599712779688385e-6,7.80382576748386e-9,4.997720015443988e-9,1.3924166794552906e-8 -LookupCoin/1/2500/1660083,1.2484602746854446e-6,1.247815712373976e-6,1.2491265511584914e-6,2.34795048068606e-9,1.8921582415414914e-9,3.0112347635990135e-9 -LookupCoin/4/1/3100,1.2423704587658755e-6,1.2407630626791196e-6,1.2439468322394299e-6,5.373034335462937e-9,4.7566006320427445e-9,6.301317405621589e-9 -LookupCoin/4/4/3100,1.2525392523923255e-6,1.251729706388684e-6,1.253521581527334e-6,2.914692348843169e-9,2.5332203917450785e-9,3.6522269496455272e-9 -LookupCoin/4/125/100100,1.260774655999151e-6,1.258804266021221e-6,1.2665097440576978e-6,9.852196327494622e-9,4.304536400104611e-9,2.0258395020026988e-8 -LookupCoin/4/2500/2000100,1.2643632216987251e-6,1.2630032246538064e-6,1.2656822810057662e-6,4.334257923244687e-9,3.457742541748888e-9,5.22087199050318e-9 -LookupCoin/13/1/10100,1.2624070567558792e-6,1.2606154235219343e-6,1.2640424050493419e-6,5.657152523515489e-9,4.561599956711443e-9,7.417663438396113e-9 -LookupCoin/13/4/10100,1.2514256046427844e-6,1.2505411221705368e-6,1.25220945382555e-6,2.7559177095290204e-9,2.2419249567489397e-9,3.6490013282809864e-9 -LookupCoin/13/125/100100,1.2516682174012342e-6,1.2494080668363907e-6,1.25599113162234e-6,1.0356156217694294e-8,5.347239956327251e-9,1.845529845521035e-8 -LookupCoin/13/2500/2000100,1.2513709932311224e-6,1.2499746607215296e-6,1.2527092313776355e-6,4.4801455294860196e-9,3.800152944697293e-9,5.2497237732200065e-9 -LookupCoin/125/1/100100,1.2566103108676568e-6,1.255628700812506e-6,1.2575111947018028e-6,3.2302262628515648e-9,2.791524531422057e-9,3.8143780305339686e-9 -LookupCoin/125/4/100100,1.2514828459336215e-6,1.2477222292612055e-6,1.254612459913698e-6,1.1357087989549857e-8,9.45455176911453e-9,1.383532734188531e-8 -LookupCoin/125/125/100100,1.2510536713395532e-6,1.2486776378617943e-6,1.253130098221779e-6,7.604087462788487e-9,6.681597085163331e-9,9.422041323534413e-9 -LookupCoin/125/2500/2000100,1.257567022561272e-6,1.2568076079972548e-6,1.2586232567348466e-6,3.16296838231096e-9,2.6942744714791043e-9,4.065265294010724e-9 -LookupCoin/1250/1/1000100,1.2437022703562684e-6,1.2426624497194861e-6,1.2448352355537035e-6,3.6639170247051537e-9,3.0754055871693162e-9,4.6664050139976854e-9 -LookupCoin/1250/4/1000100,1.2552913141875582e-6,1.2538565802582663e-6,1.2564437487245099e-6,4.248705024921862e-9,3.469885621142994e-9,5.850796247354429e-9 -LookupCoin/1250/125/1000100,1.2527903228863225e-6,1.2518855914459804e-6,1.2537844352544552e-6,3.2593544529421823e-9,2.742839194604889e-9,3.855959694739642e-9 -LookupCoin/1250/2500/2000100,1.244355189731791e-6,1.2437611615642397e-6,1.2450840154318082e-6,2.114101048001732e-9,1.8593202860339957e-9,2.4700062670136815e-9 -LookupCoin/2500/1/2000100,1.2616953743537094e-6,1.2607823671479182e-6,1.2625869674557756e-6,2.995673224252523e-9,2.5848501095906772e-9,3.497831620701429e-9 -LookupCoin/2500/4/2000100,1.2324862369243195e-6,1.231432022400554e-6,1.2338560076276956e-6,4.090214148756135e-9,3.220166680385365e-9,5.312793659204946e-9 -LookupCoin/2500/125/2000100,1.2501426989566735e-6,1.2490513642391722e-6,1.2511800621045136e-6,3.5565143042767577e-9,2.9193085819710178e-9,4.317790069989673e-9 -LookupCoin/2500/2500/2000100,1.2684506473527835e-6,1.2663866623438072e-6,1.2700234602016789e-6,6.255223338613385e-9,5.122911802979287e-9,8.695620223015002e-9 -LookupCoin/2500/1/20001,1.2205950702764077e-6,1.2194837679049681e-6,1.2215739595305359e-6,3.5885412220455425e-9,3.041070733950513e-9,4.345775209121243e-9 -LookupCoin/1/2500/20001,1.225552033705855e-6,1.224475993667657e-6,1.2267310935149546e-6,3.870212721701195e-9,3.1775642399066607e-9,4.993592546496145e-9 -LookupCoin/1250/1250/10001,1.2131187397265325e-6,1.2115373232538786e-6,1.2147049505409275e-6,5.283426708698358e-9,4.755641727910896e-9,5.863281683071315e-9 -LookupCoin/1/1/98,1.2501521377877466e-6,1.2495341913932788e-6,1.2507217872067047e-6,1.9895907484626213e-9,1.4706491314737957e-9,3.3031274098784845e-9 -LookupCoin/1/1/1,1.2075501958236993e-6,1.2068021890272933e-6,1.208262129306143e-6,2.4058069615692213e-9,2.0194049677111022e-9,2.8733377667621385e-9 -LookupCoin/1895/2345/15963058,1.2803196379252948e-6,1.2781771197173325e-6,1.2824991274173064e-6,7.762986271918989e-9,6.828295807122626e-9,8.860257555658608e-9 -LookupCoin/370/2076/12038625,1.280187988079581e-6,1.2788960629861599e-6,1.2812234664338074e-6,3.6888829156735294e-9,3.005689382197591e-9,4.531610661491176e-9 -LookupCoin/2265/757/15420120,1.2794228186796374e-6,1.2775800846507617e-6,1.2806995495549277e-6,5.042315540484943e-9,3.2890802919642043e-9,7.1587364600981135e-9 -LookupCoin/709/489/10818411,1.2926044931678004e-6,1.2910920599573055e-6,1.2938738364742565e-6,4.59334649311881e-9,3.834567590327339e-9,5.643568309075777e-9 -LookupCoin/1974/1712/7151511,1.2618735333861445e-6,1.2602185905997524e-6,1.2632714749891885e-6,5.303975479948274e-9,4.335998165513941e-9,7.595794971707872e-9 -LookupCoin/2249/2078/18765656,1.2768198259782786e-6,1.2760612499536146e-6,1.2776866455140164e-6,2.782660538142238e-9,2.2964653023942013e-9,3.3936086904482942e-9 -LookupCoin/1902/2110/25016160,1.2800125082778773e-6,1.2782090687092827e-6,1.2813538547667959e-6,5.2249049550227564e-9,3.726430052955547e-9,8.966757032776342e-9 -LookupCoin/344/276/2585868,1.2748221163951422e-6,1.2736786979195662e-6,1.2758810964221625e-6,3.5967301348288155e-9,2.9547496393505218e-9,4.371301981521861e-9 -LookupCoin/1815/2039/32405983,1.2881442260618426e-6,1.2846214351971028e-6,1.290809590793673e-6,9.782581561579647e-9,7.975572864826726e-9,1.2664604408656405e-8 -LookupCoin/2407/1150/14459754,1.261742711763931e-6,1.260490055540015e-6,1.262856050041063e-6,3.916552884020715e-9,3.1311750666188257e-9,5.139741809384566e-9 -LookupCoin/51/53/403370,1.2690691201019735e-6,1.2666972707436046e-6,1.2719904736100445e-6,8.644027945417467e-9,6.895220410010281e-9,1.0643318074188051e-8 -LookupCoin/114/2185/15518688,1.2734454001566559e-6,1.2714482679541691e-6,1.2754859090015847e-6,7.129261241642667e-9,6.113117766803054e-9,8.385862555340417e-9 -LookupCoin/1930/184/11964450,1.2646806726004963e-6,1.2619186472531779e-6,1.266631620388074e-6,7.81500116526586e-9,5.318924791154326e-9,1.2112131735135537e-8 -LookupCoin/1661/1441/18361252,1.2793428921774997e-6,1.2773290456115479e-6,1.2816965978336147e-6,6.9161326406910465e-9,5.860419402064908e-9,8.104524793474994e-9 -LookupCoin/1079/1519/10120950,1.2176172342733113e-6,1.215354493542573e-6,1.219484840382208e-6,6.576382648263217e-9,4.955915665560883e-9,9.834786651184058e-9 -LookupCoin/1583/878/18323361,1.273901063799558e-6,1.2724958995911544e-6,1.2752668463417309e-6,4.382471116625853e-9,3.7191484251445385e-9,5.1011845508551176e-9 -LookupCoin/1750/2264/9958850,1.2792231288620218e-6,1.2773527430679643e-6,1.2809795453721968e-6,6.563524166291678e-9,5.620592207284027e-9,7.797812255973995e-9 -LookupCoin/2277/146/14590215,1.2736997031304613e-6,1.2729404628754282e-6,1.274678589065324e-6,2.803802651941421e-9,2.397116093816526e-9,3.337932466090993e-9 -LookupCoin/434/1476/9160680,1.2950377927217072e-6,1.292177950010784e-6,1.2971424929530197e-6,8.517874522069e-9,6.978396259287523e-9,1.0606971559804377e-8 -LookupCoin/1600/323/16538892,1.2748475569688066e-6,1.2739374353277782e-6,1.2757741071194235e-6,3.009126866839188e-9,2.5215172882163673e-9,3.6210540961781523e-9 -LookupCoin/1278/2268/25393200,1.2748429228153157e-6,1.2731909498703963e-6,1.2767655913677555e-6,5.8759116310050834e-9,5.136063002980486e-9,6.93144062101209e-9 -LookupCoin/2037/2155/12391965,1.286507969537781e-6,1.2851082842137748e-6,1.2879782385199171e-6,4.656354491627198e-9,3.924392590758368e-9,5.7189333877099e-9 -LookupCoin/698/2337/24505212,1.3004041448864844e-6,1.2990036884776086e-6,1.302198653199329e-6,5.342213005092348e-9,4.446898938496697e-9,6.400925016937013e-9 -LookupCoin/2083/2136/16163356,1.2764223683796965e-6,1.2747326749110076e-6,1.278022885417272e-6,5.193619740804341e-9,4.18253795872677e-9,6.50739439434995e-9 -LookupCoin/671/776/6029316,1.2915448262587781e-6,1.290620114288026e-6,1.292449612633099e-6,3.1655151644047537e-9,2.650509570099081e-9,4.201734900482966e-9 -LookupCoin/59/2345/34989265,1.288189387415324e-6,1.2857572996775002e-6,1.2894313736155252e-6,5.77855506267552e-9,3.286634406761636e-9,9.23067395758222e-9 -LookupCoin/900/2286/14536575,1.2448490575673767e-6,1.2436205509277125e-6,1.2461113424391198e-6,4.214766252418104e-9,3.5105664402150484e-9,5.402356168004765e-9 -LookupCoin/832/999/2603762,1.2469669931453683e-6,1.245833580412049e-6,1.2481197787736745e-6,3.835242006275528e-9,3.1092729510819287e-9,5.04970050588965e-9 -LookupCoin/1680/1508/22826065,1.2880012317351417e-6,1.2868962639461852e-6,1.289267171137826e-6,4.1157409135944946e-9,3.4279524178612484e-9,5.041552368721841e-9 -LookupCoin/1002/1135/6899280,1.2615340362439734e-6,1.2596000174105259e-6,1.2631098592873918e-6,5.794501833559887e-9,4.562340482651247e-9,7.436081363681221e-9 -LookupCoin/1359/1152/11261320,1.2817921429788798e-6,1.280692690514904e-6,1.282766878523355e-6,3.260336727262534e-9,2.686850069925233e-9,4.0389013073466375e-9 -LookupCoin/1479/1854/13803006,1.2740944860786948e-6,1.272017359375449e-6,1.275593228992704e-6,6.013280935327777e-9,4.97075917451662e-9,8.14866656090185e-9 -LookupCoin/1228/1674/4136274,1.2804318087322261e-6,1.2793348926092004e-6,1.281654185953536e-6,3.624950116338036e-9,2.9043725188905854e-9,4.939386088033429e-9 -LookupCoin/657/1400/17092726,1.281053127582082e-6,1.2791792176585762e-6,1.2829306152492005e-6,6.308782440142078e-9,5.0754542799941174e-9,7.739057463022068e-9 -LookupCoin/2273/210/18379980,1.280677680587168e-6,1.2788447475995189e-6,1.282026514602082e-6,5.306289383708538e-9,3.7157331580635896e-9,7.348475104890475e-9 -LookupCoin/2379/373/14176605,1.2663163225985433e-6,1.2639302078289512e-6,1.2683386698387479e-6,7.23990316849903e-9,6.1218650310142794e-9,8.597931932342572e-9 -LookupCoin/2027/609/23188880,1.295105567032933e-6,1.2940425166399068e-6,1.2961731866357902e-6,3.728919832353806e-9,3.274942293144146e-9,4.328517923189467e-9 -LookupCoin/1863/1686/28971432,1.2825169420362135e-6,1.2804928385281182e-6,1.2845252525717386e-6,7.275604141359334e-9,6.057458607922365e-9,8.691833143851719e-9 -LookupCoin/52/1791/22792666,1.281709793395133e-6,1.2801005292324194e-6,1.283403098669843e-6,5.266251041537131e-9,4.52760161581891e-9,6.151824896588823e-9 -LookupCoin/2352/1129/26569604,1.2778269348736196e-6,1.2757465332763327e-6,1.2796725671718388e-6,6.6653617265910815e-9,5.072710668827788e-9,1.0249419563026495e-8 -LookupCoin/1246/573/6110997,1.2793683625071125e-6,1.277896122360298e-6,1.2809199696787995e-6,4.968435244913596e-9,4.259098678716503e-9,5.959230769465271e-9 -LookupCoin/310/1554/15670447,1.2762542093004263e-6,1.274810442212931e-6,1.2776051488945713e-6,4.816180265316213e-9,4.167931733864282e-9,5.830428336731485e-9 -LookupCoin/1294/1547/16509584,1.2773846030504825e-6,1.2763117660169196e-6,1.2783798666693647e-6,3.465517844763897e-9,2.884712446351482e-9,4.119128215253205e-9 -LookupCoin/1129/448/6962901,1.2807023889182653e-6,1.279431567712355e-6,1.2822567656222109e-6,4.7306819714227345e-9,3.88206505602893e-9,5.757701461919527e-9 -LookupCoin/1589/1186/9012099,1.259328193086861e-6,1.2582289028982644e-6,1.2603655232997637e-6,3.731909085159e-9,3.1385094267051278e-9,4.5413734210007086e-9 -LookupCoin/1625/1893/22423821,1.268217566328228e-6,1.2661110426900448e-6,1.270600590015182e-6,7.536873955700692e-9,6.4829438363242555e-9,8.636468990921138e-9 -LookupCoin/9/1946/18177584,1.2958286550753203e-6,1.2942435964656242e-6,1.2972844012060394e-6,5.074835798824309e-9,3.862947517569473e-9,7.113544720904308e-9 -LookupCoin/2003/828/10528425,1.2660119891220907e-6,1.265114808268792e-6,1.2669678059247464e-6,3.0961043223970374e-9,2.602134311717419e-9,3.727819682601455e-9 -LookupCoin/876/2425/24813879,1.2695039120707998e-6,1.2683998534998996e-6,1.2710728327069194e-6,4.522253022851903e-9,3.241285459336524e-9,7.041325855313811e-9 -LookupCoin/1656/1408/10424602,1.2722888624293668e-6,1.2707823387853345e-6,1.273713506724683e-6,4.962874014529833e-9,4.1673847114882446e-9,5.865926525726256e-9 -ValueContains/310/31,1.150224079634047e-6,1.1484029171593576e-6,1.1520655872900477e-6,6.005570260918549e-9,4.862342923346793e-9,7.521077913330694e-9 -ValueContains/310/0,1.06384320106322e-6,1.062191515033955e-6,1.0654378642108599e-6,5.509382275152861e-9,4.581027672568637e-9,6.9098851874577475e-9 -ValueContains/310/310,1.7619305168090704e-6,1.7586779792752773e-6,1.7652600884404835e-6,1.130839096873276e-8,9.41898501836534e-9,1.4108118237577274e-8 -ValueContains/3100/0,1.0705970595310977e-6,1.0696262985135277e-6,1.0713713385821135e-6,2.872487380202136e-9,2.4019278496237887e-9,3.6053075163534896e-9 -ValueContains/3100/0,1.0657043929147226e-6,1.0642775083128504e-6,1.0671113447204667e-6,4.743608263663756e-9,3.889703167539578e-9,5.989574559564032e-9 -ValueContains/3100/3100,1.1894146744057842e-5,1.1871084222520173e-5,1.191767193116453e-5,7.663599053135675e-8,6.613215443182404e-8,9.643739250799068e-8 -ValueContains/31000/0,1.0677156355522858e-6,1.0654259909394951e-6,1.0698616098158728e-6,7.893785110339014e-9,6.182586930187335e-9,1.016832064207399e-8 -ValueContains/31000/0,1.0676225905277226e-6,1.0666709296050532e-6,1.0684853389377288e-6,2.8139786554644567e-9,2.2748535065168243e-9,3.7035014342306457e-9 -ValueContains/31000/0,1.0689765323263212e-6,1.0677305291841052e-6,1.0702146129018692e-6,4.153616760933364e-9,3.294918839189322e-9,5.552405671833423e-9 -ValueContains/31000/31000,1.3989070972469196e-4,1.3961275529108828e-4,1.4014140206640736e-4,8.671153993656169e-7,7.6414975418358e-7,9.882067921741445e-7 -ValueContains/1/1,1.1103542267638899e-6,1.1091545938139845e-6,1.1115909737856854e-6,4.205783682685009e-9,3.5546448746111783e-9,5.62531694174738e-9 -ValueContains/3100/0,1.0710438033081753e-6,1.0704010953841335e-6,1.0718462620934376e-6,2.488484444011733e-9,2.0557877847046803e-9,3.0489873474860437e-9 -ValueContains/100100/0,1.0645328169031105e-6,1.0622162475708715e-6,1.066656853367623e-6,7.602979479271493e-9,6.4343569983388315e-9,9.00929760184189e-9 -ValueContains/1000100/0,1.066009615081739e-6,1.0644317487918624e-6,1.0674781132396028e-6,5.059237602185728e-9,4.298984305788049e-9,5.899498444881504e-9 -ValueContains/1/0,1.0707510664994408e-6,1.0688014263040615e-6,1.0744053224110398e-6,8.653290657117377e-9,5.716417744402521e-9,1.4758666889717379e-8 -ValueContains/651/6510,1.8768293331625005e-5,1.8735623037201094e-5,1.8834433602150336e-5,1.479036964808042e-7,8.682086466352637e-8,2.6347552785518823e-7 -ValueContains/6002/6002,1.2977825325783861e-6,1.295350415288182e-6,1.3000088661210938e-6,7.269569584734367e-9,4.743744781624348e-9,1.0786484439189123e-8 -ValueContains/0/0,1.0658809918087003e-6,1.064642141097276e-6,1.0670292955565495e-6,4.374952858028444e-9,3.608067388398209e-9,5.251828914098139e-9 -ValueContains/0/0,1.0559905086366154e-6,1.0532986959513952e-6,1.05962723226345e-6,1.0680616302731096e-8,8.108403376724673e-9,1.6991111459695734e-8 -ValueContains/310/0,1.0716910600781161e-6,1.0706227908410502e-6,1.072598412217162e-6,3.2668191835731764e-9,2.88482953898635e-9,3.851011348259737e-9 -ValueContains/3100/0,1.065442367224129e-6,1.0639547859810193e-6,1.0687240823022984e-6,7.274364500262141e-9,3.739654571820177e-9,1.4891287855036637e-8 -ValueContains/31000/0,1.067519833120599e-6,1.0670093260065182e-6,1.068122613480877e-6,1.866640161684788e-9,1.4687606205704114e-9,2.368675885581133e-9 -ValueContains/1388240/1131480,5.830377894608075e-4,5.821675362234542e-4,5.841232073966954e-4,3.369025104679992e-6,2.834202732795799e-6,4.046879330172387e-6 -ValueContains/1230323/564167,6.957637639708246e-5,6.955956916495848e-5,6.959694875467544e-5,6.312446495406844e-8,4.809150972110265e-8,9.619774963274347e-8 -ValueContains/4035324/2503148,2.4917818695306486e-4,2.488740279681662e-4,2.504652388499471e-4,1.7966337495919435e-6,3.3382868647699937e-7,4.077061376227551e-6 -ValueContains/4797225/1867905,1.1298833376394714e-4,1.129045361082674e-4,1.1307031864043225e-4,2.854406184222403e-7,2.391807868462668e-7,3.5618050652586186e-7 -ValueContains/10835055/9374274,1.5335386801324598e-3,1.5318350982017343e-3,1.5379264227913564e-3,8.543138429232696e-6,3.908796093951306e-6,1.5229404241807767e-5 -ValueContains/12920960/975284,7.787465365647193e-5,7.78420278708246e-5,7.792727123487767e-5,1.3934696167567474e-7,1.0577024852677797e-7,2.0650866021535924e-7 -ValueContains/4708200/3670800,3.2189371844861713e-4,3.2150494682355317e-4,3.231951907590193e-4,2.1279453801609014e-6,6.057641810259562e-7,4.770434654200116e-6 -ValueContains/5032730/2914202,4.4632291921110087e-4,4.459043462632429e-4,4.475786076834567e-4,2.320167134598466e-6,8.420951551137534e-7,4.246168716058968e-6 -ValueContains/2774306/2038766,2.0218706694471707e-4,2.019965715302176e-4,2.028792056625027e-4,1.1025374870853495e-6,3.513069810941506e-7,2.4451455148839037e-6 -ValueContains/4020059/3892243,5.906132100414774e-4,5.903243585569346e-4,5.913624956317791e-4,1.470087000916268e-6,6.975667267168607e-7,2.65762554322302e-6 -ValueContains/4886109/3662556,3.2147460519542283e-4,3.213241376324112e-4,3.217071380767817e-4,5.938081388368038e-7,3.9546371750080744e-7,1.0364500615543388e-6 -ValueContains/5235852/1199292,1.372392804691373e-4,1.3720117227167361e-4,1.3729818364340758e-4,1.6202421861255058e-7,9.12126479788811e-8,2.5458418247796685e-7 -ValueContains/2945850/1345990,7.977577086502939e-5,7.975265920392309e-5,7.980776844774855e-5,9.408103233206765e-8,6.939296252705069e-8,1.4176818513985068e-7 -ValueContains/980343/549990,1.3848510081532306e-4,1.3836134411876637e-4,1.386279615391105e-4,4.397023092391429e-7,3.5175845858049713e-7,5.311761295383437e-7 -ValueContains/4713406/3666582,3.184150609185994e-4,3.1827502634776004e-4,3.1857087934551574e-4,4.960888019016048e-7,3.9488356265782485e-7,6.234062993995696e-7 -ValueContains/4392192/174838,1.9185488022869813e-5,1.917432377290978e-5,1.9196127357667117e-5,3.668720069998244e-8,3.146128801545269e-8,4.6060045380628914e-8 -ValueContains/5993043/1393056,1.3698697007419702e-4,1.3694169384738768e-4,1.3703898844114826e-4,1.6315053698114676e-7,1.2765054957267603e-7,2.4922858841547223e-7 -ValueContains/2841216/258944,4.4569751518569055e-5,4.455853857311547e-5,4.458634102791225e-5,4.4622445698346663e-8,3.3782123234928744e-8,6.043866835102693e-8 -ValueContains/16889220/6440265,9.630807665046082e-4,9.626643496364997e-4,9.638691403644825e-4,1.969808428789295e-6,1.4020089798171394e-6,3.2323864058579634e-6 -ValueContains/3416075/179400,2.1114615681243928e-5,2.110543246119949e-5,2.1123974058483687e-5,3.1805446389729774e-8,2.5908251759538914e-8,4.22730124319113e-8 -ValueContains/10474516/6931665,9.064818915605667e-4,9.05987443309439e-4,9.072612704764007e-4,2.036234445019851e-6,1.4482572524718826e-6,2.820824620618682e-6 -ValueContains/23280000/14317200,2.6943367275251776e-3,2.6935838951761227e-3,2.6954131081267352e-3,2.858873305393497e-6,1.8261059946685073e-6,4.911560735731439e-6 -ValueContains/17607912/400589,2.509700334064018e-5,2.5090201730613753e-5,2.5105845387826096e-5,2.4304443668200548e-8,1.9937384758448563e-8,3.1795332354781644e-8 -ValueContains/18476472/2509380,1.595515446835561e-4,1.5948902551541017e-4,1.5969817373887767e-4,3.14792644619481e-7,1.589795748224896e-7,5.329421866453197e-7 -ValueContains/2276082/130528,8.041209938911082e-6,8.036901279192637e-6,8.044849043957893e-6,1.2820036444411411e-8,1.0776473394324325e-8,1.5535420296847403e-8 -ValueContains/3930056/2725737,3.1776002333520296e-4,3.1739194817070323e-4,3.179661744289935e-4,9.513836575001647e-7,5.650491562578674e-7,1.5340286373147029e-6 -ValueContains/3598356/380092,3.4536686380287794e-5,3.4399022056096784e-5,3.469292924889314e-5,4.806422245761377e-7,4.1350889124018223e-7,5.141444004997678e-7 -ValueContains/12169248/10889424,1.9602809428612435e-3,1.959506477247854e-3,1.9612077354371504e-3,2.937546561276068e-6,2.317477571806379e-6,4.106702668950206e-6 -ValueContains/142848/72416,1.614800770779478e-5,1.612640184397839e-5,1.6165503144045665e-5,6.261322158873831e-8,5.358060856632499e-8,7.382795473265937e-8 -ValueContains/28446/20658,7.336275590839956e-5,7.317459349934284e-5,7.357110721408839e-5,6.919130313477668e-7,6.130125155079317e-7,8.055478060102782e-7 -ValueContains/4093319/1247625,1.9056177958026678e-4,1.9051540553801757e-4,1.9062486788885537e-4,1.814675437951522e-7,1.3510555555817223e-7,2.66118650443016e-7 -ValueContains/12390235/7859709,1.2939251469556306e-3,1.2933431902760165e-3,1.294682410466329e-3,2.193951997280829e-6,1.6794123785165327e-6,2.835225981249992e-6 -ValueContains/6129818/4066035,6.062322109240712e-4,6.056020612027894e-4,6.074113543857627e-4,2.7384695691856397e-6,1.625285264130118e-6,4.472293627737563e-6 -ValueContains/1657800/1530702,3.6554774539165115e-4,3.653782969910462e-4,3.658347842664113e-4,8.17317508543419e-7,4.893817089973439e-7,1.2591133108369015e-6 -ValueContains/3304800/910440,1.4289209811072542e-4,1.4272768310138654e-4,1.430164460749529e-4,4.743737818229538e-7,3.692018891019297e-7,6.635150006708321e-7 -ValueContains/15869112/9918608,1.966922026999833e-3,1.965532162311767e-3,1.9684557580459637e-3,4.886900380572334e-6,3.8114339023972606e-6,6.5043272023058915e-6 -ValueContains/1535940/1437408,1.675079192369487e-4,1.6743898345902722e-4,1.675974683410271e-4,2.621316159867751e-7,2.0779990830234897e-7,4.0570627069547474e-7 -ValueContains/19866756/18316004,3.433782972066689e-3,3.431825291604356e-3,3.4371936732783457e-3,7.942605267700316e-6,4.4658213648082326e-6,1.543699282200521e-5 -ValueContains/2767554/101535,7.370376782582864e-6,7.367301893150696e-6,7.373809574781905e-6,1.1399966273118639e-8,9.46164017266115e-9,1.528392137629673e-8 -ValueContains/6418466/4957062,7.712746413388413e-4,7.705837930356645e-4,7.72257699804622e-4,2.691519911527554e-6,1.908409434797522e-6,3.620458138777805e-6 -ValueContains/3595660/2643280,5.897573926490326e-4,5.894703531110593e-4,5.901217699060191e-4,1.063906555408471e-6,8.012659689797687e-7,1.400088770302344e-6 -ValueContains/19078421/11705351,2.1984832793282365e-3,2.1976878588428382e-3,2.1994700112280448e-3,2.9207560746456993e-6,2.25976489043177e-6,4.385016227957237e-6 -ValueContains/2078188/690368,1.6287475493861336e-4,1.6277688884120615e-4,1.62957700148916e-4,3.0162048245436194e-7,2.560271912897383e-7,3.572126881676112e-7 -ValueContains/9108300/2616575,2.5582738803681283e-4,2.556821249609247e-4,2.560011799020167e-4,5.270886608887014e-7,4.213315620704924e-7,6.986846618352393e-7 -ValueContains/6916158/368406,3.802286624021897e-5,3.80151539227574e-5,3.8030383790436226e-5,2.629032044731183e-8,2.201626061128466e-8,3.195811927303817e-8 -ValueContains/8999515/5208710,8.056136157809999e-4,8.051642952842769e-4,8.065927838704155e-4,1.9952438976326107e-6,1.3453298416225953e-6,3.350980804138213e-6 -ValueContains/3590204/1011148,1.0520207337524529e-4,1.0517766716611235e-4,1.0523286251531954e-4,9.108695273412249e-8,6.679970571243264e-8,1.437262741780023e-7 -ValueContains/8618405/1525841,1.3447990003810246e-4,1.34435364937348e-4,1.345662890706284e-4,1.9738886556091444e-7,1.247201488379852e-7,3.4329718865165016e-7 -ValueContains/1090566/676218,3.652853539745162e-4,3.6521368175826543e-4,3.65390955680254e-4,3.044283349559993e-7,2.0695871997905786e-7,4.2463426025938833e-7 -ValueContains/17998150/4896483,5.460585925365607e-4,5.455005274479362e-4,5.46969339199242e-4,2.3611739251008407e-6,1.6155650868680277e-6,3.914730201986467e-6 -ValueContains/4799844/2492436,1.716249294942824e-4,1.7156983053522086e-4,1.7170664969734048e-4,2.3100847784072545e-7,1.6075694098077668e-7,3.441386203411614e-7 -ValueContains/1984837/245685,2.8775986614012295e-5,2.8704105825927887e-5,2.888419479974047e-5,2.891212852817797e-7,2.0878208775377933e-7,3.570018596709635e-7 -ValueContains/2142174/75164,1.3258165336340797e-5,1.3247097446542808e-5,1.3274550072140676e-5,4.469849048208671e-8,2.98946888580418e-8,6.098090781938885e-8 -ValueContains/14913261/8624418,1.5338686319268332e-3,1.5331670660293957e-3,1.5357364274093583e-3,3.656842792549137e-6,1.7468799923239558e-6,6.908436014702568e-6 -ValueContains/1707401/1316703,1.0862070605606819e-4,1.0860062436163804e-4,1.0866147173040616e-4,9.194726055446758e-8,5.269977898019595e-8,1.6790017195090266e-7 -ValueContains/4980024/1591128,1.3112143079769268e-4,1.3106926433345794e-4,1.3118613286673027e-4,1.9444865449562152e-7,1.4586150234421572e-7,2.6503330569164106e-7 -ValueContains/12956460/10548000,1.957508654239913e-3,1.95677647570763e-3,1.9583060351476274e-3,2.562461652561229e-6,1.9438229299769547e-6,3.602066047576493e-6 -ValueContains/8217775/5729209,1.0698956920126381e-3,1.0687585732563776e-3,1.0715867872757533e-3,4.868050250114949e-6,3.4296121068493134e-6,7.228146110756961e-6 -ValueContains/7272552/1557528,2.022156255589961e-4,2.0213498541107506e-4,2.022869607648368e-4,2.53115688383433e-7,1.9725970108425334e-7,3.691933219173594e-7 -ValueContains/10713400/2240361,1.812366193284897e-4,1.8116235779877508e-4,1.813766927053128e-4,3.332839427048048e-7,1.612596811539039e-7,5.703943676029055e-7 -ValueContains/963590/240480,2.4903560578250308e-5,2.489362059974177e-5,2.4915891216710552e-5,3.661956008621002e-8,2.9660121160896844e-8,4.8637963844660726e-8 -ValueContains/2394639/1603701,2.859391048819322e-4,2.8576317224094007e-4,2.862141624524469e-4,7.468778052987474e-7,4.7542197032452347e-7,1.287212303358601e-6 -ValueContains/11033220/7677912,1.631541304212993e-3,1.6308410706675916e-3,1.6326555517465176e-3,2.914717684729703e-6,1.874019892893764e-6,4.933954966466973e-6 -ValueContains/491009/179958,6.889524112989753e-5,6.882464026662156e-5,6.897513676503781e-5,2.4796183246476124e-7,2.2431121147365143e-7,2.700409630551564e-7 -ValueContains/11084414/8896750,1.4232107805540568e-3,1.4225235585870345e-3,1.4243043895285736e-3,2.765726490585935e-6,1.711780295744547e-6,4.266028265120588e-6 -ValueContains/271467/172980,2.3894128756798898e-4,2.3877636199911618e-4,2.3910103920611503e-4,5.639201789091078e-7,4.84146265106951e-7,6.505974886269501e-7 -ValueContains/40089/14857,2.0954979970178162e-5,2.0917315871604934e-5,2.1000604057377935e-5,1.3379340441460844e-7,1.1198361996558905e-7,1.5957093576177045e-7 -ValueContains/1200337/1125892,2.339006505113107e-4,2.3366650649583206e-4,2.3418223480905142e-4,8.337769259963321e-7,6.576979972783795e-7,1.2112979799509469e-6 -ValueContains/1838826/428238,9.653993911295394e-5,9.648059017078725e-5,9.661753189516794e-5,2.2395968970038456e-7,1.5411237607620095e-7,3.3927380681589213e-7 -ValueContains/13389200/4701435,5.285062717968509e-4,5.279808745318598e-4,5.294051455991618e-4,2.3074935466244204e-6,1.5036910408140082e-6,3.6691863871758815e-6 -ValueContains/1360924/490784,6.47162531082863e-5,6.470281894065016e-5,6.473263563193671e-5,4.84700294875406e-8,3.856698702898866e-8,6.351389790864793e-8 -ValueContains/7060235/1710410,1.1332567192810901e-4,1.1326013541582326e-4,1.1345067846458714e-4,2.9390185807507663e-7,1.859520264861708e-7,4.5224611836576073e-7 -ValueContains/7168728/2925342,2.3019958166231518e-4,2.3005209069534727e-4,2.3028836665561712e-4,3.925922320298606e-7,2.704538532702406e-7,6.412876014677384e-7 -ValueContains/3062696/1755572,1.4265677665455828e-4,1.425505538475746e-4,1.4304286573034607e-4,6.32558480895347e-7,2.3363813145649228e-7,1.2681246047672563e-6 -ValueContains/11969680/6332685,9.617240714933561e-4,9.611633517332247e-4,9.623093765333572e-4,2.0511425912438474e-6,1.6481397327727508e-6,2.8499370524871487e-6 -ValueContains/12699336/2423394,2.031868348925432e-4,2.0306625300929392e-4,2.034224470500471e-4,5.943785919606138e-7,3.7321236608462653e-7,9.84547111295116e-7 -ValueContains/12861500/8116375,1.3066861599144667e-3,1.3056968758639396e-3,1.307842903177105e-3,3.6527969418481483e-6,2.8884249963033977e-6,4.5825585672189005e-6 -ValueContains/20953377/15412274,2.90334709367055e-3,2.9006281181731207e-3,2.909060092516673e-3,1.2912355593307847e-5,6.47157975795324e-6,2.2357280960906057e-5 -ValueContains/7975503/3657069,5.031441153067773e-4,5.009936984129138e-4,5.04852475034121e-4,6.607943723273288e-6,5.57902102994008e-6,7.3936978355426465e-6 -ValueContains/8992218/912254,6.007525093072982e-5,6.004279292609082e-5,6.013039079988352e-5,1.3889958907855164e-7,8.54974566307128e-8,2.1970939936341664e-7 -ValueContains/116157/96173,9.175802716744137e-6,9.166092411893076e-6,9.188875187795383e-6,3.897604192065501e-8,2.952711146139307e-8,5.281903213223849e-8 -ValueContains/5366844/1303239,7.892804244199633e-5,7.888257342229591e-5,7.898322612015493e-5,1.7485088997300327e-7,1.4493882112906774e-7,2.2651537843986237e-7 -ValueContains/14277360/5654400,7.593722407604015e-4,7.58819151047441e-4,7.603205576715492e-4,2.3443319112155012e-6,1.654684408460267e-6,3.634371237506103e-6 -ValueContains/2778300/1994220,3.865455187892309e-4,3.862213776945122e-4,3.8734584942507036e-4,1.631389705385232e-6,7.419321061731839e-7,3.1389138468626554e-6 -ValueContains/2625714/1714804,2.2752714411573664e-4,2.2748011187241212e-4,2.2759856575259196e-4,1.964998717496885e-7,1.219909353824142e-7,3.747787287802566e-7 -ValueContains/3694722/1318710,1.1303820545854332e-4,1.1294941990435116e-4,1.132438432832616e-4,4.206203474210641e-7,2.2367360602305687e-7,7.565624356871839e-7 -ValueContains/6103626/4472940,6.649648364049148e-4,6.642859692890245e-4,6.662788577883692e-4,3.1023889137297782e-6,1.8653117644462426e-6,5.4753211265038996e-6 -ValueContains/10497826/9042142,2.039619603141005e-3,2.0382483819400316e-3,2.042269702048698e-3,6.047705510960005e-6,3.755850538337618e-6,1.0035148338055982e-5 -ValueContains/1960059/1455077,1.1222745901610427e-4,1.1219456665476382e-4,1.1225918423301758e-4,1.0674095875053205e-7,9.045417886847991e-8,1.2991122074798892e-7 -ValueContains/2096406/150858,2.663133880325886e-5,2.6620253179459178e-5,2.6650375062978732e-5,4.743218932646712e-8,3.308943823306096e-8,6.909814199182092e-8 -ValueContains/12989004/5392182,6.886762998329002e-4,6.879156013965011e-4,6.897338691186196e-4,2.8565415615684417e-6,2.0936482685871293e-6,3.824954796850235e-6 -ValueContains/642390/173964,3.071113180708838e-5,3.067057367187396e-5,3.080765445618444e-5,2.006366456375042e-7,8.853559204569966e-8,3.8568429886307546e-7 -ValueContains/115482/27512,9.064147361675596e-5,9.051128570298819e-5,9.076600350655485e-5,4.360960850239288e-7,3.6452723098708387e-7,5.263913215392148e-7 -ValueContains/1328176/1141482,5.035514198409748e-4,5.032739606692311e-4,5.043542802297387e-4,1.4546264394098652e-6,6.335811471276296e-7,2.9006992241714765e-6 -ValueContains/7806181/100413,6.5512674297340936e-6,6.545302453209767e-6,6.563307233192391e-6,2.6380763024944244e-8,1.0592452441477217e-8,4.314270025865915e-8 -ValueContains/4788828/917676,1.503257594000041e-4,1.501594977377007e-4,1.5093315389857768e-4,9.360293386563395e-7,2.1254033773254456e-7,1.9290513829692186e-6 -ValueContains/5688024/263720,3.428285525167467e-5,3.427291719885072e-5,3.4297396798349265e-5,4.0382747853099325e-8,2.828644276513103e-8,6.248144683887384e-8 -ValueContains/6878420/3657938,6.592213508033889e-4,6.579409944279702e-4,6.61782605276198e-4,5.969530361920488e-6,3.3639617412526817e-6,1.056368392720555e-5 -ValueContains/19772224/4693360,5.019688315456157e-4,5.015567800541507e-4,5.026393294589733e-4,1.7682410268291807e-6,1.2422627569658219e-6,2.9274257767392108e-6 -ValueContains/6070955/3682305,4.5444711174498444e-4,4.539127267159825e-4,4.5536546997632376e-4,2.507300024949188e-6,1.454923133744795e-6,4.735308195468392e-6 -ValueData/0,8.583750684602916e-7,8.574665326043169e-7,8.593672673392311e-7,3.019532432241858e-9,2.525918801783744e-9,3.859878670706656e-9 -ValueData/310,8.622479689638347e-7,8.605672500396664e-7,8.648103017078753e-7,7.2690624608328786e-9,4.4613311775058174e-9,1.1985519761994768e-8 -ValueData/10010,8.679760570564036e-7,8.668919948859114e-7,8.688166572496762e-7,3.1436494074630504e-9,2.566988136838245e-9,3.859414335066352e-9 -ValueData/3100,8.651895304168579e-7,8.635567660820601e-7,8.68377293177932e-7,7.274978664063257e-9,4.00234479276707e-9,1.4126856409467756e-8 -ValueData/100100,8.669687589120348e-7,8.662696968005817e-7,8.677207774562702e-7,2.4328432559031664e-9,1.9818699647829177e-9,3.0084405929015068e-9 -ValueData/15500,8.620033290605479e-7,8.601017323033926e-7,8.64180231502215e-7,6.763766111300699e-9,5.473388596201153e-9,9.635853378707712e-9 -ValueData/500500,8.635517053593947e-7,8.625977813772622e-7,8.649292359253146e-7,3.872697426125699e-9,2.792966849032069e-9,7.201534792722501e-9 -ValueData/31000,8.651401887855943e-7,8.639573884016736e-7,8.671683404631164e-7,5.280922858119043e-9,3.203545718908386e-9,8.838853650342515e-9 -ValueData/1001000,8.686553559118597e-7,8.675512954191544e-7,8.698302057020482e-7,3.840040039265437e-9,3.3491324591863146e-9,4.606771014371211e-9 -ValueData/155000,8.633407657769235e-7,8.618473001994409e-7,8.659534728681274e-7,6.611926139611169e-9,3.965784474535508e-9,1.1796783950969659e-8 -ValueData/5005000,8.631610151530661e-7,8.62274699473225e-7,8.640843164043536e-7,3.1099003950571255e-9,2.4495893986312256e-9,4.123981446351906e-9 -ValueData/310000,8.624200507884241e-7,8.609144115467483e-7,8.640998456654391e-7,5.902359879858976e-9,4.798806862784285e-9,7.449559516496736e-9 -ValueData/10010000,8.617479489888499e-7,8.606856134681744e-7,8.632181644655082e-7,4.030719816077838e-9,3.1770701284302586e-9,5.258502071830932e-9 -ValueData/1,8.647281489320198e-7,8.630751278496909e-7,8.67717131597178e-7,7.475927221927825e-9,5.077563259036573e-9,1.2136672154558073e-8 -ValueData/31000,8.629482948630209e-7,8.618572645147149e-7,8.641970717600778e-7,4.036352013481435e-9,3.352360167330728e-9,5.030758305594242e-9 -ValueData/101000,8.642502711189975e-7,8.627574939708884e-7,8.677897321999737e-7,7.445541564282644e-9,4.285778092966304e-9,1.3798148237347443e-8 -ValueData/1001000,8.605807510105824e-7,8.595344575208356e-7,8.615716881169933e-7,3.4595517684568643e-9,2.8025622473994713e-9,4.617901156410846e-9 -ValueData/10001000,8.674760232551506e-7,8.65435156888973e-7,8.697780749953191e-7,7.293398231168419e-9,5.639873294500882e-9,1.0632486186487765e-8 -ValueData/1,8.628976109415359e-7,8.620633617102623e-7,8.636945055998371e-7,2.6436319220489336e-9,2.1577225430059305e-9,3.506243700016569e-9 -ValueData/1,8.658590429703182e-7,8.644805715449798e-7,8.671149054232529e-7,4.591967319687212e-9,3.392322890780751e-9,6.35394360044245e-9 -ValueData/1,8.62546537252087e-7,8.618076159297699e-7,8.632137753826199e-7,2.5034929311122895e-9,2.102436684275761e-9,3.216445598585178e-9 -ValueData/372,8.683318818570483e-7,8.667003545889679e-7,8.70711336141621e-7,6.324326624146734e-9,4.6436052173446084e-9,1.0302026162313797e-8 -ValueData/4464,8.649420667261587e-7,8.635976923126619e-7,8.663944821563864e-7,4.600199974975949e-9,3.6276915069870168e-9,6.342595914111486e-9 -ValueData/13671,8.621836066399538e-7,8.607545537631805e-7,8.639339465634156e-7,5.2894406678342995e-9,4.168378763242659e-9,7.552867529600776e-9 -ValueData/0,8.638839976642206e-7,8.622204912920894e-7,8.651359212702882e-7,4.6891676548751464e-9,3.7126557081964195e-9,6.833536396058405e-9 -ValueData/4004,8.687755701430774e-7,8.672040203903232e-7,8.698451743757732e-7,4.2749448478967725e-9,3.2764390996553346e-9,6.0852194132612024e-9 -ValueData/12012,8.626351380748289e-7,8.619028110455171e-7,8.6342430858083e-7,2.5748797720203776e-9,2.2648193161178535e-9,2.980620786944366e-9 -ValueData/0,8.633110769610172e-7,8.617934220363606e-7,8.659554148224579e-7,6.4618838033455365e-9,3.779736756099013e-9,1.1565819589841476e-8 -ValueData/0,8.717315273377249e-7,8.708462397323893e-7,8.727126362599277e-7,3.181469333554735e-9,2.6674612273499665e-9,4.021223672036579e-9 -ValueData/10001,8.682085604933698e-7,8.666907150939007e-7,8.697904543716352e-7,5.243826692680096e-9,4.350649370956428e-9,6.732689911204806e-9 -ValueData/2046773080,8.799061388020214e-7,8.792008028668604e-7,8.805626279053824e-7,2.2448106084562397e-9,1.9192179398398734e-9,2.7574601080049884e-9 -ValueData/212036748,8.817248518792184e-7,8.795805571093361e-7,8.841449629848211e-7,7.636509263682473e-9,6.304100924668804e-9,9.926381322050969e-9 -ValueData/842457891,8.846468399992824e-7,8.838726386882992e-7,8.854096299615428e-7,2.7405636928139936e-9,2.1634872449587907e-9,3.6214082931513867e-9 -ValueData/1265148432,8.775353471252502e-7,8.760186615094953e-7,8.787750555869387e-7,4.6510511746278936e-9,3.845323090587232e-9,6.428244290483821e-9 -ValueData/2079833328,8.871245102652917e-7,8.860994536790355e-7,8.880843358761959e-7,3.3896386011608883e-9,2.8845323562804078e-9,4.09624979941731e-9 -ValueData/333298856,8.763892754185485e-7,8.739233907783042e-7,8.783794665611568e-7,7.499928087631522e-9,5.57455881688526e-9,1.029714184751263e-8 -ValueData/194394200,8.758213993809808e-7,8.746616705724959e-7,8.770892192315209e-7,4.013306501018826e-9,3.4471099412729444e-9,4.760978234465088e-9 -ValueData/15594240,8.811059911832802e-7,8.797285463074717e-7,8.821858388885495e-7,4.231510270129174e-9,3.3224181335611978e-9,5.2776184173331745e-9 -ValueData/60887619,8.789218890659444e-7,8.778770750557923e-7,8.798066083748263e-7,3.3974148594250846e-9,2.9602513800304063e-9,3.91669753021462e-9 -ValueData/2368018402,8.766056945044401e-7,8.758465798328167e-7,8.77412439428283e-7,2.72174093839264e-9,2.2897807958991373e-9,3.3094397737258205e-9 -ValueData/478770116,8.824026191875146e-7,8.808969302178395e-7,8.835399806964488e-7,4.508845007523353e-9,3.335594839761039e-9,6.254914196480365e-9 -ValueData/1264181688,8.787092821676913e-7,8.775732104368867e-7,8.796549448400194e-7,3.309352242996296e-9,2.700318858307644e-9,3.996434015821737e-9 -ValueData/1486997792,8.855538404912347e-7,8.847650817010667e-7,8.862626916551618e-7,2.4243766982415683e-9,2.0534210316307303e-9,3.1014469095585945e-9 -ValueData/754380000,8.829660520397515e-7,8.813596863617722e-7,8.84493256111861e-7,5.6759422408998424e-9,4.775962911936064e-9,7.173472522901001e-9 -ValueData/542248410,8.848080315721519e-7,8.837155509922712e-7,8.858404379782492e-7,3.4113979775436517e-9,2.7709230329262894e-9,4.743294292970642e-9 -ValueData/240812208,8.82248245860847e-7,8.812235930097226e-7,8.831529718131394e-7,3.180157673301647e-9,2.804635756518382e-9,3.6562581384899457e-9 -ValueData/1430096430,8.831487351515866e-7,8.820109304068219e-7,8.843526457363097e-7,3.6796192478390113e-9,3.1453052830625004e-9,4.7694007939063e-9 -ValueData/40278060,8.887025823082332e-7,8.872861240982155e-7,8.899998293333394e-7,4.853953192000954e-9,4.0609242299469125e-9,5.965475937336031e-9 -ValueData/276139794,8.825935312234712e-7,8.815053325968616e-7,8.836463647300298e-7,3.740457881690753e-9,3.1694277739274094e-9,4.5045410443279354e-9 -ValueData/312405786,8.824801235655492e-7,8.810210499022529e-7,8.841640612966216e-7,5.247345792945051e-9,4.436751497574306e-9,6.263104631517754e-9 -ValueData/1289525373,8.789978180702858e-7,8.778567142989118e-7,8.801401207130893e-7,4.043223492385461e-9,3.3763030958322775e-9,4.983444956059326e-9 -ValueData/31492272,8.778572169491559e-7,8.761117425713348e-7,8.793492858631854e-7,5.272561585385543e-9,4.014663708583722e-9,7.276583163572152e-9 -ValueData/107184384,8.818378465988198e-7,8.809639623213274e-7,8.826669948563791e-7,3.004108398303013e-9,2.307779411352837e-9,3.852753761540837e-9 -ValueData/583905343,8.83828961604512e-7,8.818390644300958e-7,8.858609853324564e-7,6.581776541916642e-9,5.525618961692241e-9,7.97206751105742e-9 -ValueData/683098768,8.842559877704424e-7,8.826761640209831e-7,8.85398361920786e-7,4.671661852922675e-9,3.2234518102792736e-9,6.73891428029885e-9 -ValueData/18410476,8.807037356543371e-7,8.793896060399384e-7,8.822257921510808e-7,4.8501666794017144e-9,4.2471701844937496e-9,5.670458663849601e-9 -ValueData/23916060,8.784479084982687e-7,8.766470055807582e-7,8.796172901151588e-7,4.965995853960267e-9,3.6568614959707447e-9,6.8046482484269464e-9 -ValueData/1670926425,8.802093694529347e-7,8.784855781664408e-7,8.819685642539668e-7,5.523024556050195e-9,4.780765359440556e-9,6.473837976773515e-9 -ValueData/2204737164,8.751495378477806e-7,8.730528129770386e-7,8.767493601276111e-7,6.114803054956147e-9,4.713082615951264e-9,8.098771046739599e-9 -ValueData/331778304,8.848479366350919e-7,8.830743194512606e-7,8.869154398087849e-7,6.459236715926961e-9,5.694915311090601e-9,7.561013169713219e-9 -ValueData/11669328,8.841498121049638e-7,8.820410227786969e-7,8.857082001678627e-7,6.315449976254246e-9,4.589904519494843e-9,9.761196251911394e-9 -ValueData/69361750,8.845614323955318e-7,8.838609791243484e-7,8.851799955248878e-7,2.1639440482291287e-9,1.7518769438720122e-9,2.91661512776194e-9 -ValueData/66764032,8.804368945296171e-7,8.79024386297518e-7,8.819560810956152e-7,4.818506753070799e-9,4.078572328116291e-9,6.212185532793539e-9 -ValueData/2138824623,8.80788899955889e-7,8.794034491353684e-7,8.816824626465143e-7,3.5978812373689384e-9,2.7164081389282516e-9,5.145775669625586e-9 -ValueData/16735140,8.797893430418764e-7,8.779381583077851e-7,8.813413792971062e-7,5.570848939066517e-9,4.33314545524839e-9,7.191812944622222e-9 -ValueData/1912638040,8.81436773516627e-7,8.791460884856874e-7,8.838183849482439e-7,8.086677428227584e-9,6.863754700072674e-9,9.856846678501969e-9 -ValueData/416994786,8.790534159083372e-7,8.778542707284947e-7,8.806118527978725e-7,4.623282713701018e-9,3.692048697315199e-9,5.906247473388641e-9 -ValueData/1017225804,8.798898782710196e-7,8.785709040670462e-7,8.808448061951191e-7,3.580364013549222e-9,2.553151270070911e-9,5.160336164174102e-9 -ValueData/2303812413,8.853526422356704e-7,8.838839220225055e-7,8.864222933504421e-7,4.192930185092394e-9,3.3648720443019316e-9,5.638918598200019e-9 -ValueData/1550487771,8.893305795100219e-7,8.882044946857695e-7,8.905424814684701e-7,3.87085888728535e-9,3.3395650069478923e-9,4.6165101262819735e-9 -ValueData/557311536,8.795485409813151e-7,8.782372933480821e-7,8.807655026552791e-7,4.325070519418052e-9,3.5778737630018756e-9,5.451801213353196e-9 -ValueData/2632043889,8.818464237778249e-7,8.804411487573649e-7,8.837489882043619e-7,5.6849069044596965e-9,4.711346822750629e-9,6.837227978367089e-9 -ValueData/456462430,8.806541307195791e-7,8.790288892137052e-7,8.827440373022262e-7,6.14916657970514e-9,4.280603951726165e-9,1.0130355044661883e-8 -ValueData/394899960,8.808575223784704e-7,8.791850589358605e-7,8.827145376292514e-7,6.063752828887917e-9,5.074441594133893e-9,7.516666228118109e-9 -ValueData/2207228400,8.816810012488357e-7,8.798575201362776e-7,8.833856758051505e-7,6.056053763776328e-9,5.048248860538733e-9,7.70975767919364e-9 -ValueData/177159636,8.800849996021792e-7,8.787426385316129e-7,8.814600638305174e-7,4.373109959334574e-9,3.832763985306158e-9,5.205320572615689e-9 -ValueData/1339433522,8.8369697936304e-7,8.813462536764825e-7,8.872230576671357e-7,9.725150233244383e-9,6.7087681434698835e-9,1.6078748268940058e-8 -ValueData/300786640,8.818663093090303e-7,8.809416039998047e-7,8.830678482922842e-7,3.4575472984454566e-9,2.828033139291388e-9,4.658949749047596e-9 -ValueData/15867390,8.835614201246594e-7,8.826618631111632e-7,8.845275141042677e-7,3.3869367863197277e-9,2.813445505198861e-9,4.331455729538697e-9 -ValueData/692120268,8.832376503612247e-7,8.819562124491105e-7,8.84722434553226e-7,4.818378781933753e-9,4.004457571672129e-9,5.814914746474962e-9 -UnValueData/4,9.068421423883069e-7,9.061851879315348e-7,9.075469372063723e-7,2.3716507105819652e-9,1.984981132077256e-9,2.910120402091428e-9 -UnValueData/146,2.9053981872376373e-6,2.9011623792897847e-6,2.9094564963237254e-6,1.41087031722094e-8,1.1888875739712734e-8,1.684538919437561e-8 -UnValueData/1477,2.907111413865943e-6,2.9040351426743376e-6,2.9107160438364092e-6,1.1722585169505525e-8,1.0239625213678274e-8,1.3533701087446573e-8 -UnValueData/1424,1.959057274947463e-5,1.9584082643210964e-5,1.9599699159862095e-5,2.7663350371587914e-8,1.998773073048335e-8,4.518875236145975e-8 -UnValueData/14734,1.9530668905760955e-5,1.951921165483708e-5,1.9541567915562188e-5,3.781919240040988e-8,3.3077890275871535e-8,4.419280781957179e-8 -UnValueData/7104,9.655933642292642e-5,9.653139723454666e-5,9.658943571528039e-5,1.0030607319282723e-7,7.988801564224824e-8,1.2919696335077385e-7 -UnValueData/73654,9.584704253047986e-5,9.578387454994725e-5,9.592021181429972e-5,2.298477743663809e-7,1.9824512203122537e-7,2.7625798128862695e-7 -UnValueData/14204,1.9539873295628687e-4,1.953129313131433e-4,1.9547535630241525e-4,2.878289571323345e-7,2.3950686541812354e-7,3.669177852270458e-7 -UnValueData/147304,1.93966071639084e-4,1.9383708601387238e-4,1.9409713066233938e-4,4.364766920954256e-7,3.6711989177859925e-7,5.529617642161011e-7 -UnValueData/71004,1.1330109053186875e-3,1.1221081458933117e-3,1.1404336363814711e-3,2.8998910958958856e-5,2.533149833057745e-5,3.6442361282690845e-5 -UnValueData/736504,1.0916397816359352e-3,1.0889953921723629e-3,1.096596068415768e-3,1.1552661496214139e-5,5.941820435510034e-6,1.8388129989159933e-5 -UnValueData/142004,2.477771794323466e-3,2.4694298869129072e-3,2.4990196172122964e-3,3.9179072105422557e-5,2.028957489738693e-5,6.98673025622596e-5 -UnValueData/1473004,2.4601048481371355e-3,2.4502083290617567e-3,2.4813366173195416e-3,4.4844819826607744e-5,2.061743345585051e-5,7.180641490025408e-5 -UnValueData/23,1.3049032491374263e-6,1.3031286663478204e-6,1.3071530087461587e-6,6.570290203634116e-9,5.436206142884675e-9,7.993355508172386e-9 -UnValueData/14204,1.946569963557336e-4,1.9450583005103632e-4,1.9484030254448623e-4,5.261890092257365e-7,3.869223921703829e-7,7.086335871840278e-7 -UnValueData/24104,1.9495938063596527e-4,1.9488872545065825e-4,1.9506189336538642e-4,2.751536681324497e-7,2.18786289415935e-7,3.566909955074637e-7 -UnValueData/147304,1.948521636948272e-4,1.9456742487488558e-4,1.9587441255395857e-4,1.6446144902511552e-6,2.8362401483757646e-7,3.468789690953717e-6 -UnValueData/1384804,1.9521958382787111e-4,1.9517200204708117e-4,1.952707562669848e-4,1.6704652042495765e-7,1.3902808007457288e-7,2.2348042922625153e-7 -UnValueData/23,1.3052076954454706e-6,1.3035432771074695e-6,1.3082312923546576e-6,7.803860530317902e-9,4.711306614460252e-9,1.3487953164312609e-8 -UnValueData/23,1.3090297713192198e-6,1.3074075434157618e-6,1.3106717219773248e-6,5.446584556746961e-9,4.822819115074655e-9,6.235147687747254e-9 -UnValueData/23,1.311386557650879e-6,1.3088097018827555e-6,1.318287998798856e-6,1.3791990291854225e-8,6.311566356543765e-9,2.6689878350957732e-8 -UnValueData/196,3.382253929834435e-6,3.3795791241429007e-6,3.3851415479600903e-6,9.13658293127138e-9,7.703123817753193e-9,1.0991138050387187e-8 -UnValueData/2020,2.769565193646776e-5,2.7677945960578738e-5,2.7709181695998228e-5,4.956861112358337e-8,4.172359040001151e-8,5.96667485220342e-8 -UnValueData/5989,8.78085379449701e-5,8.778680857966858e-5,8.783528126893412e-5,8.119635179360278e-8,6.54034652565772e-8,1.0519581251380834e-7 -UnValueData/4,8.965831917220561e-7,8.948946698968546e-7,8.975403269391364e-7,3.978636354308552e-9,2.5987193605874843e-9,7.418045188187781e-9 -UnValueData/806,1.8966673571113277e-6,1.8949694196063312e-6,1.8981767711669928e-6,5.574189488354453e-9,4.691170079282188e-9,6.656525613718971e-9 -UnValueData/2011,3.344681350987945e-6,3.3431182788229923e-6,3.3463257102325986e-6,5.210658433772258e-9,4.358519179727488e-9,6.217635254393469e-9 -UnValueData/4,8.974299954678173e-7,8.959739565868861e-7,8.989408107594033e-7,4.982089757543563e-9,4.365105929330059e-9,5.718492070203431e-9 -UnValueData/4,9.033425126442837e-7,9.020432332067919e-7,9.063245352883466e-7,6.327583302498122e-9,3.2921135915017722e-9,1.2572453341446008e-8 -UnValueData/2521,1.3118266500716435e-6,1.3102686939287234e-6,1.3133088924617764e-6,5.006353386537573e-9,4.332272366330288e-9,5.895966419360369e-9 -UnValueData/114871409,0.10230505891494138,0.10058317513688018,0.1060228517330769,3.9575937235628664e-3,1.706012930590348e-3,6.337289958860899e-3 -UnValueData/7955480,1.059066568250036e-2,1.054941025225458e-2,1.066469347657569e-2,1.4679691606051868e-4,7.389838990047171e-5,2.262859181130299e-4 -UnValueData/106506417,3.917322197078474e-2,3.881943096081982e-2,3.9712471356661255e-2,9.042729147858443e-4,5.544791072843227e-4,1.308271556527119e-3 -UnValueData/133276873,6.741456710439037e-2,6.701763781806142e-2,6.816392717958127e-2,9.078776424407558e-4,2.815588758165663e-4,1.3521281422263936e-3 -UnValueData/149948764,9.55795649538881e-2,9.491136615231101e-2,9.670401054124038e-2,1.3827573370439122e-3,3.006590766389777e-4,1.7950013442465046e-3 -UnValueData/42684588,1.3889494518145267e-2,1.381745397196657e-2,1.4011565751498796e-2,2.4574506577860144e-4,1.546708243977333e-4,3.622194317290015e-4 -UnValueData/2328330,1.7326415313575014e-2,1.724567491226159e-2,1.7460563129391007e-2,2.4275882922429468e-4,1.6242407349935e-4,3.5579022994900096e-4 -UnValueData/1817236,3.865449638314245e-3,3.8509280349554734e-3,3.8911741896913103e-3,5.8295468960910656e-5,3.389961966563605e-5,9.564524858489304e-5 -UnValueData/5018602,1.5891421680943685e-3,1.5851306547804945e-3,1.6003460257286524e-3,2.0521513321048193e-5,1.1261232038182564e-5,3.745105940473335e-5 -UnValueData/298760976,0.11766399265782508,0.11564502278841766,0.1206492872326635,3.732029898764641e-3,2.0403676296774716e-3,5.893750786666082e-3 -UnValueData/61509608,6.0072692947197005e-2,5.964346627794168e-2,6.098620435515281e-2,1.0841719945671922e-3,4.035311641393299e-4,1.7142900966794275e-3 -UnValueData/148895716,6.846849368629207e-2,6.811004588534393e-2,6.90899393872007e-2,7.924890688677503e-4,4.422023058021328e-4,1.0826088099082309e-3 -UnValueData/187844113,8.633297566867744e-2,8.563077018518622e-2,8.740873092785477e-2,1.5681982014464574e-3,9.956656284170928e-4,1.9664579627141957e-3 -UnValueData/96560479,8.770143541766123e-2,8.717671918475793e-2,8.832345825309554e-2,9.760061846602834e-4,6.064344582901466e-4,1.4253389015221323e-3 -UnValueData/5750026,0.10621549403032114,0.10489735715140505,0.10826498204497276,2.7426436165770727e-3,1.9944064160961456e-3,3.3512016431393467e-3 -UnValueData/30569413,1.524956531653715e-2,1.5194020764744331e-2,1.5347827184350507e-2,1.7769511596496746e-4,1.0563131021824827e-4,2.704359805582908e-4 -UnValueData/50809742,0.173982669152066,0.17140015408928905,0.17786427413043723,4.497340793485504e-3,2.5847689502076937e-3,6.169008569130326e-3 -UnValueData/1357928,1.263916227803773e-3,1.2617772876837034e-3,1.2681803026916147e-3,9.761145025447326e-6,4.496233328702742e-6,1.7261333861755356e-5 -UnValueData/14682800,1.79078948324892e-2,1.7763709491000097e-2,1.8097800251242215e-2,4.0319671438415647e-4,3.331163869988835e-4,4.923810804524641e-4 -UnValueData/35229121,1.3747346986933686e-2,1.3686864398855775e-2,1.3827945906666876e-2,1.7003271753283423e-4,1.2209423987234437e-4,2.2591384882888379e-4 -UnValueData/76705843,7.926317495781751e-2,7.860985664384705e-2,8.01817899538825e-2,1.3416947365746988e-3,1.0023044305621205e-3,1.8301638796914843e-3 -UnValueData/2587834,1.0072654491918435e-3,1.006579665272486e-3,1.007918925387012e-3,2.4207415639179877e-6,2.0102539711100953e-6,3.109838767548292e-6 -UnValueData/13586134,4.3119579343260115e-3,4.299409219863996e-3,4.334282567032606e-3,5.248090508033591e-5,3.434124112779327e-5,7.88640397177202e-5 -UnValueData/65975004,2.086420145344267e-2,2.0723782770528217e-2,2.105179817385415e-2,3.723693542529308e-4,2.808698420265533e-4,4.973768407227705e-4 -UnValueData/86182573,2.7016138464276727e-2,2.6838813843668572e-2,2.7321639495573508e-2,4.94126432140938e-4,3.0545446453326047e-4,7.035530617835902e-4 -UnValueData/2202211,1.0083952425196518e-3,1.0074714840597537e-3,1.009350773723672e-3,3.2321764164667094e-6,2.326334966866852e-6,4.919550979849351e-6 -UnValueData/3626914,2.340661469725662e-2,2.325101441219348e-2,2.3599846081283526e-2,3.898602954368183e-4,3.1165357117876927e-4,4.877970278032597e-4 -UnValueData/210747884,7.666129932339702e-2,7.568121474679737e-2,7.74360370099367e-2,1.5723035737500244e-3,1.0643488402185951e-3,2.4860264919901553e-3 -UnValueData/279233266,0.15765267788293155,0.15265699509835365,0.1616267102064096,6.747794309759976e-3,3.3005427832788095e-3,1.0563488348119952e-2 -UnValueData/16616604,2.2555180938968182e-2,2.2366449410268073e-2,2.2760927396947996e-2,4.343505767591083e-4,3.0134831172842725e-4,6.684628228788499e-4 -UnValueData/1759604,6.871022698594183e-4,6.865251517819906e-4,6.876065820641521e-4,1.7576441565825255e-6,1.4225349192904165e-6,2.4124859130789056e-6 -UnValueData/8817504,3.660277346543132e-3,3.650840296025303e-3,3.676240838505098e-3,3.76614550435916e-5,2.59139591619614e-5,5.4328584851303237e-5 -UnValueData/8690724,8.495466347728154e-3,8.462949503605741e-3,8.543558245591977e-3,1.0109925449702793e-4,7.579850045069569e-5,1.4692845224440897e-4 -UnValueData/269407217,9.773407785408364e-2,9.647709665704203e-2,9.949821337229675e-2,2.4081049713073057e-3,1.9146099373921828e-3,3.021067724304747e-3 -UnValueData/2347534,6.565488314749383e-4,6.561091736415499e-4,6.568947216249377e-4,1.3397100185705023e-6,1.0417283899960786e-6,1.749216169723167e-6 -UnValueData/241997912,0.10299819983382638,0.10126023418639624,0.10516212606240832,3.1767174399700455e-3,2.015755310872373e-3,4.747485988133599e-3 -UnValueData/16206322,4.412175649838896e-2,4.384531305185683e-2,4.457355014969472e-2,6.750426038807096e-4,4.350987200721451e-4,1.0522920720509913e-3 -UnValueData/75211182,7.876843805210518e-2,7.784845081719732e-2,7.970574629544798e-2,1.6062835723028406e-3,1.29859849475821e-3,1.983599687129346e-3 -UnValueData/259779678,0.12150476825190708,0.12016215596425657,0.12267757131485268,1.9738532269128633e-3,1.4481775998724114e-3,2.604093798204616e-3 -UnValueData/196591531,0.10164275914003557,9.94190867461356e-2,0.10327495369219224,3.179082870929967e-3,2.2198253875588573e-3,3.7089635026842033e-3 -UnValueData/27275076,2.2996221114788298e-2,2.2849392289812063e-2,2.3206296322648732e-2,4.057237645367218e-4,2.594701360594864e-4,6.179159594195236e-4 -UnValueData/331610230,0.1171365568365824,0.11489116091979668,0.12029999292766054,3.91535831852172e-3,2.7972016546109098e-3,5.008812554304281e-3 -UnValueData/21224754,2.63530527376584e-2,2.6136459742041068e-2,2.656662110838686e-2,4.671014484644755e-4,3.776654235679501e-4,5.893222572907877e-4 -UnValueData/50641504,4.849716296275775e-2,4.79671129815398e-2,4.9104121905264406e-2,1.0509414776559748e-3,8.284674155887278e-4,1.3301064799037486e-3 -UnValueData/278609244,0.1137901517429522,0.11170282214131605,0.11637218942854642,3.49374511357859e-3,2.2884030916294575e-3,4.906859579362178e-3 -UnValueData/22452206,9.870166622796498e-3,9.825475612238323e-3,9.904329596564173e-3,1.0178622841891616e-4,7.314005343534361e-5,1.4808184908100952e-4 -UnValueData/92714696,0.17159821468715866,0.16569243465505895,0.17883632250928455,9.627202022390665e-3,4.858150670255226e-3,1.4862449007653556e-2 -UnValueData/22287115,1.3370951614584556e-2,1.3290041733088198e-2,1.3418783818341185e-2,1.5541067658567622e-4,9.75270219091354e-5,2.4039724813167723e-4 -UnValueData/2008654,5.493689912123631e-4,5.491444016020693e-4,5.496271868811518e-4,8.62199502496023e-7,6.974190917911312e-7,1.1903651550599839e-6 -UnValueData/21066567,4.760839045584599e-2,4.687811097533973e-2,4.8757656406249024e-2,1.7906345575714306e-3,8.154148988534519e-4,2.550632242102737e-3 +LookupCoin/4/4/1,1.1534472901399238e-6,1.1524112485300528e-6,1.1547714765589249e-6,4.0641621926718e-9,3.5452038180553337e-9,4.940445527575718e-9 +LookupCoin/4/4/4,1.1610866397454247e-6,1.1604563749532721e-6,1.1617063429991664e-6,2.017385982146994e-9,1.7121017071566048e-9,2.465151601504615e-9 +LookupCoin/4/4/4,1.1774005815816455e-6,1.1757529390389185e-6,1.179176847539009e-6,5.658757651279759e-9,4.644228857340083e-9,6.611495473612035e-9 +LookupCoin/4/4/6,1.1916918928618511e-6,1.190422907748009e-6,1.193173839698956e-6,4.665977313866328e-9,3.6631933897168235e-9,5.907467979461302e-9 +LookupCoin/4/4/7,1.2081228008186858e-6,1.2075792823969807e-6,1.2087450470879218e-6,2.1007936976091115e-9,1.7416127415560338e-9,2.5734618148224033e-9 +LookupCoin/4/4/9,1.22186256897354e-6,1.22079638986199e-6,1.2228174375924155e-6,3.297746327386577e-9,2.839091055846269e-9,3.821333117747494e-9 +LookupCoin/4/4/10,1.2190771032840023e-6,1.2182323802927799e-6,1.2204703608998758e-6,3.679007873778502e-9,2.5664700856261745e-9,5.709716144647835e-9 +LookupCoin/4/4/3,1.1760034998696908e-6,1.1749764160005035e-6,1.1773987433390327e-6,4.134618566929028e-9,3.4983131522155535e-9,4.846099138284671e-9 +LookupCoin/4/4/4,1.1724389842513614e-6,1.171202474639233e-6,1.1736212940968032e-6,4.060397866264552e-9,3.3911098606443696e-9,4.874063846777242e-9 +LookupCoin/4/4/5,1.186276670542198e-6,1.1849660027412163e-6,1.1877881978386803e-6,4.746233008575273e-9,3.96889048330745e-9,6.169049327002083e-9 +LookupCoin/4/4/7,1.1985154329655813e-6,1.1977012560461198e-6,1.1998861807550411e-6,3.5356660936590374e-9,2.199240326494903e-9,6.085998058416401e-9 +LookupCoin/4/4/10,1.212044503566453e-6,1.2112549781307214e-6,1.2132939641287698e-6,3.085806921876905e-9,2.1491725020386978e-9,4.274791294719317e-9 +LookupCoin/4/4/9,1.2197458596870582e-6,1.2188660580397794e-6,1.2208428419766672e-6,3.3842947898904777e-9,2.8668608524608777e-9,4.0727782723269836e-9 +LookupCoin/4/4/9,1.2010997264914224e-6,1.200106382607801e-6,1.2023171386855648e-6,3.431246601005009e-9,2.867932018216361e-9,4.0822590889582006e-9 +LookupCoin/4/4/10,1.2348766962338111e-6,1.2339246262576525e-6,1.2357811788641032e-6,3.2816607860449476e-9,2.857535355670083e-9,3.780985674266283e-9 +LookupCoin/4/4/9,1.2144090697470449e-6,1.2131084097130315e-6,1.2156572132531938e-6,4.304814734381262e-9,3.6577989003638705e-9,5.042081882140313e-9 +LookupCoin/4/4/10,1.209618422286151e-6,1.2084066754067936e-6,1.2111073368850447e-6,4.371855457335534e-9,3.3656545268840697e-9,5.779470032895302e-9 +LookupCoin/4/4/10,1.210165342950211e-6,1.2090749210374545e-6,1.2113250291719528e-6,3.788921550293763e-9,3.2155320868767343e-9,4.6269499754478604e-9 +LookupCoin/4/4/10,1.2235940789270705e-6,1.2225606057299341e-6,1.2246289196011864e-6,3.400679978557537e-9,2.8011107626270736e-9,4.613236340246698e-9 +LookupCoin/4/4/10,1.2230668561970737e-6,1.2221937446410287e-6,1.2237095716104843e-6,2.475674557308414e-9,1.9626501907285127e-9,3.7071967743530107e-9 +LookupCoin/4/4/9,1.1889029156920706e-6,1.1880053862709033e-6,1.1900374917253151e-6,3.3478126043567047e-9,2.7289049311982276e-9,4.855469961787361e-9 +LookupCoin/4/4/10,1.227862756358173e-6,1.2267847329829582e-6,1.228962269773679e-6,3.6921321326127223e-9,3.139000902274087e-9,4.687705887612031e-9 +LookupCoin/4/4/10,1.2072638717824325e-6,1.2065372351649394e-6,1.2080603606433759e-6,2.5605379801492863e-9,2.130719335261522e-9,3.342840436529004e-9 +LookupCoin/4/4/9,1.2048640045178505e-6,1.2041040836384836e-6,1.206053529944406e-6,3.1152890266742653e-9,2.2986310562366542e-9,4.9659107627078964e-9 +LookupCoin/4/4/9,1.2170554214680805e-6,1.2158461767462672e-6,1.218250184207636e-6,4.05936816577866e-9,3.4099039201076022e-9,4.9708528153023505e-9 +LookupCoin/4/4/9,1.2116410991702124e-6,1.2110855372022904e-6,1.2123167194971357e-6,2.110680574196297e-9,1.5738372055536842e-9,3.1795340192951133e-9 +LookupCoin/4/4/9,1.2200438970276316e-6,1.2189933591524046e-6,1.221305925182948e-6,3.7037679394520034e-9,3.1290372975654653e-9,4.551229486028815e-9 +LookupCoin/4/4/10,1.2173088998090225e-6,1.2165042326120895e-6,1.2181983291801061e-6,2.8029973454960424e-9,2.37231637695913e-9,3.4604317606972556e-9 +LookupCoin/4/4/9,1.2017126423022042e-6,1.200632281748984e-6,1.202903116044268e-6,3.781045240585668e-9,2.9397025316566446e-9,4.946098843185507e-9 +LookupCoin/4/4/10,1.2304983791984658e-6,1.2299797841357625e-6,1.2309998972246447e-6,1.7068516958025802e-9,1.4729426671866016e-9,2.033510242377355e-9 +LookupCoin/4/4/8,1.213066221159993e-6,1.2116525285687004e-6,1.215071690889799e-6,5.3617662326851e-9,3.935749632031287e-9,7.901580396978991e-9 +LookupCoin/4/4/9,1.2253324093752865e-6,1.2240369347052394e-6,1.2264504879254988e-6,3.88427355225941e-9,2.968318109520233e-9,5.133414413710082e-9 +LookupCoin/4/4/10,1.2311475932985818e-6,1.2299045696058998e-6,1.232424953162509e-6,4.129560644494372e-9,3.4953810297482135e-9,5.366496584623623e-9 +LookupCoin/4/4/10,1.2349346616905418e-6,1.2336204242442853e-6,1.236189233621282e-6,4.010625806071552e-9,3.4640917847106747e-9,4.803344725349452e-9 +LookupCoin/4/4/10,1.2197488623106857e-6,1.218870714132973e-6,1.220587553143493e-6,2.9601116205664266e-9,2.511249230129429e-9,3.4768164681892435e-9 +LookupCoin/4/4/9,1.2087709881874945e-6,1.2075273290853454e-6,1.2099009737387109e-6,3.887060104710359e-9,3.3371957867118426e-9,4.511098188658732e-9 +LookupCoin/4/4/10,1.2300092057070488e-6,1.2290346373801981e-6,1.2308991882796534e-6,3.064016089741907e-9,2.583419648104346e-9,3.79983204057076e-9 +LookupCoin/4/4/9,1.2059029078447557e-6,1.2052928651550498e-6,1.2065914611136291e-6,2.1010403170160913e-9,1.7796349524022461e-9,2.652918769719015e-9 +LookupCoin/4/4/10,1.2132412510204579e-6,1.2121888809755203e-6,1.2149708146143543e-6,4.232696012011695e-9,3.0783915523862898e-9,6.910426954285835e-9 +LookupCoin/4/4/7,1.1988345585365298e-6,1.1978472369136555e-6,1.1999495924891883e-6,3.6450023936990258e-9,3.2413028652772947e-9,4.418496031279859e-9 +LookupCoin/4/4/9,1.214519533779959e-6,1.2136575736660475e-6,1.2159919307151074e-6,3.7050313705220404e-9,2.3354419165849325e-9,6.5731886027933965e-9 +LookupCoin/4/4/8,1.2020350986276132e-6,1.201218193546641e-6,1.2026925436305998e-6,2.467081687777941e-9,1.8043871359229474e-9,3.3392450543947458e-9 +LookupCoin/4/4/10,1.2222679020181828e-6,1.220905632495155e-6,1.2246266737260014e-6,5.679227279774581e-9,3.727096530858876e-9,9.523614827378908e-9 +LookupCoin/4/4/9,1.2135489900544324e-6,1.2126793816267723e-6,1.2144133815929518e-6,3.023744411916157e-9,2.5780024526158883e-9,3.596657852145017e-9 +LookupCoin/4/4/8,1.2197908538280475e-6,1.2180956604588496e-6,1.2217632683497774e-6,6.084910617903105e-9,5.435179776000006e-9,7.073790751341013e-9 +LookupCoin/4/4/9,1.212007864598544e-6,1.2113330398221342e-6,1.2126660609808017e-6,2.308335843355634e-9,1.915042172033909e-9,2.774023536063372e-9 +LookupCoin/4/4/8,1.2212852306980274e-6,1.2201513163209499e-6,1.2224841849159272e-6,3.953112459758078e-9,3.16437124868229e-9,5.026939221050529e-9 +LookupCoin/4/4/10,1.2353131845776723e-6,1.233941986574437e-6,1.2370980165559903e-6,5.530757184850481e-9,4.753838675200683e-9,6.442169482481464e-9 +LookupCoin/4/4/9,1.1793206086375916e-6,1.178584733986701e-6,1.179961860665618e-6,2.4267020853651928e-9,1.959651496291369e-9,3.3470155014444936e-9 +LookupCoin/4/4/8,1.204870645799376e-6,1.2036139668967718e-6,1.205886776594027e-6,3.727968380828233e-9,3.0891533145762463e-9,4.467331996571003e-9 +LookupCoin/4/4/10,1.2178982336014464e-6,1.2169471540437263e-6,1.2191283317440976e-6,3.7112786514496762e-9,2.935318707378828e-9,5.140744984906639e-9 +LookupCoin/4/4/10,1.2188458213877058e-6,1.2179859338278188e-6,1.2199100722773312e-6,3.3422795823639585e-9,2.7411903970205664e-9,4.636506287545538e-9 +LookupCoin/4/4/9,1.214638995454963e-6,1.213708813972099e-6,1.2160569047240595e-6,3.7490605869356555e-9,2.9160780648119563e-9,5.229456441325402e-9 +LookupCoin/4/4/10,1.2225433614748636e-6,1.2215482375269644e-6,1.2237754976291384e-6,3.629038618997282e-9,3.0305032419436265e-9,4.414320498812328e-9 +LookupCoin/4/4/10,1.2275498051888786e-6,1.2264323478666893e-6,1.2286517276695741e-6,3.6702369088252977e-9,3.3133800555606663e-9,4.176629006390668e-9 +LookupCoin/4/4/8,1.2016804483751465e-6,1.2011310435585076e-6,1.2023378701823055e-6,1.937509982283731e-9,1.5303199131455102e-9,2.4570647348392655e-9 +LookupCoin/4/4/10,1.2112570026879238e-6,1.2101568608309042e-6,1.212360063064909e-6,3.717319310167394e-9,2.9194951052602018e-9,4.970362447163203e-9 +LookupCoin/4/4/9,1.2188977630170537e-6,1.2178359601285404e-6,1.2201188282513097e-6,3.769356684584986e-9,3.149442271264225e-9,4.772762980433492e-9 +LookupCoin/4/4/10,1.2323943829237225e-6,1.2315382548194777e-6,1.2337680234645939e-6,3.561426918764251e-9,2.28979787786825e-9,6.099199160825918e-9 +LookupCoin/4/4/10,1.2298650745956071e-6,1.229110859787272e-6,1.230744307303272e-6,2.806991300904623e-9,2.2927922205537944e-9,3.7754207967714976e-9 +LookupCoin/4/4/7,1.193032734889915e-6,1.19178202411572e-6,1.1947430231611674e-6,4.869158030513213e-9,3.931740250825642e-9,6.177773842346549e-9 +LookupCoin/4/4/9,1.216371198408557e-6,1.2158361401488627e-6,1.2168538849375672e-6,1.7697403817443696e-9,1.3963436510638211e-9,2.27239285508568e-9 +LookupCoin/4/4/10,1.2325742846654678e-6,1.231734878079346e-6,1.2346106018503925e-6,4.183543302328641e-9,2.1037526600700003e-9,7.804656639944263e-9 +LookupCoin/4/4/11,1.237407537657278e-6,1.2356528408070078e-6,1.2392376472775964e-6,5.821969594412085e-9,5.16630720838863e-9,6.586214451160239e-9 +LookupCoin/4/4/5,1.1856258433419084e-6,1.1842069572543944e-6,1.187178673161659e-6,5.1846898288680965e-9,4.409310187551346e-9,6.254192759844087e-9 +LookupCoin/4/4/11,1.2155008424622768e-6,1.2146757827742595e-6,1.2164111476274816e-6,2.899675672525393e-9,2.441539784366106e-9,3.512372279146876e-9 +LookupCoin/4/4/10,1.2065546917201032e-6,1.2046172722692515e-6,1.2090198796299678e-6,7.545930799225587e-9,5.9688206286642834e-9,1.1089470895454683e-8 +LookupCoin/4/4/10,1.2196360708625704e-6,1.2184040276358496e-6,1.2213006834303905e-6,4.802926137384681e-9,3.757626126043643e-9,6.290923368477043e-9 +LookupCoin/4/4/11,1.224974987541705e-6,1.223160938351159e-6,1.2311246718525401e-6,1.013385284774211e-8,4.07257074376166e-9,1.971828248431561e-8 +LookupCoin/4/4/8,1.2011736531568869e-6,1.200438396722228e-6,1.2020688899348711e-6,2.6751216897864477e-9,2.2604525350603145e-9,3.388947160952035e-9 +LookupCoin/4/4/11,1.2184304981837817e-6,1.2166589664240896e-6,1.22329905903681e-6,8.97842151304465e-9,3.728768405784872e-9,1.889722867283809e-8 +LookupCoin/4/4/8,1.2067816840543925e-6,1.206361748517341e-6,1.2075703192123119e-6,1.9068537051218633e-9,1.4189981821104017e-9,2.8939086084684083e-9 +LookupCoin/4/4/8,1.2125223673672614e-6,1.211204434430315e-6,1.2160943051154748e-6,7.288770169418742e-9,2.485098578436094e-9,1.5025899876584037e-8 +LookupCoin/4/4/11,1.2205219527129726e-6,1.2192549402163512e-6,1.2215892353197644e-6,3.8614757915982414e-9,3.1992058613565774e-9,5.063023013505288e-9 +LookupCoin/4/4/10,1.2300843789497594e-6,1.2290438497712692e-6,1.2311008897226012e-6,3.5227882086061747e-9,2.7499034147861968e-9,4.810875970489256e-9 +LookupCoin/4/4/10,1.2013929562744759e-6,1.200481607647232e-6,1.202504870822784e-6,3.2751923244814385e-9,2.1168456634541903e-9,5.8109592636043915e-9 +LookupCoin/4/4/10,1.2305977876473265e-6,1.2294905496966056e-6,1.2318603561077214e-6,4.0711509166902646e-9,3.378055077358201e-9,4.9481380681675515e-9 +LookupCoin/4/4/11,1.2288881103180648e-6,1.2282348118217263e-6,1.2296516339789366e-6,2.377608466835124e-9,1.982176930726083e-9,2.9684094818468865e-9 +LookupCoin/4/4/11,1.2350331861787772e-6,1.233964666618698e-6,1.2362266144993453e-6,3.732233729284558e-9,3.1991169653336913e-9,4.476369285213807e-9 +LookupCoin/4/4/10,1.2209007387611954e-6,1.2202357876462576e-6,1.2221044179899346e-6,3.0047569336565615e-9,1.6387754598225905e-9,4.949949437006407e-9 +LookupCoin/4/4/11,1.2375217358339814e-6,1.2367125703734653e-6,1.2384104957761834e-6,2.9578146690622734e-9,2.373257191219735e-9,3.641735250392075e-9 +LookupCoin/4/4/11,1.231512711706511e-6,1.2304143879197356e-6,1.2325937237500649e-6,3.5919239356151746e-9,2.787931962181056e-9,5.207498544217727e-9 +LookupCoin/4/4/11,1.2332103660304604e-6,1.2324095784582703e-6,1.2340205232095756e-6,2.703178647844072e-9,2.207595315547423e-9,3.3698139708385147e-9 +LookupCoin/4/4/10,1.2151010613053054e-6,1.2139069708297562e-6,1.2171063042801e-6,4.881478217634782e-9,3.5874051362365304e-9,7.992433034555917e-9 +LookupCoin/4/4/11,1.2290435369298266e-6,1.2269191688897788e-6,1.230921245801445e-6,6.574508748365292e-9,5.607199588352304e-9,7.77862262124682e-9 +LookupCoin/4/4/10,1.2091823523230104e-6,1.2084458834186694e-6,1.2104132057142133e-6,3.1511186351630638e-9,2.0381734613969673e-9,5.324717673383524e-9 +LookupCoin/4/4/10,1.2120435917234926e-6,1.2106595211874085e-6,1.21343947039997e-6,4.463333369427232e-9,3.999211413752267e-9,5.065051826522262e-9 +LookupCoin/4/4/10,1.2115496386333912e-6,1.2107029499384152e-6,1.212711881455988e-6,3.3007519858248528e-9,2.4441693312056897e-9,5.1149851260605535e-9 +LookupCoin/4/4/10,1.2150987387014107e-6,1.2144473549563434e-6,1.2155839955357989e-6,1.9583246105665682e-9,1.5801607100607197e-9,2.671433754728061e-9 +LookupCoin/4/4/9,1.2208167607196566e-6,1.2191459373986416e-6,1.222880466312901e-6,6.255260576547086e-9,4.994336110190262e-9,9.083471646866714e-9 +LookupCoin/4/4/11,1.2358513536522013e-6,1.2352265536976772e-6,1.2366449353576938e-6,2.3451142257690808e-9,1.7693730410291272e-9,3.5932198647789172e-9 +LookupCoin/4/4/11,1.2257651415075026e-6,1.2248368995463083e-6,1.2271096253059002e-6,3.541646825146961e-9,2.5912654373993167e-9,4.65583839066808e-9 +LookupCoin/4/4/10,1.189168503538572e-6,1.188508588087873e-6,1.1898835184581933e-6,2.3638681236668316e-9,1.95397492832121e-9,2.982019185548157e-9 +LookupCoin/4/4/10,1.2145997780830431e-6,1.2125174055568225e-6,1.2175875014853785e-6,8.092910767610745e-9,6.236989087716155e-9,1.1448673234348647e-8 +LookupCoin/4/4/10,1.195433386129742e-6,1.1939042519461409e-6,1.1970554349787428e-6,4.914528778264369e-9,4.188980683740096e-9,5.745555946414595e-9 +LookupCoin/4/4/10,1.1928666809369907e-6,1.1916103904744267e-6,1.195695686873602e-6,5.7476910522975475e-9,3.558187498450454e-9,1.0467393690289418e-8 +LookupCoin/4/4/8,1.203582653497446e-6,1.202423914671103e-6,1.2047152726294545e-6,3.664306628139334e-9,3.104264253142358e-9,4.318388775789471e-9 +LookupCoin/4/4/10,1.2084679827135482e-6,1.206996019622262e-6,1.214027836858732e-6,8.226948327647268e-9,2.5153713838484612e-9,1.696432659805014e-8 +LookupCoin/4/4/10,1.2267797289998131e-6,1.2262703098660658e-6,1.2274384057461149e-6,1.9698454215779976e-9,1.6576190632875758e-9,2.5665926112104314e-9 +LookupCoin/4/4/9,1.217240806072733e-6,1.215964834128526e-6,1.2202844236669054e-6,6.107061895278018e-9,3.2397793222663967e-9,1.3099167126308328e-8 +LookupCoin/4/4/10,1.2056710515306366e-6,1.204254538908951e-6,1.206733200031426e-6,4.110966465288715e-9,3.252502432967364e-9,5.030311055395879e-9 +LookupCoin/4/4/11,1.2223353980960082e-6,1.2209166862802165e-6,1.2252746353501009e-6,6.480951807842912e-9,3.5034487409886137e-9,1.1574221631620568e-8 +LookupCoin/4/4/11,1.2381906860640788e-6,1.2373816720875036e-6,1.2390309550000634e-6,2.8631615772459806e-9,2.584711595331991e-9,3.2912099452583487e-9 +LookupCoin/4/4/9,1.2041700063443865e-6,1.202723266979627e-6,1.2079953584787903e-6,7.970720318115764e-9,2.6455179323248265e-9,1.4875884319605539e-8 +LookupCoin/4/4/11,1.2206119738308772e-6,1.2193183542760845e-6,1.2219578402103584e-6,4.421091993181346e-9,3.5314140955497563e-9,5.24459337396916e-9 +LookupCoin/4/4/10,1.198688570671991e-6,1.1968092788731975e-6,1.2002881672968227e-6,6.2467596841419095e-9,4.8838727318866745e-9,8.577949540828311e-9 +LookupCoin/4/4/9,1.2232712816681831e-6,1.222385109292051e-6,1.2243819421118973e-6,3.3287527982165607e-9,2.6530086716414487e-9,4.259887685515721e-9 +LookupCoin/4/4/10,1.2319188457093468e-6,1.231387927634095e-6,1.232453405915841e-6,1.8550053754712164e-9,1.5485091332345065e-9,2.2575283281189487e-9 +LookupCoin/4/4/11,1.2259649685593469e-6,1.2246129154364666e-6,1.2281652455358455e-6,5.816142161858434e-9,3.8951489061387544e-9,9.646584992867164e-9 +LookupCoin/4/4/9,1.220142726511326e-6,1.2189261873190347e-6,1.2213994758036873e-6,4.396649594965005e-9,3.778505570958797e-9,5.324803083927569e-9 +LookupCoin/4/4/11,1.2323923802385869e-6,1.2314441308735349e-6,1.2334798069320034e-6,3.490723498014477e-9,2.973056637385596e-9,4.581233410471864e-9 +LookupCoin/4/4/11,1.2157910391410865e-6,1.2144861124759398e-6,1.2172171945348252e-6,4.69167039176928e-9,4.107982909033791e-9,5.419100776764417e-9 +LookupCoin/4/4/11,1.2328985154623782e-6,1.231888251912911e-6,1.2338849794884602e-6,3.440244761247414e-9,2.9487504128928588e-9,4.095042364806446e-9 +LookupCoin/4/4/10,1.2125476453531075e-6,1.2115571273688314e-6,1.213813380078619e-6,3.838510243393416e-9,2.9102832815809218e-9,5.171613800260002e-9 +LookupCoin/4/4/11,1.2311677618980396e-6,1.2297267327679114e-6,1.232241892736664e-6,4.263137256955254e-9,3.4722101552463757e-9,5.727556907342786e-9 +ValueContains/4/1,1.108631478585558e-6,1.1077652148756856e-6,1.1095780707507516e-6,2.962047278539296e-9,2.4162243025980203e-9,3.6314232245633624e-9 +ValueContains/4/0,1.0225226778070809e-6,1.021594419066775e-6,1.0233771220888523e-6,2.903386621690029e-9,2.3700337419464644e-9,3.764812542120098e-9 +ValueContains/4/10,1.7251097731022483e-6,1.7217077584311812e-6,1.7290432063745155e-6,1.2504176745196251e-8,1.0689538466640446e-8,1.496722555714063e-8 +ValueContains/7/0,1.0235784262974995e-6,1.0227465999855973e-6,1.0244906985278278e-6,2.8917566010951786e-9,2.5231122576095735e-9,3.3727234776056936e-9 +ValueContains/7/0,1.0226450157806123e-6,1.0219602483898282e-6,1.0233104732466841e-6,2.245538471635945e-9,1.9317147620264348e-9,2.605014466382995e-9 +ValueContains/7/100,1.123983377436773e-5,1.1222673975558804e-5,1.1254568730097023e-5,5.2545069499185855e-8,4.2203479105756465e-8,6.81581825686575e-8 +ValueContains/10/0,1.0234815356516939e-6,1.0230323184094808e-6,1.0239782481409003e-6,1.6788403190347666e-9,1.3441788715659217e-9,2.3066110647896127e-9 +ValueContains/10/0,1.022244619801779e-6,1.0216088163183763e-6,1.0229490704321379e-6,2.2613060048559777e-9,1.9185721869678515e-9,2.7029739563952686e-9 +ValueContains/10/0,1.0187419478061535e-6,1.0180992699422179e-6,1.0194600390407757e-6,2.139824337180833e-9,1.6898653373863045e-9,2.626277907225411e-9 +ValueContains/10/1000,1.4095585241474237e-4,1.40817663844188e-4,1.4113608222739038e-4,5.341300107272371e-7,3.422739478520462e-7,7.303955664486585e-7 +ValueContains/5/200,1.750832958011064e-5,1.7483324946348768e-5,1.7531721338028892e-5,8.510690895587012e-8,7.098396376367275e-8,1.0344742833746426e-7 +ValueContains/1/0,1.020592742026185e-6,1.0195509509947287e-6,1.0217298205535592e-6,3.6166590105004055e-9,2.868519802715473e-9,5.003483216788357e-9 +ValueContains/4/0,1.0231213517874792e-6,1.0222083712608126e-6,1.0238784207289675e-6,2.7288594177355198e-9,2.1989322634766497e-9,3.4454860180383572e-9 +ValueContains/7/0,1.019703897420794e-6,1.0187441603659637e-6,1.021204124435237e-6,4.0538660814804425e-9,2.7584878102639575e-9,6.677707647772776e-9 +ValueContains/10/0,1.0206037033135496e-6,1.0200419460920349e-6,1.0211692962911852e-6,1.9432013088163367e-9,1.6471240403324677e-9,2.380931488825781e-9 +ValueContains/12/110,1.47200444837102e-5,1.470742072091629e-5,1.4735858043877813e-5,4.677837546673136e-8,4.061882525635276e-8,6.191283791581553e-8 +ValueContains/12/1313,1.7126666241371247e-4,1.7099080545307678e-4,1.7157898192302426e-4,9.68202018105592e-7,8.242358907525413e-7,1.1807674208216776e-6 +ValueContains/12/731,9.111141935328779e-5,9.089197590201364e-5,9.132384112555336e-5,7.192499505891549e-7,6.228624593803585e-7,8.584991672857017e-7 +ValueContains/12/3039,3.914054205241898e-4,3.904410118270601e-4,3.922776629299477e-4,3.087938735099823e-6,2.8023718189301774e-6,3.5020103424802864e-6 +ValueContains/8/29,3.53257811940542e-6,3.52865120291237e-6,3.5358542503453723e-6,1.2617613719759917e-8,1.0488847962062658e-8,1.5039190078498538e-8 +ValueContains/12/1387,1.7694455888490418e-4,1.767281190836957e-4,1.7716181771349444e-4,7.60547601643498e-7,6.586865242973147e-7,8.743651755609427e-7 +ValueContains/13/3588,4.7962670255488073e-4,4.787679277093584e-4,4.802711879365964e-4,2.609712886280009e-6,2.095427255079846e-6,3.1730649897826924e-6 +ValueContains/10/338,3.980823325383313e-5,3.974294686041632e-5,3.991431540039092e-5,2.869470839788121e-7,2.2147806515839266e-7,3.9098843554983166e-7 +ValueContains/12/2500,3.156930700588844e-4,3.153512578350851e-4,3.1608346679380553e-4,1.216935995051478e-6,1.0060533134261604e-6,1.4129709113305515e-6 +ValueContains/7/64,6.1035335386966655e-6,6.092514189843279e-6,6.1146805902651605e-6,3.752745203736218e-8,3.0816926658117025e-8,4.689103628448276e-8 +ValueContains/12/3182,4.10425232177756e-4,4.0978424672677785e-4,4.1100941942771976e-4,2.1224795575404285e-6,1.725067418676846e-6,2.8846629766683404e-6 +ValueContains/12/2076,2.591879470344235e-4,2.5894433377232303e-4,2.595175156188034e-4,9.487716829141452e-7,8.168184243920077e-7,1.109150937413403e-6 +ValueContains/12/1961,2.4850180952223173e-4,2.48326818085388e-4,2.487268295474985e-4,6.625368533225912e-7,5.448690968949389e-7,8.364963932806562e-7 +ValueContains/12/2980,3.809153778711491e-4,3.80474288223098e-4,3.8139115048989086e-4,1.5739831516032031e-6,1.320058965715184e-6,1.8193675785828874e-6 +ValueContains/11/205,2.5166582970979212e-5,2.508722790097956e-5,2.5232680826483777e-5,2.548368685620478e-7,2.1610800831303402e-7,2.9195695702762577e-7 +ValueContains/12/594,7.673364632125908e-5,7.665367709406551e-5,7.681009691834373e-5,2.607765906000331e-7,2.1370603129064027e-7,3.3549853027091536e-7 +ValueContains/13/3484,4.6410319453403715e-4,4.6352240032246974e-4,4.6466177647826575e-4,1.9822881797750665e-6,1.5041935527871901e-6,2.6046263177698874e-6 +ValueContains/13/33,4.8026691322994296e-6,4.797899512108592e-6,4.806995809846416e-6,1.532867093004693e-8,1.3252964970782209e-8,1.8330647941339627e-8 +ValueContains/10/144,1.6113413799843423e-5,1.6088900211313373e-5,1.6138758232005147e-5,8.455665267697632e-8,6.807650199999726e-8,1.066701763474308e-7 +ValueContains/12/2000,2.509994622932922e-4,2.5058199061113147e-4,2.513872301160663e-4,1.388573091390673e-6,1.182968307382935e-6,1.6605794288165797e-6 +ValueContains/13/2818,3.822259955150316e-4,3.813812302617948e-4,3.8284964292651405e-4,2.4073636397134105e-6,1.8388313198246135e-6,3.0702784321357275e-6 +ValueContains/12/1073,1.3256797382621142e-4,1.3244611935063065e-4,1.3270153786615604e-4,4.183392260824016e-7,3.5758255811849654e-7,4.992325654739546e-7 +ValueContains/11/1653,2.0171575123535486e-4,2.0130163845224583e-4,2.0208630582881662e-4,1.3722072907616494e-6,1.1703381245781852e-6,1.5637685576960973e-6 +ValueContains/13/1290,1.6512335952874338e-4,1.6494787773835452e-4,1.6527942337550919e-4,5.385093568127713e-7,4.4597118979784986e-7,6.74039437079728e-7 +ValueContains/12/1931,2.450869679238732e-4,2.447834902360666e-4,2.454533985092889e-4,1.1906080631538036e-6,9.653767871673086e-7,1.5841348439079563e-6 +ValueContains/12/113,1.4796083273877808e-5,1.4782517877194369e-5,1.4810289038988382e-5,4.903953145522286e-8,4.1858748560837425e-8,6.038102833364655e-8 +ValueContains/11/1466,1.7847298578394394e-4,1.7822258494108463e-4,1.7870184591731365e-4,8.261047563844038e-7,7.072730209232701e-7,9.673451728187376e-7 +ValueContains/12/243,2.912490900665435e-5,2.9089466363409e-5,2.9163214775750145e-5,1.2747698899741995e-7,1.092683913894289e-7,1.475739080764433e-7 +ValueContains/12/2725,3.5637934324297255e-4,3.555965345136923e-4,3.5712722853321747e-4,2.5189582340500527e-6,2.2113499787592496e-6,2.843821038015072e-6 +ValueContains/8/16,2.35511207934695e-6,2.3509261679096494e-6,2.3600084734896943e-6,1.5801598817434442e-8,1.2949378720804634e-8,2.193354996893263e-8 +ValueContains/11/1092,1.3551024067092528e-4,1.3528473912369104e-4,1.3574569731652835e-4,7.927947394548566e-7,6.224871129328504e-7,1.024184593891981e-6 +ValueContains/12/940,1.1546863743962826e-4,1.1531637820652565e-4,1.1568324418859595e-4,5.98922036386318e-7,5.057760604153949e-7,7.12357072934672e-7 +ValueContains/11/151,1.8906076066984876e-5,1.888605286651995e-5,1.892546686882719e-5,6.528839694424791e-8,5.551952808949426e-8,7.70546638326298e-8 +ValueContains/13/174,2.1718554560470205e-5,2.1688747834500112e-5,2.1759546711082756e-5,1.1509401305820709e-7,8.560452494599941e-8,1.8420460364946676e-7 +ValueContains/13/2449,3.23381191757996e-4,3.2304395484226116e-4,3.23865504904467e-4,1.3445274737734421e-6,9.809378950827171e-7,2.0706376713102894e-6 +ValueContains/12/2376,2.9768745493160816e-4,2.9709750010639663e-4,2.982641475913256e-4,1.97185260463418e-6,1.7263299212532655e-6,2.277879313627657e-6 +ValueContains/9/261,2.8124375075753676e-5,2.8076223121234054e-5,2.8179584052987132e-5,1.7441868120971644e-7,1.5610723993862283e-7,2.19321137505491e-7 +ValueContains/12/2011,2.545145959529957e-4,2.5414989211875556e-4,2.548397339152954e-4,1.1118180145894015e-6,9.172919101252035e-7,1.3906023094523358e-6 +ValueContains/13/3321,4.326743531138778e-4,4.3219164206709124e-4,4.3314184948469917e-4,1.637321748147985e-6,1.4308402728774026e-6,1.9454261689476855e-6 +ValueContains/12/1957,2.4444228524223726e-4,2.4414177372526606e-4,2.447615994648408e-4,1.037669844413743e-6,8.626781895343198e-7,1.299332016839317e-6 +ValueContains/12/144,1.8683203713856623e-5,1.8660725343598865e-5,1.8707839589944395e-5,7.657795393951314e-8,6.524837319600728e-8,9.255694497951914e-8 +ValueContains/11/47,5.943223770706193e-6,5.939942333033249e-6,5.9468407461967824e-6,1.1495571184973524e-8,9.450564677686707e-9,1.5318444359792727e-8 +ValueContains/12/1333,1.6572830370516635e-4,1.6550763129061263e-4,1.6610644552462428e-4,9.088824843141705e-7,5.400858217117058e-7,1.3835082448700263e-6 +ValueContains/13/4466,5.883552562353645e-4,5.877883356318053e-4,5.889456000900964e-4,2.0600754658523784e-6,1.837504876567189e-6,2.3998936154702603e-6 +ValueContains/12/483,6.211720183600771e-5,6.205000004948712e-5,6.222546127321215e-5,2.9302848770815617e-7,1.9395773199602564e-7,5.092671308489676e-7 +ValueContains/10/367,4.290681112071325e-5,4.283524055173336e-5,4.298151308282174e-5,2.418540264711245e-7,1.9804423368519547e-7,3.119019270822064e-7 +ValueContains/13/2280,3.001734441359379e-4,2.9964097767535305e-4,3.006303532594835e-4,1.7266774979727402e-6,1.5267491734511754e-6,2.062086789150401e-6 +ValueContains/10/836,9.757156053037398e-5,9.749455952320636e-5,9.766478670277101e-5,2.918808129765305e-7,2.411994749602096e-7,3.64682005836559e-7 +ValueContains/12/3712,4.8345409303365903e-4,4.8287458174537203e-4,4.8407638545173087e-4,2.11436941802913e-6,1.7748853284884427e-6,2.819296668716201e-6 +ValueContains/12/735,9.380987162873078e-5,9.370656738311049e-5,9.391220743009741e-5,3.291930700990749e-7,2.637603735476657e-7,4.4035632702576677e-7 +ValueContains/11/69,8.740065703800622e-6,8.73206918897248e-6,8.748144563675079e-6,2.7645984900076896e-8,2.4655318056668294e-8,3.200696702993197e-8 +ValueContains/13/2164,2.8226614728641016e-4,2.819592503007586e-4,2.825339221471438e-4,9.35048304631259e-7,7.830738177269742e-7,1.101422722293502e-6 +ValueContains/12/1681,2.0722746077054513e-4,2.067364561772548e-4,2.0783380144606467e-4,1.8476919280218599e-6,1.5917684248372793e-6,2.4035623332525304e-6 +ValueContains/12/74,9.751052467014276e-6,9.738153518141473e-6,9.769135587772237e-6,5.104564367509155e-8,4.137263888631603e-8,6.784579429681918e-8 +ValueContains/10/139,1.6490135612515683e-5,1.646480703042599e-5,1.6520899999498563e-5,9.386934931557386e-8,7.67497822489482e-8,1.1829754375337699e-7 +ValueContains/12/2017,2.666065542828511e-4,2.6634135768148617e-4,2.668356320274318e-4,8.068964397686883e-7,6.711601209431939e-7,1.0002714710368192e-6 +ValueContains/12/2345,3.065589415214533e-4,3.0600730248579386e-4,3.07235797718338e-4,2.1656848744943406e-6,1.6035862037654688e-6,3.3945380729893793e-6 +ValueContains/8/86,9.484026691964886e-6,9.4598571284918e-6,9.510257836634471e-6,8.318439396788857e-8,7.377201987458882e-8,9.645150938140082e-8 +ValueContains/13/1354,1.822301161569283e-4,1.8201339281833105e-4,1.8251883577336103e-4,8.601085159361935e-7,5.058945823465912e-7,1.4933572773367855e-6 +ValueContains/12/926,1.1739513464620693e-4,1.1728372233638402e-4,1.1750491914580553e-4,3.77534300353773e-7,3.166540812652804e-7,4.750385461143361e-7 +ValueContains/12/2090,2.59202825156191e-4,2.587524049856163e-4,2.5977063394204327e-4,1.6346722534750102e-6,1.228784598695743e-6,2.4281127075343204e-6 +ValueContains/9/32,4.2459803191325445e-6,4.242026073286432e-6,4.251233958314122e-6,1.4944535148921693e-8,1.0547364744468492e-8,2.381590299881724e-8 +ValueContains/11/127,1.4893903500281279e-5,1.4879635368636673e-5,1.4908393629647666e-5,4.9157868851736634e-8,4.05166848312878e-8,6.036358174975088e-8 +ValueContains/11/878,1.0625910363342736e-4,1.0619531477260937e-4,1.0631636611290635e-4,2.0157250984174788e-7,1.70722343760839e-7,2.388625189810645e-7 +ValueContains/12/178,2.2385596549019208e-5,2.2344359901498833e-5,2.2443371435391062e-5,1.6096578924614795e-7,1.0912652844682803e-7,2.677203076358949e-7 +ValueContains/11/18,2.840118752821919e-6,2.837080391571991e-6,2.8427475559187277e-6,9.808708515015208e-9,7.406932957825681e-9,1.2961147988223096e-8 +ValueContains/12/1823,2.2947306907293607e-4,2.2891246475553203e-4,2.3074600169947687e-4,2.7163159662133814e-6,1.3788317105269304e-6,5.278763202725306e-6 +ValueContains/13/3143,4.185460854876617e-4,4.180554359077283e-4,4.190122304553418e-4,1.6566285473210499e-6,1.274473801595235e-6,2.222609809552533e-6 +ValueContains/11/475,5.586002120314921e-5,5.57855068885348e-5,5.606353660949901e-5,3.7252999192278584e-7,1.8639352637885462e-7,7.537942536898368e-7 +ValueContains/12/899,1.0911510543915941e-4,1.0893985999913757e-4,1.0932246198183435e-4,6.461828497683495e-7,5.348516081396722e-7,7.701515408934036e-7 +ValueContains/11/496,6.038313848337131e-5,6.02934891081398e-5,6.0591102825611974e-5,4.4336132755104704e-7,2.0828679783401164e-7,8.575229338742292e-7 +ValueContains/11/361,4.261425919476745e-5,4.257334183453867e-5,4.2666218004492606e-5,1.4705722177034502e-7,1.1327731924623607e-7,2.1601785681198762e-7 +ValueContains/10/821,9.519906689615632e-5,9.50482279406412e-5,9.55544384289624e-5,7.585266683581104e-7,4.436027670088501e-7,1.4502570669156058e-6 +ValueContains/12/2360,2.9806416148304705e-4,2.976577021595465e-4,2.984329220097875e-4,1.3496905134254881e-6,1.1552122805976157e-6,1.6341921730276273e-6 +ValueContains/11/1385,1.6646542946938453e-4,1.6623537738069108e-4,1.669575587698667e-4,1.1053250292718617e-6,4.953007173179001e-7,2.134754554413376e-6 +ValueContains/11/1103,1.3070946562038287e-4,1.305995674430096e-4,1.3083698940945848e-4,3.9193902361530565e-7,3.4024189405871164e-7,4.795878958318945e-7 +ValueContains/12/698,8.937994899368279e-5,8.911848251141686e-5,9.000803198469786e-5,1.355470540757024e-6,5.400287598884221e-7,2.6474069137052814e-6 +ValueContains/11/554,6.627601682268413e-5,6.608794162470003e-5,6.651053743806329e-5,6.794380013654803e-7,5.919530415753716e-7,7.609734147094929e-7 +ValueContains/11/1462,1.7723794398198577e-4,1.7690560315032882e-4,1.780857235488939e-4,1.6320172898599461e-6,7.160673407762405e-7,3.38611869498516e-6 +ValueContains/12/3929,5.114683189390875e-4,5.108823344846136e-4,5.120638208675391e-4,1.932961928418717e-6,1.64601870345476e-6,2.2485445520791425e-6 +ValueContains/11/1501,1.8265889163916692e-4,1.824032717647174e-4,1.8319969887632852e-4,1.2075749286827018e-6,3.95646164331573e-7,1.971307347766472e-6 +ValueContains/12/2644,3.4395582842133246e-4,3.4325705139035396e-4,3.445663440351393e-4,2.2459324776977035e-6,1.9802970747187393e-6,2.6732846278087163e-6 +ValueContains/13/1710,2.2630468090120153e-4,2.2602447716197943e-4,2.266339650610043e-4,1.0092740699134108e-6,8.228956305963694e-7,1.192691783695068e-6 +ValueContains/12/2106,2.675136709449191e-4,2.6728519659863584e-4,2.678663190479629e-4,9.628740894834272e-7,7.145739340741488e-7,1.4617072197248056e-6 +ValueContains/12/1609,2.0673038091264975e-4,2.0635716210327303e-4,2.0767854207862254e-4,1.9902928646007943e-6,7.930160612545927e-7,4.187729151592018e-6 +ValueContains/11/218,2.558938785812943e-5,2.5573825772138e-5,2.560817331740303e-5,5.8839114721490037e-8,4.754059305360504e-8,7.466670389950067e-8 +ValueContains/13/2594,3.3996222275771686e-4,3.3938141060966236e-4,3.405730256196416e-4,2.0263240635596373e-6,1.849561163456103e-6,2.296176935049034e-6 +ValueContains/12/1074,1.4359801626900707e-4,1.4329196353462137e-4,1.4391744904026694e-4,1.0203786682314504e-6,8.723331275963217e-7,1.2293953659787833e-6 +ValueContains/12/2131,2.777805228279675e-4,2.773621617840402e-4,2.7818633853963153e-4,1.3442693284744144e-6,1.1440005022797041e-6,1.6111600957444925e-6 +ValueContains/13/1281,1.6251881979095228e-4,1.6240943290812208e-4,1.6264116305182474e-4,3.727089935119192e-7,3.1532670897460217e-7,4.5228713429259585e-7 +ValueContains/11/1650,2.0118004766971022e-4,2.0086339114876303e-4,2.0147528510632495e-4,1.0236706875408362e-6,9.290949238324031e-7,1.1654207959215543e-6 +ValueContains/9/31,4.2781508693801835e-6,4.269785122686407e-6,4.2862243167611635e-6,2.7783251437423314e-8,2.4200749761328568e-8,3.149628938222245e-8 +ValueContains/12/216,2.8241964850588032e-5,2.822599079371751e-5,2.826278147487947e-5,6.029384063373202e-8,4.712657894246709e-8,8.27284120655479e-8 +ValueContains/12/2165,2.736051884812679e-4,2.732775118521652e-4,2.7384602030101977e-4,9.913766064438774e-7,8.679131113234608e-7,1.1449757050205114e-6 +ValueContains/7/33,3.5450273448522575e-6,3.5426547002066714e-6,3.547478093019328e-6,8.56684391017993e-9,7.0940981903321665e-9,1.0350576327528435e-8 +ValueContains/9/390,4.341681285153536e-5,4.33652900440057e-5,4.347880175083487e-5,2.1029490564358867e-7,1.8254976974209643e-7,2.389207340295556e-7 +ValueContains/12/2883,3.6897212131933735e-4,3.6834144196343336e-4,3.695181587765242e-4,1.931807293907194e-6,1.7186713005105091e-6,2.283301180763716e-6 +ValueContains/11/706,8.395902905029007e-5,8.389215479156398e-5,8.402358160098535e-5,2.3131221739509136e-7,1.9956461239921385e-7,2.7884440531254544e-7 +ValueContains/12/1963,2.5456959977743844e-4,2.5438013013151067e-4,2.547825898452976e-4,6.669701647543044e-7,5.826304504253809e-7,7.844446853575884e-7 +ValueContains/12/1478,1.86861615625485e-4,1.8663747224495622e-4,1.871659571681982e-4,8.863695523773327e-7,7.105816352313534e-7,1.1626576023954886e-6 +ValueData/0,8.244454201615579e-7,8.23433293501754e-7,8.256213678834717e-7,3.742260219943055e-9,3.0812603017279235e-9,4.4146686349114295e-9 +ValueData/10,8.22117499973743e-7,8.211243746799455e-7,8.230308035842674e-7,3.0946590753686337e-9,2.610092909583127e-9,3.866927719317043e-9 +ValueData/100,8.221819452453929e-7,8.21048270247861e-7,8.233528399357892e-7,4.039505590682658e-9,3.5797568158276e-9,4.590950630092258e-9 +ValueData/500,8.163397290707937e-7,8.15773335425612e-7,8.169363817983215e-7,1.9366759680442005e-9,1.6074863504670616e-9,2.5286798414998783e-9 +ValueData/1000,8.202725937332094e-7,8.195662314381959e-7,8.209489335990944e-7,2.343092667215858e-9,1.866780979986148e-9,2.9344997517981207e-9 +ValueData/5000,8.161768980975118e-7,8.152867065992876e-7,8.171227681739271e-7,3.0743792985235683e-9,2.560499413734067e-9,3.905128238295594e-9 +ValueData/10000,8.186813343151185e-7,8.18190746694553e-7,8.1923209635009e-7,1.7785247185136356e-9,1.5296591921807378e-9,2.0944121326572294e-9 +ValueData/12,8.193056821477145e-7,8.184430190229789e-7,8.203090609240571e-7,3.1122913487637987e-9,2.6442795306026595e-9,3.664646733366502e-9 +ValueData/132,8.212467144493349e-7,8.199889551578968e-7,8.228647531471329e-7,4.560769672924292e-9,3.743388186459986e-9,5.544331817222215e-9 +ValueData/400,8.205709408140604e-7,8.196287165179266e-7,8.215035594245682e-7,3.2079146580475585e-9,2.8857475081103714e-9,3.7035076364625423e-9 +ValueData/2988,8.201412297157129e-7,8.194534771379229e-7,8.208311526198327e-7,2.2066286828884032e-9,1.8519239429052266e-9,2.744954445779122e-9 +ValueData/89540,8.20872414590064e-7,8.199366938198826e-7,8.219862584692773e-7,3.3544584077178134e-9,2.7271437719638854e-9,4.057235122642681e-9 +ValueData/72320,8.224876982589812e-7,8.217298357183517e-7,8.234034779155377e-7,2.814181928775027e-9,2.3008078917358744e-9,3.6703684541045173e-9 +ValueData/27300,8.185074530743931e-7,8.177207414511934e-7,8.195166970852875e-7,2.8747827840376272e-9,2.228274244115483e-9,3.767679517871087e-9 +ValueData/244570,8.20454645354226e-7,8.194943063222285e-7,8.215223282266286e-7,3.521570631049841e-9,2.8542659819307667e-9,4.4007321696312755e-9 +ValueData/44448,8.239843871228996e-7,8.229408304588001e-7,8.250463066111123e-7,3.6072233159518366e-9,3.1863501594039706e-9,4.239201330338147e-9 +ValueData/170352,8.2455779180604e-7,8.230398608899784e-7,8.263277645365452e-7,5.4439937195030216e-9,4.7440924636577775e-9,6.047871371268118e-9 +ValueData/218152,8.230271914413192e-7,8.21546465127632e-7,8.245481566758423e-7,4.872994695985695e-9,4.236411658578428e-9,5.739916731984539e-9 +ValueData/425952,8.203457569797886e-7,8.19608072590304e-7,8.212784742976612e-7,2.743008529127879e-9,2.1674535399962145e-9,3.6588883550751806e-9 +ValueData/279538,8.195474882132555e-7,8.182573637368075e-7,8.209206901647557e-7,4.7165491844897005e-9,3.994039576916133e-9,5.677341148669239e-9 +ValueData/39820,8.208435129037743e-7,8.203007288065669e-7,8.214118615989832e-7,1.8935718234671093e-9,1.5489949847948677e-9,2.3821560679490826e-9 +ValueData/83636,8.201310288599092e-7,8.191933907563492e-7,8.214508364266832e-7,3.844975905778905e-9,2.5203152536153045e-9,5.552414853322374e-9 +ValueData/299398,8.232310397117945e-7,8.224220181220569e-7,8.240706777609594e-7,2.7912162770180534e-9,2.2671647291529514e-9,3.52962515306279e-9 +ValueData/54530,8.27603661647116e-7,8.260768510784006e-7,8.289428648332192e-7,4.643217215145481e-9,3.908397149790088e-9,5.43553475182136e-9 +ValueData/18886,8.215021753586944e-7,8.207844208954321e-7,8.223623732542666e-7,2.769837818117766e-9,2.3351167741817255e-9,3.2881789082136985e-9 +ValueData/93450,8.204190446392335e-7,8.192333752020768e-7,8.215388016131464e-7,3.936176937364659e-9,3.503796320690723e-9,4.4439553879784326e-9 +ValueData/228542,8.208423266679402e-7,8.202045502020515e-7,8.215538621190297e-7,2.1588137621830542e-9,1.81563676458015e-9,2.597167509087378e-9 +ValueData/150792,8.235605511246239e-7,8.22789421905344e-7,8.244472970345505e-7,2.8627335498439904e-9,2.416784539573174e-9,3.4745986889503555e-9 +ValueData/49024,8.246790078242883e-7,8.235423991738796e-7,8.257851883468644e-7,3.7053305326945513e-9,3.1156817522826614e-9,4.495466587739984e-9 +ValueData/132328,8.270862423730109e-7,8.260851651326046e-7,8.281607063752865e-7,3.6126580953983926e-9,3.0769289521676575e-9,4.3619589383346215e-9 +ValueData/18864,8.214483124148549e-7,8.203312994013875e-7,8.225392862725836e-7,3.728587256896244e-9,3.3352565281065484e-9,4.299462069024661e-9 +ValueData/71208,8.203695247082273e-7,8.198937044013412e-7,8.210256490927769e-7,1.8923463489600707e-9,1.5012479670306166e-9,2.4545288715178135e-9 +ValueData/211508,8.266460926647436e-7,8.258964350034215e-7,8.272677997383069e-7,2.320109563559006e-9,2.0228007978372696e-9,2.7652169008190787e-9 +ValueData/56516,8.24615190392142e-7,8.238369406932445e-7,8.257196357657181e-7,3.171398965448706e-9,2.625831068963112e-9,3.9824482222818364e-9 +ValueData/48298,8.229631222484406e-7,8.217398931360068e-7,8.244732355896116e-7,4.500108807130222e-9,3.6629535584917373e-9,5.61723215800674e-9 +ValueData/13362,8.222133015780036e-7,8.21342126417965e-7,8.23148488231374e-7,2.9388660991135616e-9,2.415861094485281e-9,3.6074160877605393e-9 +ValueData/126555,8.199337600220388e-7,8.192821802956436e-7,8.206784815869801e-7,2.3218368437302743e-9,1.9517863055085853e-9,2.756340032781499e-9 +ValueData/51465,8.25975433176981e-7,8.250203522209206e-7,8.268473970007414e-7,3.0255571985196647e-9,2.4781397761879002e-9,3.6916506509221513e-9 +ValueData/231702,8.268449630882003e-7,8.261046060231018e-7,8.279694674047836e-7,3.02152797067613e-9,2.336918651658897e-9,3.86203520866395e-9 +ValueData/316,8.332810715075529e-7,8.317957238737365e-7,8.343598788636821e-7,4.23958540939879e-9,3.329696694775728e-9,5.2126610397838e-9 +ValueData/83655,8.300648237861331e-7,8.292977837361904e-7,8.30911931674328e-7,2.684590380801402e-9,2.2286786714087038e-9,3.19334125980831e-9 +ValueData/27500,8.252076029896516e-7,8.244011763404174e-7,8.258718545881323e-7,2.41302974832356e-9,1.9691337749911034e-9,2.9578090599609055e-9 +ValueData/234494,8.224910899592814e-7,8.218633796931829e-7,8.230605742960272e-7,1.993440465547803e-9,1.7361391040241124e-9,2.3066368259341814e-9 +ValueData/71959,8.293806091070653e-7,8.285684459368036e-7,8.303841255915646e-7,3.0245687195475286e-9,2.1494130161949623e-9,3.847952146552444e-9 +ValueData/2187,8.224824664247516e-7,8.218106719402002e-7,8.235446002173017e-7,2.6992902993182545e-9,2.0680735821154223e-9,4.183177881307455e-9 +ValueData/57951,8.280962854762504e-7,8.273096515559853e-7,8.292096572984379e-7,3.0648220168982696e-9,2.3634004258585118e-9,3.8444551113794714e-9 +ValueData/30744,8.326082276323256e-7,8.316342915216535e-7,8.335562323476703e-7,3.2862066836587618e-9,2.792643869494247e-9,3.994537454396677e-9 +ValueData/62122,8.233358171747173e-7,8.22710641085643e-7,8.241742614788164e-7,2.3582069481678468e-9,1.6105514488019716e-9,3.765127064703871e-9 +ValueData/9807,8.271909739306661e-7,8.26031957297151e-7,8.282322603567579e-7,3.6986066654931186e-9,3.1762089140800916e-9,4.468497957034641e-9 +ValueData/22116,8.256482182069902e-7,8.245441581830742e-7,8.269202063096741e-7,3.963698026375453e-9,3.325220536382015e-9,4.6280316916492655e-9 +ValueData/116298,8.224519503002362e-7,8.217488428876309e-7,8.231750165689685e-7,2.3146032600676372e-9,1.866144095262344e-9,3.0358759884507236e-9 +ValueData/337953,8.255115322491715e-7,8.24668725228097e-7,8.266546206408221e-7,3.260357656962594e-9,2.541021079907588e-9,4.055745705991836e-9 +ValueData/7905,8.330641809091734e-7,8.322898310300378e-7,8.338620508706807e-7,2.665723602996034e-9,2.3305267033388244e-9,3.518143536635139e-9 +ValueData/134090,8.261427399950324e-7,8.251366006904944e-7,8.272431352068293e-7,3.5507224178490417e-9,3.1785415138412026e-9,3.992986123698293e-9 +ValueData/83006,8.254214837876659e-7,8.242247408602064e-7,8.273285790340231e-7,4.887168627229412e-9,3.842603276758196e-9,6.342713996078145e-9 +ValueData/36540,8.280149814010451e-7,8.271494631448716e-7,8.288838774486129e-7,2.9044778093717868e-9,2.2815144230384666e-9,3.7251399021511512e-9 +ValueData/306125,8.306982652566297e-7,8.297981435526217e-7,8.319348409103995e-7,3.43613287520932e-9,2.8138998792480703e-9,4.191248781773384e-9 +ValueData/139125,8.207838888057991e-7,8.194250975173603e-7,8.222616783044705e-7,4.5139079966325845e-9,3.802401973556008e-9,5.290941278704563e-9 +ValueData/274164,8.231051811599564e-7,8.223282303695108e-7,8.240756915156489e-7,2.9623909454241763e-9,2.171006494735078e-9,4.017682238102333e-9 +ValueData/114454,8.246612985793178e-7,8.236875269735684e-7,8.262534582915164e-7,3.834620588845891e-9,2.6955386866157867e-9,5.704675853113967e-9 +UnValueData/4,8.814707544381939e-7,8.804725070677484e-7,8.823471365443689e-7,2.9482977593301646e-9,2.44628385001842e-9,3.929069382146581e-9 +UnValueData/146,2.5870907863963996e-6,2.5855718088559514e-6,2.5889492970240463e-6,6.128345195836809e-9,5.023713854759932e-9,7.274702316360512e-9 +UnValueData/1424,1.7206064639310656e-5,1.7191504653194482e-5,1.722024845553145e-5,4.734386123201548e-8,3.874418654003048e-8,6.145127714531319e-8 +UnValueData/7104,8.362469167695932e-5,8.357209407036697e-5,8.367602197250932e-5,1.8895665609682302e-7,1.530185031734147e-7,2.5531833574257767e-7 +UnValueData/14204,1.704310798406903e-4,1.7025902337178755e-4,1.705781111899975e-4,5.529583631219131e-7,4.660361418782681e-7,6.810892709873758e-7 +UnValueData/71004,9.58574670300882e-4,9.536919722540894e-4,9.625114724557927e-4,1.4672996528760974e-5,1.1411848643366675e-5,1.8350279003937462e-5 +UnValueData/142004,2.342476377270298e-3,2.3291587332260034e-3,2.3517155756466873e-3,3.5285917997363786e-5,2.6968686170481196e-5,4.787044439995054e-5 +UnValueData/196,2.926389063362384e-6,2.924436663100386e-6,2.9285915595789803e-6,6.92710145446734e-9,5.9905018568068284e-9,7.89335432373771e-9 +UnValueData/1852,2.255370626227775e-5,2.254000902066636e-5,2.256952939021159e-5,4.823634389334619e-8,4.105888712808848e-8,5.8757201721543305e-8 +UnValueData/5444,6.815777869204673e-5,6.812298969192928e-5,6.818444105177809e-5,1.0411354465938307e-7,8.278938422154348e-8,1.4772807649247813e-7 +UnValueData/39280,6.47318627124663e-4,6.469757140611054e-4,6.476807669879141e-4,1.2166450200006558e-6,1.0542219006306254e-6,1.4478891009580309e-6 +UnValueData/1172904,3.0913773945298866e-2,3.0393434972703103e-2,3.1183828224595547e-2,8.037785360051158e-4,3.809514367981205e-4,1.4736308924952557e-3 +UnValueData/945588,2.39508395471181e-2,2.3600728393489128e-2,2.4202383973430504e-2,6.37108862819296e-4,4.018417348134392e-4,1.0454531348408232e-3 +UnValueData/355804,8.589346906253056e-3,8.524265366301657e-3,8.632774953118594e-3,1.5263747812641247e-4,1.083570235534613e-4,2.4500294211551426e-4 +UnValueData/3187346,0.10331826001689876,0.10062176479943215,0.1063046103860769,4.623701246221441e-3,3.3147794955261417e-3,6.810944977092971e-3 +UnValueData/583384,1.2765699904511438e-2,1.2702924340086606e-2,1.2834570607761891e-2,1.655230521421776e-4,1.2914846623880968e-4,2.2826538877161433e-4 +UnValueData/2222068,6.989666920760775e-2,6.870708700254068e-2,7.155345413608082e-2,2.5402400204450606e-3,1.2999895673927813e-3,4.329297041380369e-3 +UnValueData/2844824,9.02636660804982e-2,8.772392780249001e-2,9.149031602536087e-2,2.7553926791901644e-3,9.77971278212264e-4,4.714805068545969e-3 +UnValueData/5548516,0.18253146313751736,0.17470398537504175,0.1877387719642785,8.552592291424263e-3,3.6792108869790827e-3,1.1786526999305118e-2 +UnValueData/3640886,0.12065583245975653,0.11773332931722204,0.12304799077433667,4.2884992990610766e-3,3.128731799551303e-3,5.9372428520211564e-3 +UnValueData/518984,1.2888476639080373e-2,1.2822252847393838e-2,1.2958869372761368e-2,1.8010054490204602e-4,1.3307831273761398e-4,2.529136962109431e-4 +UnValueData/1097016,2.7437004902670075e-2,2.7103162513727724e-2,2.7624881382781043e-2,5.435083322307567e-4,2.7771501704805534e-4,8.921493500185314e-4 +UnValueData/3900362,0.12702963936067785,0.12166317274040055,0.1295020544178052,5.414563993547031e-3,2.189425127296667e-3,8.656674282930344e-3 +UnValueData/711174,1.804444737709224e-2,1.7784331353898924e-2,1.81642280071127e-2,3.834768337259202e-4,2.1407666449012728e-4,6.442796445132827e-4 +UnValueData/251486,4.702617409392112e-3,4.6735559776439894e-3,4.725891504375187e-3,7.824150976483432e-5,6.13024428523557e-5,9.973583586405014e-5 +UnValueData/1219054,3.491563529296652e-2,3.424975840783657e-2,3.607312922949248e-2,1.7601257382396946e-3,8.400178103566094e-4,2.9232166641789755e-3 +UnValueData/2976546,9.781775035065102e-2,9.54381991652082e-2,9.943876222081521e-2,3.208618717052165e-3,1.9203822695934123e-3,4.803329131698663e-3 +UnValueData/1970188,5.968214018489485e-2,5.872649675449168e-2,6.093962713876137e-2,1.978623386144956e-3,1.2055103813255286e-3,3.1743286575666332e-3 +UnValueData/638852,1.6417998928983827e-2,1.6223209933320774e-2,1.6511501737594667e-2,3.239221957399417e-4,1.5686490990686526e-4,6.141584823290552e-4 +UnValueData/1731692,5.088152643125891e-2,5.0171259261978705e-2,5.1946749241449736e-2,1.688541113403487e-3,8.588593850525171e-4,2.87150119580516e-3 +UnValueData/246964,5.3374522450953e-3,5.317564818591537e-3,5.353340740640756e-3,5.633056018805761e-5,4.4452772430179823e-5,7.595476521522324e-5 +UnValueData/928804,2.4988392961184307e-2,2.462135908570554e-2,2.5925185025086464e-2,1.2115037931675636e-3,3.7166156225736254e-4,2.239260433211775e-3 +UnValueData/2759640,8.67670032566428e-2,8.438685280603489e-2,8.840050996495559e-2,3.1872167096294863e-3,1.8750568111371311e-3,5.390424663519083e-3 +UnValueData/744264,1.6457150792767963e-2,1.6184644889171276e-2,1.6583589895754078e-2,4.07752884052212e-4,2.1850985011782092e-4,6.465703636997289e-4 +UnValueData/637226,1.3667107270261053e-2,1.3545497198704624e-2,1.372844954411446e-2,2.1996111464304513e-4,1.4250632227681524e-4,3.708315464387721e-4 +UnValueData/178426,3.3127857359065934e-3,3.300976824042302e-3,3.3215405614025763e-3,3.366884248058469e-5,2.271248059427335e-5,4.8176124234948854e-5 +UnValueData/1654423,4.8417158025112865e-2,4.785748068257738e-2,4.941144782419231e-2,1.3894597794297575e-3,6.942690917814364e-4,2.409704641006147e-3 +UnValueData/670741,1.6957949146630364e-2,1.6822310381670726e-2,1.7033353225931157e-2,2.652305922367694e-4,1.6278290234390206e-4,4.364338064389038e-4 +UnValueData/3018478,9.937505917849489e-2,9.721944732989826e-2,0.10163280513955567,3.7174569863218684e-3,2.5786680729009146e-3,5.131090948343308e-3 +UnValueData/5060,5.751885233077096e-5,5.748333393852673e-5,5.7557358593790856e-5,1.2290676381525568e-7,9.725157826066853e-8,1.5289857702614492e-7 +UnValueData/1092667,2.9660856546798665e-2,2.9355879647692627e-2,3.0306183135092528e-2,9.217230672598662e-4,4.6541204946275546e-4,1.5653003850173198e-3 +UnValueData/360504,7.663426183941959e-3,7.62956825836068e-3,7.696136881811834e-3,9.630149250118415e-5,7.297761833152014e-5,1.2816562515843873e-4 +UnValueData/3057474,9.757587071261788e-2,9.486766001653103e-2,9.949748440887089e-2,3.629152805905121e-3,1.9718028530284785e-3,5.573670378283491e-3 +UnValueData/938195,2.5516736772938316e-2,2.529523548437108e-2,2.577993551022413e-2,5.507883169090115e-4,3.861088032048023e-4,7.754657796028178e-4 +UnValueData/31351,3.794440277720582e-4,3.792986902989907e-4,3.7964085274660336e-4,5.636735065125375e-7,4.4833077870519565e-7,8.228939567060915e-7 +UnValueData/758443,1.8391077717100763e-2,1.810849422684369e-2,1.8913655447828085e-2,8.794417728764309e-4,4.5352513329323895e-4,1.4082372728346153e-3 +UnValueData/402700,8.883993653910516e-3,8.856349934916352e-3,8.915581600179811e-3,8.803255766046738e-5,6.184630473679648e-5,1.2884264703395465e-4 +UnValueData/815966,1.9293342965148588e-2,1.9042203329400716e-2,1.9793484281817646e-2,7.92549742002015e-4,3.7918566505787664e-4,1.3736516216592172e-3 +UnValueData/127747,3.1306911500748776e-3,3.1220245193965502e-3,3.1369653229303073e-3,2.466245089189588e-5,1.8400103480861507e-5,3.470525525801844e-5 +UnValueData/288676,6.645767467209073e-3,6.6207958661609724e-3,6.6699330461812475e-3,7.106967999341454e-5,5.009579306966509e-5,1.1574905918210243e-4 +UnValueData/1519546,4.4455198764938864e-2,4.3881514973162936e-2,4.5144713611423894e-2,1.2651091613634833e-3,7.713333009244095e-4,2.033757739072662e-3 +UnValueData/4404565,0.1424591612469937,0.1381316568170275,0.14481412209126923,4.674712272678646e-3,2.4120624506187415e-3,6.85872679509471e-3 +UnValueData/108349,1.7981659186657182e-3,1.794709118269817e-3,1.802130635380069e-3,1.2513170505276615e-5,9.021600874330734e-6,2.0156426360822056e-5 +UnValueData/1749534,5.321115732037697e-2,5.2342570794778116e-2,5.387104092141948e-2,1.4791590671407657e-3,9.110922030450458e-4,2.4373989399546774e-3 +UnValueData/1085550,2.837395804942373e-2,2.8186313041170894e-2,2.8571790223544384e-2,4.22142981227161e-4,3.127639213843074e-4,5.959412566434413e-4 +UnValueData/477544,1.096403937194356e-2,1.0872864607374598e-2,1.1015912021362047e-2,1.796792621482667e-4,1.1109966782409862e-4,2.9949710066597357e-4 +UnValueData/3988929,0.13036026550814442,0.12702548788372606,0.13358291170637435,5.277650991401465e-3,3.6155023029658534e-3,8.317242999952778e-3 +UnValueData/1813129,5.668536234038809e-2,5.589823921392154e-2,5.7248521915470314e-2,1.2032278475752258e-3,6.468777111526906e-4,1.9686013537490604e-3 +UnValueData/3572980,0.1156469710891889,0.11202591267259171,0.11812273848945984,4.976948988572253e-3,2.5708389602726515e-3,7.849883215477199e-3 +UnValueData/1495622,4.294574041476179e-2,4.2345256325965905e-2,4.34389490400093e-2,1.121339863668914e-3,7.021794540026286e-4,1.7051035518656247e-3 From e8a9f5373d19b73e77a6193757771bf85f4fab85 Mon Sep 17 00:00:00 2001 From: Yura Lazaryev Date: Thu, 9 Oct 2025 11:22:33 +0200 Subject: [PATCH 10/17] refactor: refine cost model parameters for Value builtins MIME-Version: 1.0 Content-Type: text/plain; charset=UTF-8 Content-Transfer-Encoding: 8bit Updated cost parameters based on fresh benchmark data analysis: - lookupCoin: Adjusted intercept (284421→179661) and slope (1→7151) to better reflect actual performance with varying currency counts - valueContains: Changed from added_sizes to linear_in_y model with refined parameters (intercept 42125119→1000, slope 30→130383) - valueData: Reduced constant cost (205465→153844) based on updated profiling results - unValueData: Switched to linear_in_x model with refined parameters (intercept 10532326261→1000, slope 431→33094) All three cost model variants (A, B, C) updated for consistency. --- .../cost-model/data/builtinCostModelA.json | 16 +- .../cost-model/data/builtinCostModelB.json | 2510 ++++++++-------- .../cost-model/data/builtinCostModelC.json | 2546 ++++++++--------- 3 files changed, 2536 insertions(+), 2536 deletions(-) diff --git a/plutus-core/cost-model/data/builtinCostModelA.json b/plutus-core/cost-model/data/builtinCostModelA.json index c49ff540ad2..71443fee763 100644 --- a/plutus-core/cost-model/data/builtinCostModelA.json +++ b/plutus-core/cost-model/data/builtinCostModelA.json @@ -1209,8 +1209,8 @@ "lookupCoin": { "cpu": { "arguments": { - "intercept": 284421, - "slope": 1 + "intercept": 179661, + "slope": 7151 }, "type": "linear_in_z" }, @@ -1222,10 +1222,10 @@ "valueContains": { "cpu": { "arguments": { - "intercept": 42125119, - "slope": 30 + "intercept": 1000, + "slope": 130383 }, - "type": "added_sizes" + "type": "linear_in_y" }, "memory": { "arguments": 1, @@ -1234,7 +1234,7 @@ }, "valueData": { "cpu": { - "arguments": 205465, + "arguments": 153844, "type": "constant_cost" }, "memory": { @@ -1245,8 +1245,8 @@ "unValueData": { "cpu": { "arguments": { - "intercept": 10532326261, - "slope": 431 + "intercept": 1000, + "slope": 33094 }, "type": "linear_in_x" }, diff --git a/plutus-core/cost-model/data/builtinCostModelB.json b/plutus-core/cost-model/data/builtinCostModelB.json index 8cb65a566d7..76d7e47535c 100644 --- a/plutus-core/cost-model/data/builtinCostModelB.json +++ b/plutus-core/cost-model/data/builtinCostModelB.json @@ -1,1258 +1,1258 @@ { - "addInteger": { - "cpu": { - "arguments": { - "intercept": 100788, - "slope": 420 - }, - "type": "max_size" - }, - "memory": { - "arguments": { - "intercept": 1, - "slope": 1 - }, - "type": "max_size" - } - }, - "appendByteString": { - "cpu": { - "arguments": { - "intercept": 1000, - "slope": 173 - }, - "type": "added_sizes" - }, - "memory": { - "arguments": { - "intercept": 0, - "slope": 1 - }, - "type": "added_sizes" - } - }, - "appendString": { - "cpu": { - "arguments": { - "intercept": 1000, - "slope": 59957 - }, - "type": "added_sizes" - }, - "memory": { - "arguments": { - "intercept": 4, - "slope": 1 - }, - "type": "added_sizes" - } - }, - "bData": { - "cpu": { - "arguments": 11183, - "type": "constant_cost" - }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } - }, - "blake2b_224": { - "cpu": { - "arguments": { - "intercept": 207616, - "slope": 8310 - }, - "type": "linear_in_x" - }, - "memory": { - "arguments": 4, - "type": "constant_cost" - } - }, - "blake2b_256": { - "cpu": { - "arguments": { - "intercept": 201305, - "slope": 8356 - }, - "type": "linear_in_x" - }, - "memory": { - "arguments": 4, - "type": "constant_cost" - } - }, - "bls12_381_G1_add": { - "cpu": { - "arguments": 962335, - "type": "constant_cost" - }, - "memory": { - "arguments": 18, - "type": "constant_cost" - } - }, - "bls12_381_G1_compress": { - "cpu": { - "arguments": 2780678, - "type": "constant_cost" - }, - "memory": { - "arguments": 6, - "type": "constant_cost" - } - }, - "bls12_381_G1_equal": { - "cpu": { - "arguments": 442008, - "type": "constant_cost" - }, - "memory": { - "arguments": 1, - "type": "constant_cost" - } - }, - "bls12_381_G1_hashToGroup": { - "cpu": { - "arguments": { - "intercept": 52538055, - "slope": 3756 - }, - "type": "linear_in_x" - }, - "memory": { - "arguments": 18, - "type": "constant_cost" - } - }, - "bls12_381_G1_neg": { - "cpu": { - "arguments": 267929, - "type": "constant_cost" - }, - "memory": { - "arguments": 18, - "type": "constant_cost" - } - }, - "bls12_381_G1_scalarMul": { - "cpu": { - "arguments": { - "intercept": 76433006, - "slope": 8868 - }, - "type": "linear_in_x" - }, - "memory": { - "arguments": 18, - "type": "constant_cost" - } - }, - "bls12_381_G1_multiScalarMul": { - "cpu": { - "arguments": { - "intercept": 321837444, - "slope": 25087669 - }, - "type": "linear_in_x" - }, - "memory": { - "arguments": 18, - "type": "constant_cost" - } - }, - "bls12_381_G1_uncompress": { - "cpu": { - "arguments": 52948122, - "type": "constant_cost" - }, - "memory": { - "arguments": 18, - "type": "constant_cost" - } - }, - "bls12_381_G2_add": { - "cpu": { - "arguments": 1995836, - "type": "constant_cost" - }, - "memory": { - "arguments": 36, - "type": "constant_cost" - } - }, - "bls12_381_G2_compress": { - "cpu": { - "arguments": 3227919, - "type": "constant_cost" - }, - "memory": { - "arguments": 12, - "type": "constant_cost" - } - }, - "bls12_381_G2_equal": { - "cpu": { - "arguments": 901022, - "type": "constant_cost" - }, - "memory": { - "arguments": 1, - "type": "constant_cost" - } - }, - "bls12_381_G2_hashToGroup": { - "cpu": { - "arguments": { - "intercept": 166917843, - "slope": 4307 - }, - "type": "linear_in_x" - }, - "memory": { - "arguments": 36, - "type": "constant_cost" - } - }, - "bls12_381_G2_neg": { - "cpu": { - "arguments": 284546, - "type": "constant_cost" - }, - "memory": { - "arguments": 36, - "type": "constant_cost" - } - }, - "bls12_381_G2_scalarMul": { - "cpu": { - "arguments": { - "intercept": 158221314, - "slope": 26549 - }, - "type": "linear_in_x" - }, - "memory": { - "arguments": 36, - "type": "constant_cost" - } - }, - "bls12_381_G2_multiScalarMul": { - "cpu": { - "arguments": { - "intercept": 617887431, - "slope": 67302824 - }, - "type": "linear_in_x" - }, - "memory": { - "arguments": 36, - "type": "constant_cost" - } - }, - "bls12_381_G2_uncompress": { - "cpu": { - "arguments": 74698472, - "type": "constant_cost" - }, - "memory": { - "arguments": 36, - "type": "constant_cost" - } - }, - "bls12_381_finalVerify": { - "cpu": { - "arguments": 333849714, - "type": "constant_cost" - }, - "memory": { - "arguments": 1, - "type": "constant_cost" - } - }, - "bls12_381_millerLoop": { - "cpu": { - "arguments": 254006273, - "type": "constant_cost" - }, - "memory": { - "arguments": 72, - "type": "constant_cost" - } - }, - "bls12_381_mulMlResult": { - "cpu": { - "arguments": 2174038, - "type": "constant_cost" - }, - "memory": { - "arguments": 72, - "type": "constant_cost" - } - }, - "byteStringToInteger": { - "cpu": { - "arguments": { - "c0": 1006041, - "c1": 43623, - "c2": 251 - }, - "type": "quadratic_in_y" - }, - "memory": { - "arguments": { - "intercept": 0, - "slope": 1 - }, - "type": "linear_in_y" - } - }, - "chooseData": { - "cpu": { - "arguments": 94375, - "type": "constant_cost" - }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } - }, - "chooseList": { - "cpu": { - "arguments": 132994, - "type": "constant_cost" - }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } - }, - "chooseUnit": { - "cpu": { - "arguments": 61462, - "type": "constant_cost" - }, - "memory": { - "arguments": 4, - "type": "constant_cost" - } - }, - "consByteString": { - "cpu": { - "arguments": { - "intercept": 72010, - "slope": 178 - }, - "type": "linear_in_y" - }, - "memory": { - "arguments": { - "intercept": 0, - "slope": 1 - }, - "type": "added_sizes" - } - }, - "constrData": { - "cpu": { - "arguments": 22151, - "type": "constant_cost" - }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } - }, - "decodeUtf8": { - "cpu": { - "arguments": { - "intercept": 91189, - "slope": 769 - }, - "type": "linear_in_x" - }, - "memory": { - "arguments": { - "intercept": 4, - "slope": 2 - }, - "type": "linear_in_x" - } - }, - "divideInteger": { - "cpu": { - "arguments": { - "constant": 85848, - "model": { - "arguments": { - "intercept": 228465, - "slope": 122 - }, - "type": "multiplied_sizes" - } - }, - "type": "const_above_diagonal" - }, - "memory": { - "arguments": { - "intercept": 0, - "minimum": 1, - "slope": 1 - }, - "type": "subtracted_sizes" - } - }, - "encodeUtf8": { - "cpu": { - "arguments": { - "intercept": 1000, - "slope": 42921 - }, - "type": "linear_in_x" - }, - "memory": { - "arguments": { - "intercept": 4, - "slope": 2 - }, - "type": "linear_in_x" - } - }, - "equalsByteString": { - "cpu": { - "arguments": { - "constant": 24548, - "intercept": 29498, - "slope": 38 - }, - "type": "linear_on_diagonal" - }, - "memory": { - "arguments": 1, - "type": "constant_cost" - } - }, - "equalsData": { - "cpu": { - "arguments": { - "intercept": 898148, - "slope": 27279 - }, - "type": "min_size" - }, - "memory": { - "arguments": 1, - "type": "constant_cost" - } - }, - "equalsInteger": { - "cpu": { - "arguments": { - "intercept": 51775, - "slope": 558 - }, - "type": "min_size" - }, - "memory": { - "arguments": 1, - "type": "constant_cost" - } - }, - "equalsString": { - "cpu": { - "arguments": { - "constant": 39184, - "intercept": 1000, - "slope": 60594 - }, - "type": "linear_on_diagonal" - }, - "memory": { - "arguments": 1, - "type": "constant_cost" - } - }, - "fstPair": { - "cpu": { - "arguments": 141895, - "type": "constant_cost" - }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } - }, - "headList": { - "cpu": { - "arguments": 83150, - "type": "constant_cost" - }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } - }, - "iData": { - "cpu": { - "arguments": 15299, - "type": "constant_cost" - }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } - }, - "ifThenElse": { - "cpu": { - "arguments": 76049, - "type": "constant_cost" - }, - "memory": { - "arguments": 1, - "type": "constant_cost" - } - }, - "indexByteString": { - "cpu": { - "arguments": 13169, - "type": "constant_cost" - }, - "memory": { - "arguments": 4, - "type": "constant_cost" - } - }, - "integerToByteString": { - "cpu": { - "arguments": { - "c0": 1293828, - "c1": 28716, - "c2": 63 - }, - "type": "quadratic_in_z" - }, - "memory": { - "arguments": { - "intercept": 0, - "slope": 1 - }, - "type": "literal_in_y_or_linear_in_z" - } - }, - "keccak_256": { - "cpu": { - "arguments": { - "intercept": 2261318, - "slope": 64571 - }, - "type": "linear_in_x" - }, - "memory": { - "arguments": 4, - "type": "constant_cost" - } - }, - "lengthOfByteString": { - "cpu": { - "arguments": 22100, - "type": "constant_cost" - }, - "memory": { - "arguments": 10, - "type": "constant_cost" - } - }, - "lessThanByteString": { - "cpu": { - "arguments": { - "intercept": 28999, - "slope": 74 - }, - "type": "min_size" - }, - "memory": { - "arguments": 1, - "type": "constant_cost" - } - }, - "lessThanEqualsByteString": { - "cpu": { - "arguments": { - "intercept": 28999, - "slope": 74 - }, - "type": "min_size" - }, - "memory": { - "arguments": 1, - "type": "constant_cost" - } - }, - "lessThanEqualsInteger": { - "cpu": { - "arguments": { - "intercept": 43285, - "slope": 552 - }, - "type": "min_size" - }, - "memory": { - "arguments": 1, - "type": "constant_cost" - } - }, - "lessThanInteger": { - "cpu": { - "arguments": { - "intercept": 44749, - "slope": 541 - }, - "type": "min_size" - }, - "memory": { - "arguments": 1, - "type": "constant_cost" - } - }, - "listData": { - "cpu": { - "arguments": 33852, - "type": "constant_cost" - }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } - }, - "mapData": { - "cpu": { - "arguments": 68246, - "type": "constant_cost" - }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } - }, - "mkCons": { - "cpu": { - "arguments": 72362, - "type": "constant_cost" - }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } - }, - "mkNilData": { - "cpu": { - "arguments": 7243, - "type": "constant_cost" - }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } - }, - "mkNilPairData": { - "cpu": { - "arguments": 7391, - "type": "constant_cost" - }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } - }, - "mkPairData": { - "cpu": { - "arguments": 11546, - "type": "constant_cost" - }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } - }, - "modInteger": { - "cpu": { - "arguments": { - "constant": 85848, - "model": { - "arguments": { - "intercept": 228465, - "slope": 122 - }, - "type": "multiplied_sizes" - } - }, - "type": "const_above_diagonal" - }, - "memory": { - "arguments": { - "intercept": 0, - "minimum": 1, - "slope": 1 - }, - "type": "subtracted_sizes" - } - }, - "multiplyInteger": { - "cpu": { - "arguments": { - "intercept": 90434, - "slope": 519 - }, - "type": "multiplied_sizes" - }, - "memory": { - "arguments": { - "intercept": 0, - "slope": 1 - }, - "type": "added_sizes" - } - }, - "nullList": { - "cpu": { - "arguments": 74433, - "type": "constant_cost" - }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } - }, - "indexArray": { - "cpu": { - "arguments": 194922, - "type": "constant_cost" - }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } - }, - "lengthOfArray": { - "cpu": { - "arguments": 198994, - "type": "constant_cost" - }, - "memory": { - "arguments": 10, - "type": "constant_cost" - } - }, - "listToArray": { - "cpu": { - "arguments": { - "intercept": 307802, - "slope": 8496 - }, - "type": "linear_in_x" - }, - "memory": { - "arguments": { - "intercept": 7, - "slope": 1 - }, - "type": "linear_in_x" - } - }, - "quotientInteger": { - "cpu": { - "arguments": { - "constant": 85848, - "model": { - "arguments": { - "intercept": 228465, - "slope": 122 - }, - "type": "multiplied_sizes" - } - }, - "type": "const_above_diagonal" - }, - "memory": { - "arguments": { - "intercept": 0, - "minimum": 1, - "slope": 1 - }, - "type": "subtracted_sizes" - } - }, - "remainderInteger": { - "cpu": { - "arguments": { - "constant": 85848, - "model": { - "arguments": { - "intercept": 228465, - "slope": 122 - }, - "type": "multiplied_sizes" - } - }, - "type": "const_above_diagonal" - }, - "memory": { - "arguments": { - "intercept": 0, - "minimum": 1, - "slope": 1 - }, - "type": "subtracted_sizes" - } - }, - "serialiseData": { - "cpu": { - "arguments": { - "intercept": 955506, - "slope": 213312 - }, - "type": "linear_in_x" - }, - "memory": { - "arguments": { - "intercept": 0, - "slope": 2 - }, - "type": "linear_in_x" - } - }, - "sha2_256": { - "cpu": { - "arguments": { - "intercept": 270652, - "slope": 22588 - }, - "type": "linear_in_x" - }, - "memory": { - "arguments": 4, - "type": "constant_cost" - } - }, - "sha3_256": { - "cpu": { - "arguments": { - "intercept": 1457325, - "slope": 64566 - }, - "type": "linear_in_x" - }, - "memory": { - "arguments": 4, - "type": "constant_cost" - } - }, - "sliceByteString": { - "cpu": { - "arguments": { - "intercept": 20467, - "slope": 1 - }, - "type": "linear_in_z" - }, - "memory": { - "arguments": { - "intercept": 4, - "slope": 0 - }, - "type": "linear_in_z" - } - }, - "sndPair": { - "cpu": { - "arguments": 141992, - "type": "constant_cost" - }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } - }, - "subtractInteger": { - "cpu": { - "arguments": { - "intercept": 100788, - "slope": 420 - }, - "type": "max_size" - }, - "memory": { - "arguments": { - "intercept": 1, - "slope": 1 - }, - "type": "max_size" - } - }, - "tailList": { - "cpu": { - "arguments": 81663, - "type": "constant_cost" - }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } - }, - "trace": { - "cpu": { - "arguments": 59498, - "type": "constant_cost" - }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } - }, - "unBData": { - "cpu": { - "arguments": 20142, - "type": "constant_cost" - }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } - }, - "unConstrData": { - "cpu": { - "arguments": 24588, - "type": "constant_cost" - }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } - }, - "unIData": { - "cpu": { - "arguments": 20744, - "type": "constant_cost" - }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } - }, - "unListData": { - "cpu": { - "arguments": 25933, - "type": "constant_cost" - }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } - }, - "unMapData": { - "cpu": { - "arguments": 24623, - "type": "constant_cost" - }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } - }, - "verifyEcdsaSecp256k1Signature": { - "cpu": { - "arguments": 43053543, - "type": "constant_cost" - }, - "memory": { - "arguments": 10, - "type": "constant_cost" - } - }, - "verifyEd25519Signature": { - "cpu": { - "arguments": { - "intercept": 53384111, - "slope": 14333 - }, - "type": "linear_in_y" - }, - "memory": { - "arguments": 10, - "type": "constant_cost" - } - }, - "verifySchnorrSecp256k1Signature": { - "cpu": { - "arguments": { - "intercept": 43574283, - "slope": 26308 - }, - "type": "linear_in_y" - }, - "memory": { - "arguments": 10, - "type": "constant_cost" - } - }, - "andByteString": { - "cpu": { - "arguments": { - "intercept": 100181, - "slope1": 726, - "slope2": 719 - }, - "type": "linear_in_y_and_z" - }, - "memory": { - "arguments": { - "intercept": 0, - "slope": 1 - }, - "type": "linear_in_max_yz" - } - }, - "orByteString": { - "cpu": { - "arguments": { - "intercept": 100181, - "slope1": 726, - "slope2": 719 - }, - "type": "linear_in_y_and_z" - }, - "memory": { - "arguments": { - "intercept": 0, - "slope": 1 - }, - "type": "linear_in_max_yz" - } - }, - "xorByteString": { - "cpu": { - "arguments": { - "intercept": 100181, - "slope1": 726, - "slope2": 719 - }, - "type": "linear_in_y_and_z" - }, - "memory": { - "arguments": { - "intercept": 0, - "slope": 1 - }, - "type": "linear_in_max_yz" - } - }, - "complementByteString": { - "cpu": { - "arguments": { - "intercept": 107878, - "slope": 680 - }, - "type": "linear_in_x" - }, - "memory": { - "arguments": { - "intercept": 0, - "slope": 1 - }, - "type": "linear_in_x" - } - }, - "readBit": { - "cpu": { - "arguments": 95336, - "type": "constant_cost" - }, - "memory": { - "arguments": 1, - "type": "constant_cost" - } - }, - "writeBits": { - "cpu": { - "arguments": { - "intercept": 281145, - "slope": 18848 - }, - "type": "linear_in_y" - }, - "memory": { - "arguments": { - "intercept": 0, - "slope": 1 - }, - "type": "linear_in_x" - } - }, - "replicateByte": { - "cpu": { - "arguments": { - "intercept": 180194, - "slope": 159 - }, - "type": "linear_in_x" - }, - "memory": { - "arguments": { - "intercept": 1, - "slope": 1 - }, - "type": "linear_in_x" - } - }, - "shiftByteString": { - "cpu": { - "arguments": { - "intercept": 158519, - "slope": 8942 - }, - "type": "linear_in_x" - }, - "memory": { - "arguments": { - "intercept": 0, - "slope": 1 - }, - "type": "linear_in_x" - } - }, - "rotateByteString": { - "cpu": { - "arguments": { - "intercept": 159378, - "slope": 8813 - }, - "type": "linear_in_x" - }, - "memory": { - "arguments": { - "intercept": 0, - "slope": 1 - }, - "type": "linear_in_x" - } - }, - "countSetBits": { - "cpu": { - "arguments": { - "intercept": 107490, - "slope": 3298 - }, - "type": "linear_in_x" - }, - "memory": { - "arguments": 1, - "type": "constant_cost" - } - }, - "findFirstSetBit": { - "cpu": { - "arguments": { - "intercept": 106057, - "slope": 655 - }, - "type": "linear_in_x" - }, - "memory": { - "arguments": 1, - "type": "constant_cost" - } - }, - "ripemd_160": { - "cpu": { - "arguments": { - "intercept": 1964219, - "slope": 24520 - }, - "type": "linear_in_x" - }, - "memory": { - "arguments": 3, - "type": "constant_cost" - } - }, - "expModInteger": { - "cpu": { - "arguments": { - "coefficient00": 607153, - "coefficient11": 231697, - "coefficient12": 53144 - }, - "type": "exp_mod_cost" - }, - "memory": { - "arguments": { - "intercept": 0, - "slope": 1 - }, - "type": "linear_in_z" - } - }, - "dropList": { - "cpu": { - "arguments": { - "intercept": 116711, - "slope": 1957 - }, - "type": "linear_in_x" - }, - "memory": { - "arguments": 4, - "type": "constant_cost" - } - }, - "lookupCoin": { - "cpu": { - "arguments": { - "intercept": 284421, - "slope": 1 - }, - "type": "linear_in_z" - }, - "memory": { - "arguments": 1, - "type": "constant_cost" - } - }, - "valueContains": { - "cpu": { - "arguments": { - "intercept": 42125119, - "slope": 30 - }, - "type": "added_sizes" - }, - "memory": { - "arguments": 1, - "type": "constant_cost" - } - }, - "valueData": { - "cpu": { - "arguments": 205465, - "type": "constant_cost" - }, - "memory": { - "arguments": 1, - "type": "constant_cost" - } - }, - "unValueData": { - "cpu": { - "arguments": { - "intercept": 10532326261, - "slope": 431 - }, - "type": "linear_in_x" - }, - "memory": { - "arguments": 1, - "type": "constant_cost" - } + "addInteger": { + "cpu": { + "arguments": { + "intercept": 100788, + "slope": 420 + }, + "type": "max_size" + }, + "memory": { + "arguments": { + "intercept": 1, + "slope": 1 + }, + "type": "max_size" + } + }, + "appendByteString": { + "cpu": { + "arguments": { + "intercept": 1000, + "slope": 173 + }, + "type": "added_sizes" + }, + "memory": { + "arguments": { + "intercept": 0, + "slope": 1 + }, + "type": "added_sizes" + } + }, + "appendString": { + "cpu": { + "arguments": { + "intercept": 1000, + "slope": 59957 + }, + "type": "added_sizes" + }, + "memory": { + "arguments": { + "intercept": 4, + "slope": 1 + }, + "type": "added_sizes" + } + }, + "bData": { + "cpu": { + "arguments": 11183, + "type": "constant_cost" + }, + "memory": { + "arguments": 32, + "type": "constant_cost" + } + }, + "blake2b_224": { + "cpu": { + "arguments": { + "intercept": 207616, + "slope": 8310 + }, + "type": "linear_in_x" + }, + "memory": { + "arguments": 4, + "type": "constant_cost" + } + }, + "blake2b_256": { + "cpu": { + "arguments": { + "intercept": 201305, + "slope": 8356 + }, + "type": "linear_in_x" + }, + "memory": { + "arguments": 4, + "type": "constant_cost" + } + }, + "bls12_381_G1_add": { + "cpu": { + "arguments": 962335, + "type": "constant_cost" + }, + "memory": { + "arguments": 18, + "type": "constant_cost" + } + }, + "bls12_381_G1_compress": { + "cpu": { + "arguments": 2780678, + "type": "constant_cost" + }, + "memory": { + "arguments": 6, + "type": "constant_cost" + } + }, + "bls12_381_G1_equal": { + "cpu": { + "arguments": 442008, + "type": "constant_cost" + }, + "memory": { + "arguments": 1, + "type": "constant_cost" + } + }, + "bls12_381_G1_hashToGroup": { + "cpu": { + "arguments": { + "intercept": 52538055, + "slope": 3756 + }, + "type": "linear_in_x" + }, + "memory": { + "arguments": 18, + "type": "constant_cost" + } + }, + "bls12_381_G1_neg": { + "cpu": { + "arguments": 267929, + "type": "constant_cost" + }, + "memory": { + "arguments": 18, + "type": "constant_cost" + } + }, + "bls12_381_G1_scalarMul": { + "cpu": { + "arguments": { + "intercept": 76433006, + "slope": 8868 + }, + "type": "linear_in_x" + }, + "memory": { + "arguments": 18, + "type": "constant_cost" + } + }, + "bls12_381_G1_multiScalarMul": { + "cpu": { + "arguments": { + "intercept": 321837444, + "slope": 25087669 + }, + "type": "linear_in_x" + }, + "memory": { + "arguments": 18, + "type": "constant_cost" + } + }, + "bls12_381_G1_uncompress": { + "cpu": { + "arguments": 52948122, + "type": "constant_cost" + }, + "memory": { + "arguments": 18, + "type": "constant_cost" + } + }, + "bls12_381_G2_add": { + "cpu": { + "arguments": 1995836, + "type": "constant_cost" + }, + "memory": { + "arguments": 36, + "type": "constant_cost" + } + }, + "bls12_381_G2_compress": { + "cpu": { + "arguments": 3227919, + "type": "constant_cost" + }, + "memory": { + "arguments": 12, + "type": "constant_cost" + } + }, + "bls12_381_G2_equal": { + "cpu": { + "arguments": 901022, + "type": "constant_cost" + }, + "memory": { + "arguments": 1, + "type": "constant_cost" + } + }, + "bls12_381_G2_hashToGroup": { + "cpu": { + "arguments": { + "intercept": 166917843, + "slope": 4307 + }, + "type": "linear_in_x" + }, + "memory": { + "arguments": 36, + "type": "constant_cost" + } + }, + "bls12_381_G2_neg": { + "cpu": { + "arguments": 284546, + "type": "constant_cost" + }, + "memory": { + "arguments": 36, + "type": "constant_cost" + } + }, + "bls12_381_G2_scalarMul": { + "cpu": { + "arguments": { + "intercept": 158221314, + "slope": 26549 + }, + "type": "linear_in_x" + }, + "memory": { + "arguments": 36, + "type": "constant_cost" + } + }, + "bls12_381_G2_multiScalarMul": { + "cpu": { + "arguments": { + "intercept": 617887431, + "slope": 67302824 + }, + "type": "linear_in_x" + }, + "memory": { + "arguments": 36, + "type": "constant_cost" + } + }, + "bls12_381_G2_uncompress": { + "cpu": { + "arguments": 74698472, + "type": "constant_cost" + }, + "memory": { + "arguments": 36, + "type": "constant_cost" + } + }, + "bls12_381_finalVerify": { + "cpu": { + "arguments": 333849714, + "type": "constant_cost" + }, + "memory": { + "arguments": 1, + "type": "constant_cost" + } + }, + "bls12_381_millerLoop": { + "cpu": { + "arguments": 254006273, + "type": "constant_cost" + }, + "memory": { + "arguments": 72, + "type": "constant_cost" + } + }, + "bls12_381_mulMlResult": { + "cpu": { + "arguments": 2174038, + "type": "constant_cost" + }, + "memory": { + "arguments": 72, + "type": "constant_cost" + } + }, + "byteStringToInteger": { + "cpu": { + "arguments": { + "c0": 1006041, + "c1": 43623, + "c2": 251 + }, + "type": "quadratic_in_y" + }, + "memory": { + "arguments": { + "intercept": 0, + "slope": 1 + }, + "type": "linear_in_y" + } + }, + "chooseData": { + "cpu": { + "arguments": 94375, + "type": "constant_cost" + }, + "memory": { + "arguments": 32, + "type": "constant_cost" + } + }, + "chooseList": { + "cpu": { + "arguments": 132994, + "type": "constant_cost" + }, + "memory": { + "arguments": 32, + "type": "constant_cost" + } + }, + "chooseUnit": { + "cpu": { + "arguments": 61462, + "type": "constant_cost" + }, + "memory": { + "arguments": 4, + "type": "constant_cost" + } + }, + "consByteString": { + "cpu": { + "arguments": { + "intercept": 72010, + "slope": 178 + }, + "type": "linear_in_y" + }, + "memory": { + "arguments": { + "intercept": 0, + "slope": 1 + }, + "type": "added_sizes" + } + }, + "constrData": { + "cpu": { + "arguments": 22151, + "type": "constant_cost" + }, + "memory": { + "arguments": 32, + "type": "constant_cost" + } + }, + "decodeUtf8": { + "cpu": { + "arguments": { + "intercept": 91189, + "slope": 769 + }, + "type": "linear_in_x" + }, + "memory": { + "arguments": { + "intercept": 4, + "slope": 2 + }, + "type": "linear_in_x" + } + }, + "divideInteger": { + "cpu": { + "arguments": { + "constant": 85848, + "model": { + "arguments": { + "intercept": 228465, + "slope": 122 + }, + "type": "multiplied_sizes" + } + }, + "type": "const_above_diagonal" + }, + "memory": { + "arguments": { + "intercept": 0, + "minimum": 1, + "slope": 1 + }, + "type": "subtracted_sizes" + } + }, + "encodeUtf8": { + "cpu": { + "arguments": { + "intercept": 1000, + "slope": 42921 + }, + "type": "linear_in_x" + }, + "memory": { + "arguments": { + "intercept": 4, + "slope": 2 + }, + "type": "linear_in_x" + } + }, + "equalsByteString": { + "cpu": { + "arguments": { + "constant": 24548, + "intercept": 29498, + "slope": 38 + }, + "type": "linear_on_diagonal" + }, + "memory": { + "arguments": 1, + "type": "constant_cost" + } + }, + "equalsData": { + "cpu": { + "arguments": { + "intercept": 898148, + "slope": 27279 + }, + "type": "min_size" + }, + "memory": { + "arguments": 1, + "type": "constant_cost" + } + }, + "equalsInteger": { + "cpu": { + "arguments": { + "intercept": 51775, + "slope": 558 + }, + "type": "min_size" + }, + "memory": { + "arguments": 1, + "type": "constant_cost" + } + }, + "equalsString": { + "cpu": { + "arguments": { + "constant": 39184, + "intercept": 1000, + "slope": 60594 + }, + "type": "linear_on_diagonal" + }, + "memory": { + "arguments": 1, + "type": "constant_cost" + } + }, + "fstPair": { + "cpu": { + "arguments": 141895, + "type": "constant_cost" + }, + "memory": { + "arguments": 32, + "type": "constant_cost" + } + }, + "headList": { + "cpu": { + "arguments": 83150, + "type": "constant_cost" + }, + "memory": { + "arguments": 32, + "type": "constant_cost" + } + }, + "iData": { + "cpu": { + "arguments": 15299, + "type": "constant_cost" + }, + "memory": { + "arguments": 32, + "type": "constant_cost" + } + }, + "ifThenElse": { + "cpu": { + "arguments": 76049, + "type": "constant_cost" + }, + "memory": { + "arguments": 1, + "type": "constant_cost" + } + }, + "indexByteString": { + "cpu": { + "arguments": 13169, + "type": "constant_cost" + }, + "memory": { + "arguments": 4, + "type": "constant_cost" + } + }, + "integerToByteString": { + "cpu": { + "arguments": { + "c0": 1293828, + "c1": 28716, + "c2": 63 + }, + "type": "quadratic_in_z" + }, + "memory": { + "arguments": { + "intercept": 0, + "slope": 1 + }, + "type": "literal_in_y_or_linear_in_z" + } + }, + "keccak_256": { + "cpu": { + "arguments": { + "intercept": 2261318, + "slope": 64571 + }, + "type": "linear_in_x" + }, + "memory": { + "arguments": 4, + "type": "constant_cost" + } + }, + "lengthOfByteString": { + "cpu": { + "arguments": 22100, + "type": "constant_cost" + }, + "memory": { + "arguments": 10, + "type": "constant_cost" + } + }, + "lessThanByteString": { + "cpu": { + "arguments": { + "intercept": 28999, + "slope": 74 + }, + "type": "min_size" + }, + "memory": { + "arguments": 1, + "type": "constant_cost" + } + }, + "lessThanEqualsByteString": { + "cpu": { + "arguments": { + "intercept": 28999, + "slope": 74 + }, + "type": "min_size" + }, + "memory": { + "arguments": 1, + "type": "constant_cost" + } + }, + "lessThanEqualsInteger": { + "cpu": { + "arguments": { + "intercept": 43285, + "slope": 552 + }, + "type": "min_size" + }, + "memory": { + "arguments": 1, + "type": "constant_cost" + } + }, + "lessThanInteger": { + "cpu": { + "arguments": { + "intercept": 44749, + "slope": 541 + }, + "type": "min_size" + }, + "memory": { + "arguments": 1, + "type": "constant_cost" + } + }, + "listData": { + "cpu": { + "arguments": 33852, + "type": "constant_cost" + }, + "memory": { + "arguments": 32, + "type": "constant_cost" + } + }, + "mapData": { + "cpu": { + "arguments": 68246, + "type": "constant_cost" + }, + "memory": { + "arguments": 32, + "type": "constant_cost" + } + }, + "mkCons": { + "cpu": { + "arguments": 72362, + "type": "constant_cost" + }, + "memory": { + "arguments": 32, + "type": "constant_cost" + } + }, + "mkNilData": { + "cpu": { + "arguments": 7243, + "type": "constant_cost" + }, + "memory": { + "arguments": 32, + "type": "constant_cost" + } + }, + "mkNilPairData": { + "cpu": { + "arguments": 7391, + "type": "constant_cost" + }, + "memory": { + "arguments": 32, + "type": "constant_cost" + } + }, + "mkPairData": { + "cpu": { + "arguments": 11546, + "type": "constant_cost" + }, + "memory": { + "arguments": 32, + "type": "constant_cost" + } + }, + "modInteger": { + "cpu": { + "arguments": { + "constant": 85848, + "model": { + "arguments": { + "intercept": 228465, + "slope": 122 + }, + "type": "multiplied_sizes" + } + }, + "type": "const_above_diagonal" + }, + "memory": { + "arguments": { + "intercept": 0, + "minimum": 1, + "slope": 1 + }, + "type": "subtracted_sizes" + } + }, + "multiplyInteger": { + "cpu": { + "arguments": { + "intercept": 90434, + "slope": 519 + }, + "type": "multiplied_sizes" + }, + "memory": { + "arguments": { + "intercept": 0, + "slope": 1 + }, + "type": "added_sizes" + } + }, + "nullList": { + "cpu": { + "arguments": 74433, + "type": "constant_cost" + }, + "memory": { + "arguments": 32, + "type": "constant_cost" + } + }, + "indexArray": { + "cpu": { + "arguments": 194922, + "type": "constant_cost" + }, + "memory": { + "arguments": 32, + "type": "constant_cost" + } + }, + "lengthOfArray": { + "cpu": { + "arguments": 198994, + "type": "constant_cost" + }, + "memory": { + "arguments": 10, + "type": "constant_cost" + } + }, + "listToArray": { + "cpu": { + "arguments": { + "intercept": 307802, + "slope": 8496 + }, + "type": "linear_in_x" + }, + "memory": { + "arguments": { + "intercept": 7, + "slope": 1 + }, + "type": "linear_in_x" + } + }, + "quotientInteger": { + "cpu": { + "arguments": { + "constant": 85848, + "model": { + "arguments": { + "intercept": 228465, + "slope": 122 + }, + "type": "multiplied_sizes" + } + }, + "type": "const_above_diagonal" + }, + "memory": { + "arguments": { + "intercept": 0, + "minimum": 1, + "slope": 1 + }, + "type": "subtracted_sizes" + } + }, + "remainderInteger": { + "cpu": { + "arguments": { + "constant": 85848, + "model": { + "arguments": { + "intercept": 228465, + "slope": 122 + }, + "type": "multiplied_sizes" + } + }, + "type": "const_above_diagonal" + }, + "memory": { + "arguments": { + "intercept": 0, + "minimum": 1, + "slope": 1 + }, + "type": "subtracted_sizes" + } + }, + "serialiseData": { + "cpu": { + "arguments": { + "intercept": 955506, + "slope": 213312 + }, + "type": "linear_in_x" + }, + "memory": { + "arguments": { + "intercept": 0, + "slope": 2 + }, + "type": "linear_in_x" + } + }, + "sha2_256": { + "cpu": { + "arguments": { + "intercept": 270652, + "slope": 22588 + }, + "type": "linear_in_x" + }, + "memory": { + "arguments": 4, + "type": "constant_cost" + } + }, + "sha3_256": { + "cpu": { + "arguments": { + "intercept": 1457325, + "slope": 64566 + }, + "type": "linear_in_x" + }, + "memory": { + "arguments": 4, + "type": "constant_cost" + } + }, + "sliceByteString": { + "cpu": { + "arguments": { + "intercept": 20467, + "slope": 1 + }, + "type": "linear_in_z" + }, + "memory": { + "arguments": { + "intercept": 4, + "slope": 0 + }, + "type": "linear_in_z" + } + }, + "sndPair": { + "cpu": { + "arguments": 141992, + "type": "constant_cost" + }, + "memory": { + "arguments": 32, + "type": "constant_cost" + } + }, + "subtractInteger": { + "cpu": { + "arguments": { + "intercept": 100788, + "slope": 420 + }, + "type": "max_size" + }, + "memory": { + "arguments": { + "intercept": 1, + "slope": 1 + }, + "type": "max_size" + } + }, + "tailList": { + "cpu": { + "arguments": 81663, + "type": "constant_cost" + }, + "memory": { + "arguments": 32, + "type": "constant_cost" + } + }, + "trace": { + "cpu": { + "arguments": 59498, + "type": "constant_cost" + }, + "memory": { + "arguments": 32, + "type": "constant_cost" + } + }, + "unBData": { + "cpu": { + "arguments": 20142, + "type": "constant_cost" + }, + "memory": { + "arguments": 32, + "type": "constant_cost" + } + }, + "unConstrData": { + "cpu": { + "arguments": 24588, + "type": "constant_cost" + }, + "memory": { + "arguments": 32, + "type": "constant_cost" + } + }, + "unIData": { + "cpu": { + "arguments": 20744, + "type": "constant_cost" + }, + "memory": { + "arguments": 32, + "type": "constant_cost" + } + }, + "unListData": { + "cpu": { + "arguments": 25933, + "type": "constant_cost" + }, + "memory": { + "arguments": 32, + "type": "constant_cost" + } + }, + "unMapData": { + "cpu": { + "arguments": 24623, + "type": "constant_cost" + }, + "memory": { + "arguments": 32, + "type": "constant_cost" + } + }, + "verifyEcdsaSecp256k1Signature": { + "cpu": { + "arguments": 43053543, + "type": "constant_cost" + }, + "memory": { + "arguments": 10, + "type": "constant_cost" + } + }, + "verifyEd25519Signature": { + "cpu": { + "arguments": { + "intercept": 53384111, + "slope": 14333 + }, + "type": "linear_in_y" + }, + "memory": { + "arguments": 10, + "type": "constant_cost" + } + }, + "verifySchnorrSecp256k1Signature": { + "cpu": { + "arguments": { + "intercept": 43574283, + "slope": 26308 + }, + "type": "linear_in_y" + }, + "memory": { + "arguments": 10, + "type": "constant_cost" + } + }, + "andByteString": { + "cpu": { + "arguments": { + "intercept": 100181, + "slope1": 726, + "slope2": 719 + }, + "type": "linear_in_y_and_z" + }, + "memory": { + "arguments": { + "intercept": 0, + "slope": 1 + }, + "type": "linear_in_max_yz" + } + }, + "orByteString": { + "cpu": { + "arguments": { + "intercept": 100181, + "slope1": 726, + "slope2": 719 + }, + "type": "linear_in_y_and_z" + }, + "memory": { + "arguments": { + "intercept": 0, + "slope": 1 + }, + "type": "linear_in_max_yz" + } + }, + "xorByteString": { + "cpu": { + "arguments": { + "intercept": 100181, + "slope1": 726, + "slope2": 719 + }, + "type": "linear_in_y_and_z" + }, + "memory": { + "arguments": { + "intercept": 0, + "slope": 1 + }, + "type": "linear_in_max_yz" + } + }, + "complementByteString": { + "cpu": { + "arguments": { + "intercept": 107878, + "slope": 680 + }, + "type": "linear_in_x" + }, + "memory": { + "arguments": { + "intercept": 0, + "slope": 1 + }, + "type": "linear_in_x" + } + }, + "readBit": { + "cpu": { + "arguments": 95336, + "type": "constant_cost" + }, + "memory": { + "arguments": 1, + "type": "constant_cost" + } + }, + "writeBits": { + "cpu": { + "arguments": { + "intercept": 281145, + "slope": 18848 + }, + "type": "linear_in_y" + }, + "memory": { + "arguments": { + "intercept": 0, + "slope": 1 + }, + "type": "linear_in_x" + } + }, + "replicateByte": { + "cpu": { + "arguments": { + "intercept": 180194, + "slope": 159 + }, + "type": "linear_in_x" + }, + "memory": { + "arguments": { + "intercept": 1, + "slope": 1 + }, + "type": "linear_in_x" + } + }, + "shiftByteString": { + "cpu": { + "arguments": { + "intercept": 158519, + "slope": 8942 + }, + "type": "linear_in_x" + }, + "memory": { + "arguments": { + "intercept": 0, + "slope": 1 + }, + "type": "linear_in_x" + } + }, + "rotateByteString": { + "cpu": { + "arguments": { + "intercept": 159378, + "slope": 8813 + }, + "type": "linear_in_x" + }, + "memory": { + "arguments": { + "intercept": 0, + "slope": 1 + }, + "type": "linear_in_x" + } + }, + "countSetBits": { + "cpu": { + "arguments": { + "intercept": 107490, + "slope": 3298 + }, + "type": "linear_in_x" + }, + "memory": { + "arguments": 1, + "type": "constant_cost" + } + }, + "findFirstSetBit": { + "cpu": { + "arguments": { + "intercept": 106057, + "slope": 655 + }, + "type": "linear_in_x" + }, + "memory": { + "arguments": 1, + "type": "constant_cost" + } + }, + "ripemd_160": { + "cpu": { + "arguments": { + "intercept": 1964219, + "slope": 24520 + }, + "type": "linear_in_x" + }, + "memory": { + "arguments": 3, + "type": "constant_cost" + } + }, + "expModInteger": { + "cpu": { + "arguments": { + "coefficient00": 607153, + "coefficient11": 231697, + "coefficient12": 53144 + }, + "type": "exp_mod_cost" + }, + "memory": { + "arguments": { + "intercept": 0, + "slope": 1 + }, + "type": "linear_in_z" + } + }, + "dropList": { + "cpu": { + "arguments": { + "intercept": 116711, + "slope": 1957 + }, + "type": "linear_in_x" + }, + "memory": { + "arguments": 4, + "type": "constant_cost" + } + }, + "lookupCoin": { + "cpu": { + "arguments": { + "intercept": 179661, + "slope": 7151 + }, + "type": "linear_in_z" + }, + "memory": { + "arguments": 1, + "type": "constant_cost" + } + }, + "valueContains": { + "cpu": { + "arguments": { + "intercept": 1000, + "slope": 130383 + }, + "type": "linear_in_y" + }, + "memory": { + "arguments": 1, + "type": "constant_cost" + } + }, + "valueData": { + "cpu": { + "arguments": 153844, + "type": "constant_cost" + }, + "memory": { + "arguments": 1, + "type": "constant_cost" + } + }, + "unValueData": { + "cpu": { + "arguments": { + "intercept": 1000, + "slope": 33094 + }, + "type": "linear_in_x" + }, + "memory": { + "arguments": 1, + "type": "constant_cost" } + } } diff --git a/plutus-core/cost-model/data/builtinCostModelC.json b/plutus-core/cost-model/data/builtinCostModelC.json index b31f63df1b8..620f98d462d 100644 --- a/plutus-core/cost-model/data/builtinCostModelC.json +++ b/plutus-core/cost-model/data/builtinCostModelC.json @@ -1,1276 +1,1276 @@ { - "addInteger": { - "cpu": { - "arguments": { - "intercept": 100788, - "slope": 420 - }, - "type": "max_size" - }, - "memory": { - "arguments": { - "intercept": 1, - "slope": 1 - }, - "type": "max_size" - } - }, - "appendByteString": { - "cpu": { - "arguments": { - "intercept": 1000, - "slope": 173 - }, - "type": "added_sizes" - }, - "memory": { - "arguments": { - "intercept": 0, - "slope": 1 - }, - "type": "added_sizes" - } - }, - "appendString": { - "cpu": { - "arguments": { - "intercept": 1000, - "slope": 59957 - }, - "type": "added_sizes" - }, - "memory": { - "arguments": { - "intercept": 4, - "slope": 1 - }, - "type": "added_sizes" - } - }, - "bData": { - "cpu": { - "arguments": 11183, - "type": "constant_cost" - }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } - }, - "blake2b_224": { - "cpu": { - "arguments": { - "intercept": 207616, - "slope": 8310 - }, - "type": "linear_in_x" - }, - "memory": { - "arguments": 4, - "type": "constant_cost" - } - }, - "blake2b_256": { - "cpu": { - "arguments": { - "intercept": 201305, - "slope": 8356 - }, - "type": "linear_in_x" - }, - "memory": { - "arguments": 4, - "type": "constant_cost" - } - }, - "bls12_381_G1_add": { - "cpu": { - "arguments": 962335, - "type": "constant_cost" - }, - "memory": { - "arguments": 18, - "type": "constant_cost" - } - }, - "bls12_381_G1_compress": { - "cpu": { - "arguments": 2780678, - "type": "constant_cost" - }, - "memory": { - "arguments": 6, - "type": "constant_cost" - } - }, - "bls12_381_G1_equal": { - "cpu": { - "arguments": 442008, - "type": "constant_cost" - }, - "memory": { - "arguments": 1, - "type": "constant_cost" - } - }, - "bls12_381_G1_hashToGroup": { - "cpu": { - "arguments": { - "intercept": 52538055, - "slope": 3756 - }, - "type": "linear_in_x" - }, - "memory": { - "arguments": 18, - "type": "constant_cost" - } - }, - "bls12_381_G1_neg": { - "cpu": { - "arguments": 267929, - "type": "constant_cost" - }, - "memory": { - "arguments": 18, - "type": "constant_cost" - } - }, - "bls12_381_G1_scalarMul": { - "cpu": { - "arguments": { - "intercept": 76433006, - "slope": 8868 - }, - "type": "linear_in_x" - }, - "memory": { - "arguments": 18, - "type": "constant_cost" - } - }, - "bls12_381_G1_multiScalarMul": { - "cpu": { - "arguments": { - "intercept": 321837444, - "slope": 25087669 - }, - "type": "linear_in_x" - }, - "memory": { - "arguments": 18, - "type": "constant_cost" - } - }, - "bls12_381_G1_uncompress": { - "cpu": { - "arguments": 52948122, - "type": "constant_cost" - }, - "memory": { - "arguments": 18, - "type": "constant_cost" - } - }, - "bls12_381_G2_add": { - "cpu": { - "arguments": 1995836, - "type": "constant_cost" - }, - "memory": { - "arguments": 36, - "type": "constant_cost" - } - }, - "bls12_381_G2_compress": { - "cpu": { - "arguments": 3227919, - "type": "constant_cost" - }, - "memory": { - "arguments": 12, - "type": "constant_cost" - } - }, - "bls12_381_G2_equal": { - "cpu": { - "arguments": 901022, - "type": "constant_cost" - }, - "memory": { - "arguments": 1, - "type": "constant_cost" - } - }, - "bls12_381_G2_hashToGroup": { - "cpu": { - "arguments": { - "intercept": 166917843, - "slope": 4307 - }, - "type": "linear_in_x" - }, - "memory": { - "arguments": 36, - "type": "constant_cost" - } - }, - "bls12_381_G2_neg": { - "cpu": { - "arguments": 284546, - "type": "constant_cost" - }, - "memory": { - "arguments": 36, - "type": "constant_cost" - } - }, - "bls12_381_G2_scalarMul": { - "cpu": { - "arguments": { - "intercept": 158221314, - "slope": 26549 - }, - "type": "linear_in_x" - }, - "memory": { - "arguments": 36, - "type": "constant_cost" - } - }, - "bls12_381_G2_multiScalarMul": { - "cpu": { - "arguments": { - "intercept": 617887431, - "slope": 67302824 - }, - "type": "linear_in_x" - }, - "memory": { - "arguments": 36, - "type": "constant_cost" - } - }, - "bls12_381_G2_uncompress": { - "cpu": { - "arguments": 74698472, - "type": "constant_cost" - }, - "memory": { - "arguments": 36, - "type": "constant_cost" - } - }, - "bls12_381_finalVerify": { - "cpu": { - "arguments": 333849714, - "type": "constant_cost" - }, - "memory": { - "arguments": 1, - "type": "constant_cost" - } - }, - "bls12_381_millerLoop": { - "cpu": { - "arguments": 254006273, - "type": "constant_cost" - }, - "memory": { - "arguments": 72, - "type": "constant_cost" - } - }, - "bls12_381_mulMlResult": { - "cpu": { - "arguments": 2174038, - "type": "constant_cost" - }, - "memory": { - "arguments": 72, - "type": "constant_cost" - } - }, - "byteStringToInteger": { - "cpu": { - "arguments": { - "c0": 1006041, - "c1": 43623, - "c2": 251 - }, - "type": "quadratic_in_y" - }, - "memory": { - "arguments": { - "intercept": 0, - "slope": 1 - }, - "type": "linear_in_y" - } - }, - "chooseData": { - "cpu": { - "arguments": 94375, - "type": "constant_cost" - }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } - }, - "chooseList": { - "cpu": { - "arguments": 132994, - "type": "constant_cost" - }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } - }, - "chooseUnit": { - "cpu": { - "arguments": 61462, - "type": "constant_cost" - }, - "memory": { - "arguments": 4, - "type": "constant_cost" - } - }, - "consByteString": { - "cpu": { - "arguments": { - "intercept": 72010, - "slope": 178 - }, - "type": "linear_in_y" - }, - "memory": { - "arguments": { - "intercept": 0, - "slope": 1 - }, - "type": "added_sizes" - } - }, - "constrData": { - "cpu": { - "arguments": 22151, - "type": "constant_cost" - }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } - }, - "decodeUtf8": { - "cpu": { - "arguments": { - "intercept": 91189, - "slope": 769 - }, - "type": "linear_in_x" - }, - "memory": { - "arguments": { - "intercept": 4, - "slope": 2 - }, - "type": "linear_in_x" - } - }, - "divideInteger": { - "cpu": { - "arguments": { - "constant": 85848, - "model": { - "arguments": { - "c00": 123203, - "c01": 7305, - "c02": -900, - "c10": 1716, - "c11": 549, - "c20": 57, - "minimum": 85848 - }, - "type": "quadratic_in_x_and_y" - } - }, - "type": "const_above_diagonal" - }, - "memory": { - "arguments": { - "intercept": 0, - "minimum": 1, - "slope": 1 - }, - "type": "subtracted_sizes" - } - }, - "encodeUtf8": { - "cpu": { - "arguments": { - "intercept": 1000, - "slope": 42921 - }, - "type": "linear_in_x" - }, - "memory": { - "arguments": { - "intercept": 4, - "slope": 2 - }, - "type": "linear_in_x" - } - }, - "equalsByteString": { - "cpu": { - "arguments": { - "constant": 24548, - "intercept": 29498, - "slope": 38 - }, - "type": "linear_on_diagonal" - }, - "memory": { - "arguments": 1, - "type": "constant_cost" - } - }, - "equalsData": { - "cpu": { - "arguments": { - "intercept": 898148, - "slope": 27279 - }, - "type": "min_size" - }, - "memory": { - "arguments": 1, - "type": "constant_cost" - } - }, - "equalsInteger": { - "cpu": { - "arguments": { - "intercept": 51775, - "slope": 558 - }, - "type": "min_size" - }, - "memory": { - "arguments": 1, - "type": "constant_cost" - } - }, - "equalsString": { - "cpu": { - "arguments": { - "constant": 39184, - "intercept": 1000, - "slope": 60594 - }, - "type": "linear_on_diagonal" - }, - "memory": { - "arguments": 1, - "type": "constant_cost" - } - }, - "fstPair": { - "cpu": { - "arguments": 141895, - "type": "constant_cost" - }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } - }, - "headList": { - "cpu": { - "arguments": 83150, - "type": "constant_cost" - }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } - }, - "iData": { - "cpu": { - "arguments": 15299, - "type": "constant_cost" - }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } - }, - "ifThenElse": { - "cpu": { - "arguments": 76049, - "type": "constant_cost" - }, - "memory": { - "arguments": 1, - "type": "constant_cost" - } - }, - "indexByteString": { - "cpu": { - "arguments": 13169, - "type": "constant_cost" - }, - "memory": { - "arguments": 4, - "type": "constant_cost" - } - }, - "integerToByteString": { - "cpu": { - "arguments": { - "c0": 1293828, - "c1": 28716, - "c2": 63 - }, - "type": "quadratic_in_z" - }, - "memory": { - "arguments": { - "intercept": 0, - "slope": 1 - }, - "type": "literal_in_y_or_linear_in_z" - } - }, - "keccak_256": { - "cpu": { - "arguments": { - "intercept": 2261318, - "slope": 64571 - }, - "type": "linear_in_x" - }, - "memory": { - "arguments": 4, - "type": "constant_cost" - } - }, - "lengthOfByteString": { - "cpu": { - "arguments": 22100, - "type": "constant_cost" - }, - "memory": { - "arguments": 10, - "type": "constant_cost" - } - }, - "lessThanByteString": { - "cpu": { - "arguments": { - "intercept": 28999, - "slope": 74 - }, - "type": "min_size" - }, - "memory": { - "arguments": 1, - "type": "constant_cost" - } - }, - "lessThanEqualsByteString": { - "cpu": { - "arguments": { - "intercept": 28999, - "slope": 74 - }, - "type": "min_size" - }, - "memory": { - "arguments": 1, - "type": "constant_cost" - } - }, - "lessThanEqualsInteger": { - "cpu": { - "arguments": { - "intercept": 43285, - "slope": 552 - }, - "type": "min_size" - }, - "memory": { - "arguments": 1, - "type": "constant_cost" - } - }, - "lessThanInteger": { - "cpu": { - "arguments": { - "intercept": 44749, - "slope": 541 - }, - "type": "min_size" - }, - "memory": { - "arguments": 1, - "type": "constant_cost" - } - }, - "listData": { - "cpu": { - "arguments": 33852, - "type": "constant_cost" - }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } - }, - "mapData": { - "cpu": { - "arguments": 68246, - "type": "constant_cost" - }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } - }, - "mkCons": { - "cpu": { - "arguments": 72362, - "type": "constant_cost" - }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } - }, - "mkNilData": { - "cpu": { - "arguments": 7243, - "type": "constant_cost" - }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } - }, - "mkNilPairData": { - "cpu": { - "arguments": 7391, - "type": "constant_cost" - }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } - }, - "mkPairData": { - "cpu": { - "arguments": 11546, - "type": "constant_cost" - }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } - }, - "modInteger": { - "cpu": { - "arguments": { - "constant": 85848, - "model": { - "arguments": { - "c00": 123203, - "c01": 7305, - "c02": -900, - "c10": 1716, - "c11": 549, - "c20": 57, - "minimum": 85848 - }, - "type": "quadratic_in_x_and_y" - } - }, - "type": "const_above_diagonal" - }, - "memory": { - "arguments": { - "intercept": 0, - "slope": 1 - }, - "type": "linear_in_y" - } - }, - "multiplyInteger": { - "cpu": { - "arguments": { - "intercept": 90434, - "slope": 519 - }, - "type": "multiplied_sizes" - }, - "memory": { - "arguments": { - "intercept": 0, - "slope": 1 - }, - "type": "added_sizes" - } - }, - "nullList": { - "cpu": { - "arguments": 74433, - "type": "constant_cost" - }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } - }, - "indexArray": { - "cpu": { - "arguments": 194922, - "type": "constant_cost" - }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } - }, - "lengthOfArray": { - "cpu": { - "arguments": 198994, - "type": "constant_cost" - }, - "memory": { - "arguments": 10, - "type": "constant_cost" - } - }, - "listToArray": { - "cpu": { - "arguments": { - "intercept": 307802, - "slope": 8496 - }, - "type": "linear_in_x" - }, - "memory": { - "arguments": { - "intercept": 7, - "slope": 1 - }, - "type": "linear_in_x" - } - }, - "quotientInteger": { - "cpu": { - "arguments": { - "constant": 85848, - "model": { - "arguments": { - "c00": 123203, - "c01": 7305, - "c02": -900, - "c10": 1716, - "c11": 549, - "c20": 57, - "minimum": 85848 - }, - "type": "quadratic_in_x_and_y" - } - }, - "type": "const_above_diagonal" - }, - "memory": { - "arguments": { - "intercept": 0, - "minimum": 1, - "slope": 1 - }, - "type": "subtracted_sizes" - } - }, - "remainderInteger": { - "cpu": { - "arguments": { - "constant": 85848, - "model": { - "arguments": { - "c00": 123203, - "c01": 7305, - "c02": -900, - "c10": 1716, - "c11": 549, - "c20": 57, - "minimum": 85848 - }, - "type": "quadratic_in_x_and_y" - } - }, - "type": "const_above_diagonal" - }, - "memory": { - "arguments": { - "intercept": 0, - "slope": 1 - }, - "type": "linear_in_y" - } - }, - "serialiseData": { - "cpu": { - "arguments": { - "intercept": 955506, - "slope": 213312 - }, - "type": "linear_in_x" - }, - "memory": { - "arguments": { - "intercept": 0, - "slope": 2 - }, - "type": "linear_in_x" - } - }, - "sha2_256": { - "cpu": { - "arguments": { - "intercept": 270652, - "slope": 22588 - }, - "type": "linear_in_x" - }, - "memory": { - "arguments": 4, - "type": "constant_cost" - } - }, - "sha3_256": { - "cpu": { - "arguments": { - "intercept": 1457325, - "slope": 64566 - }, - "type": "linear_in_x" - }, - "memory": { - "arguments": 4, - "type": "constant_cost" - } - }, - "sliceByteString": { - "cpu": { - "arguments": { - "intercept": 20467, - "slope": 1 - }, - "type": "linear_in_z" - }, - "memory": { - "arguments": { - "intercept": 4, - "slope": 0 - }, - "type": "linear_in_z" - } - }, - "sndPair": { - "cpu": { - "arguments": 141992, - "type": "constant_cost" - }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } - }, - "subtractInteger": { - "cpu": { - "arguments": { - "intercept": 100788, - "slope": 420 - }, - "type": "max_size" - }, - "memory": { - "arguments": { - "intercept": 1, - "slope": 1 - }, - "type": "max_size" - } - }, - "tailList": { - "cpu": { - "arguments": 81663, - "type": "constant_cost" - }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } - }, - "trace": { - "cpu": { - "arguments": 59498, - "type": "constant_cost" - }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } - }, - "unBData": { - "cpu": { - "arguments": 20142, - "type": "constant_cost" - }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } - }, - "unConstrData": { - "cpu": { - "arguments": 24588, - "type": "constant_cost" - }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } - }, - "unIData": { - "cpu": { - "arguments": 20744, - "type": "constant_cost" - }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } - }, - "unListData": { - "cpu": { - "arguments": 25933, - "type": "constant_cost" - }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } - }, - "unMapData": { - "cpu": { - "arguments": 24623, - "type": "constant_cost" - }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } - }, - "verifyEcdsaSecp256k1Signature": { - "cpu": { - "arguments": 43053543, - "type": "constant_cost" - }, - "memory": { - "arguments": 10, - "type": "constant_cost" - } - }, - "verifyEd25519Signature": { - "cpu": { - "arguments": { - "intercept": 53384111, - "slope": 14333 - }, - "type": "linear_in_y" - }, - "memory": { - "arguments": 10, - "type": "constant_cost" - } - }, - "verifySchnorrSecp256k1Signature": { - "cpu": { - "arguments": { - "intercept": 43574283, - "slope": 26308 - }, - "type": "linear_in_y" - }, - "memory": { - "arguments": 10, - "type": "constant_cost" - } - }, - "andByteString": { - "cpu": { - "arguments": { - "intercept": 100181, - "slope1": 726, - "slope2": 719 - }, - "type": "linear_in_y_and_z" - }, - "memory": { - "arguments": { - "intercept": 0, - "slope": 1 - }, - "type": "linear_in_max_yz" - } - }, - "orByteString": { - "cpu": { - "arguments": { - "intercept": 100181, - "slope1": 726, - "slope2": 719 - }, - "type": "linear_in_y_and_z" - }, - "memory": { - "arguments": { - "intercept": 0, - "slope": 1 - }, - "type": "linear_in_max_yz" - } - }, - "xorByteString": { - "cpu": { - "arguments": { - "intercept": 100181, - "slope1": 726, - "slope2": 719 - }, - "type": "linear_in_y_and_z" - }, - "memory": { - "arguments": { - "intercept": 0, - "slope": 1 - }, - "type": "linear_in_max_yz" - } - }, - "complementByteString": { - "cpu": { - "arguments": { - "intercept": 107878, - "slope": 680 - }, - "type": "linear_in_x" - }, - "memory": { - "arguments": { - "intercept": 0, - "slope": 1 - }, - "type": "linear_in_x" - } - }, - "readBit": { - "cpu": { - "arguments": 95336, - "type": "constant_cost" - }, - "memory": { - "arguments": 1, - "type": "constant_cost" - } - }, - "writeBits": { - "cpu": { - "arguments": { - "intercept": 281145, - "slope": 18848 - }, - "type": "linear_in_y" - }, - "memory": { - "arguments": { - "intercept": 0, - "slope": 1 - }, - "type": "linear_in_x" - } - }, - "replicateByte": { - "cpu": { - "arguments": { - "intercept": 180194, - "slope": 159 - }, - "type": "linear_in_x" - }, - "memory": { - "arguments": { - "intercept": 1, - "slope": 1 - }, - "type": "linear_in_x" - } - }, - "shiftByteString": { - "cpu": { - "arguments": { - "intercept": 158519, - "slope": 8942 - }, - "type": "linear_in_x" - }, - "memory": { - "arguments": { - "intercept": 0, - "slope": 1 - }, - "type": "linear_in_x" - } - }, - "rotateByteString": { - "cpu": { - "arguments": { - "intercept": 159378, - "slope": 8813 - }, - "type": "linear_in_x" - }, - "memory": { - "arguments": { - "intercept": 0, - "slope": 1 - }, - "type": "linear_in_x" - } - }, - "countSetBits": { - "cpu": { - "arguments": { - "intercept": 107490, - "slope": 3298 - }, - "type": "linear_in_x" - }, - "memory": { - "arguments": 1, - "type": "constant_cost" - } - }, - "findFirstSetBit": { - "cpu": { - "arguments": { - "intercept": 106057, - "slope": 655 - }, - "type": "linear_in_x" - }, - "memory": { - "arguments": 1, - "type": "constant_cost" - } - }, - "ripemd_160": { - "cpu": { - "arguments": { - "intercept": 1964219, - "slope": 24520 - }, - "type": "linear_in_x" - }, - "memory": { - "arguments": 3, - "type": "constant_cost" - } - }, - "expModInteger": { - "cpu": { - "arguments": { - "coefficient00": 607153, - "coefficient11": 231697, - "coefficient12": 53144 - }, - "type": "exp_mod_cost" - }, - "memory": { - "arguments": { - "intercept": 0, - "slope": 1 - }, - "type": "linear_in_z" - } - }, - "dropList": { - "cpu": { - "arguments": { - "intercept": 116711, - "slope": 1957 - }, - "type": "linear_in_x" - }, - "memory": { - "arguments": 4, - "type": "constant_cost" - } - }, - "lookupCoin": { - "cpu": { - "arguments": { - "intercept": 284421, - "slope": 1 - }, - "type": "linear_in_z" - }, - "memory": { - "arguments": 1, - "type": "constant_cost" - } - }, - "valueContains": { - "cpu": { - "arguments": { - "intercept": 42125119, - "slope": 30 - }, - "type": "added_sizes" - }, - "memory": { - "arguments": 1, - "type": "constant_cost" - } - }, - "valueData": { - "cpu": { - "arguments": 205465, - "type": "constant_cost" - }, - "memory": { - "arguments": 1, - "type": "constant_cost" - } - }, - "unValueData": { - "cpu": { - "arguments": { - "intercept": 10532326261, - "slope": 431 - }, - "type": "linear_in_x" - }, - "memory": { - "arguments": 1, - "type": "constant_cost" - } + "addInteger": { + "cpu": { + "arguments": { + "intercept": 100788, + "slope": 420 + }, + "type": "max_size" + }, + "memory": { + "arguments": { + "intercept": 1, + "slope": 1 + }, + "type": "max_size" + } + }, + "appendByteString": { + "cpu": { + "arguments": { + "intercept": 1000, + "slope": 173 + }, + "type": "added_sizes" + }, + "memory": { + "arguments": { + "intercept": 0, + "slope": 1 + }, + "type": "added_sizes" + } + }, + "appendString": { + "cpu": { + "arguments": { + "intercept": 1000, + "slope": 59957 + }, + "type": "added_sizes" + }, + "memory": { + "arguments": { + "intercept": 4, + "slope": 1 + }, + "type": "added_sizes" + } + }, + "bData": { + "cpu": { + "arguments": 11183, + "type": "constant_cost" + }, + "memory": { + "arguments": 32, + "type": "constant_cost" + } + }, + "blake2b_224": { + "cpu": { + "arguments": { + "intercept": 207616, + "slope": 8310 + }, + "type": "linear_in_x" + }, + "memory": { + "arguments": 4, + "type": "constant_cost" + } + }, + "blake2b_256": { + "cpu": { + "arguments": { + "intercept": 201305, + "slope": 8356 + }, + "type": "linear_in_x" + }, + "memory": { + "arguments": 4, + "type": "constant_cost" + } + }, + "bls12_381_G1_add": { + "cpu": { + "arguments": 962335, + "type": "constant_cost" + }, + "memory": { + "arguments": 18, + "type": "constant_cost" + } + }, + "bls12_381_G1_compress": { + "cpu": { + "arguments": 2780678, + "type": "constant_cost" + }, + "memory": { + "arguments": 6, + "type": "constant_cost" + } + }, + "bls12_381_G1_equal": { + "cpu": { + "arguments": 442008, + "type": "constant_cost" + }, + "memory": { + "arguments": 1, + "type": "constant_cost" + } + }, + "bls12_381_G1_hashToGroup": { + "cpu": { + "arguments": { + "intercept": 52538055, + "slope": 3756 + }, + "type": "linear_in_x" + }, + "memory": { + "arguments": 18, + "type": "constant_cost" + } + }, + "bls12_381_G1_neg": { + "cpu": { + "arguments": 267929, + "type": "constant_cost" + }, + "memory": { + "arguments": 18, + "type": "constant_cost" + } + }, + "bls12_381_G1_scalarMul": { + "cpu": { + "arguments": { + "intercept": 76433006, + "slope": 8868 + }, + "type": "linear_in_x" + }, + "memory": { + "arguments": 18, + "type": "constant_cost" + } + }, + "bls12_381_G1_multiScalarMul": { + "cpu": { + "arguments": { + "intercept": 321837444, + "slope": 25087669 + }, + "type": "linear_in_x" + }, + "memory": { + "arguments": 18, + "type": "constant_cost" + } + }, + "bls12_381_G1_uncompress": { + "cpu": { + "arguments": 52948122, + "type": "constant_cost" + }, + "memory": { + "arguments": 18, + "type": "constant_cost" + } + }, + "bls12_381_G2_add": { + "cpu": { + "arguments": 1995836, + "type": "constant_cost" + }, + "memory": { + "arguments": 36, + "type": "constant_cost" + } + }, + "bls12_381_G2_compress": { + "cpu": { + "arguments": 3227919, + "type": "constant_cost" + }, + "memory": { + "arguments": 12, + "type": "constant_cost" + } + }, + "bls12_381_G2_equal": { + "cpu": { + "arguments": 901022, + "type": "constant_cost" + }, + "memory": { + "arguments": 1, + "type": "constant_cost" + } + }, + "bls12_381_G2_hashToGroup": { + "cpu": { + "arguments": { + "intercept": 166917843, + "slope": 4307 + }, + "type": "linear_in_x" + }, + "memory": { + "arguments": 36, + "type": "constant_cost" + } + }, + "bls12_381_G2_neg": { + "cpu": { + "arguments": 284546, + "type": "constant_cost" + }, + "memory": { + "arguments": 36, + "type": "constant_cost" + } + }, + "bls12_381_G2_scalarMul": { + "cpu": { + "arguments": { + "intercept": 158221314, + "slope": 26549 + }, + "type": "linear_in_x" + }, + "memory": { + "arguments": 36, + "type": "constant_cost" + } + }, + "bls12_381_G2_multiScalarMul": { + "cpu": { + "arguments": { + "intercept": 617887431, + "slope": 67302824 + }, + "type": "linear_in_x" + }, + "memory": { + "arguments": 36, + "type": "constant_cost" + } + }, + "bls12_381_G2_uncompress": { + "cpu": { + "arguments": 74698472, + "type": "constant_cost" + }, + "memory": { + "arguments": 36, + "type": "constant_cost" + } + }, + "bls12_381_finalVerify": { + "cpu": { + "arguments": 333849714, + "type": "constant_cost" + }, + "memory": { + "arguments": 1, + "type": "constant_cost" + } + }, + "bls12_381_millerLoop": { + "cpu": { + "arguments": 254006273, + "type": "constant_cost" + }, + "memory": { + "arguments": 72, + "type": "constant_cost" + } + }, + "bls12_381_mulMlResult": { + "cpu": { + "arguments": 2174038, + "type": "constant_cost" + }, + "memory": { + "arguments": 72, + "type": "constant_cost" + } + }, + "byteStringToInteger": { + "cpu": { + "arguments": { + "c0": 1006041, + "c1": 43623, + "c2": 251 + }, + "type": "quadratic_in_y" + }, + "memory": { + "arguments": { + "intercept": 0, + "slope": 1 + }, + "type": "linear_in_y" + } + }, + "chooseData": { + "cpu": { + "arguments": 94375, + "type": "constant_cost" + }, + "memory": { + "arguments": 32, + "type": "constant_cost" + } + }, + "chooseList": { + "cpu": { + "arguments": 132994, + "type": "constant_cost" + }, + "memory": { + "arguments": 32, + "type": "constant_cost" + } + }, + "chooseUnit": { + "cpu": { + "arguments": 61462, + "type": "constant_cost" + }, + "memory": { + "arguments": 4, + "type": "constant_cost" + } + }, + "consByteString": { + "cpu": { + "arguments": { + "intercept": 72010, + "slope": 178 + }, + "type": "linear_in_y" + }, + "memory": { + "arguments": { + "intercept": 0, + "slope": 1 + }, + "type": "added_sizes" + } + }, + "constrData": { + "cpu": { + "arguments": 22151, + "type": "constant_cost" + }, + "memory": { + "arguments": 32, + "type": "constant_cost" + } + }, + "decodeUtf8": { + "cpu": { + "arguments": { + "intercept": 91189, + "slope": 769 + }, + "type": "linear_in_x" + }, + "memory": { + "arguments": { + "intercept": 4, + "slope": 2 + }, + "type": "linear_in_x" + } + }, + "divideInteger": { + "cpu": { + "arguments": { + "constant": 85848, + "model": { + "arguments": { + "c00": 123203, + "c01": 7305, + "c02": -900, + "c10": 1716, + "c11": 549, + "c20": 57, + "minimum": 85848 + }, + "type": "quadratic_in_x_and_y" + } + }, + "type": "const_above_diagonal" + }, + "memory": { + "arguments": { + "intercept": 0, + "minimum": 1, + "slope": 1 + }, + "type": "subtracted_sizes" + } + }, + "encodeUtf8": { + "cpu": { + "arguments": { + "intercept": 1000, + "slope": 42921 + }, + "type": "linear_in_x" + }, + "memory": { + "arguments": { + "intercept": 4, + "slope": 2 + }, + "type": "linear_in_x" + } + }, + "equalsByteString": { + "cpu": { + "arguments": { + "constant": 24548, + "intercept": 29498, + "slope": 38 + }, + "type": "linear_on_diagonal" + }, + "memory": { + "arguments": 1, + "type": "constant_cost" + } + }, + "equalsData": { + "cpu": { + "arguments": { + "intercept": 898148, + "slope": 27279 + }, + "type": "min_size" + }, + "memory": { + "arguments": 1, + "type": "constant_cost" + } + }, + "equalsInteger": { + "cpu": { + "arguments": { + "intercept": 51775, + "slope": 558 + }, + "type": "min_size" + }, + "memory": { + "arguments": 1, + "type": "constant_cost" + } + }, + "equalsString": { + "cpu": { + "arguments": { + "constant": 39184, + "intercept": 1000, + "slope": 60594 + }, + "type": "linear_on_diagonal" + }, + "memory": { + "arguments": 1, + "type": "constant_cost" + } + }, + "fstPair": { + "cpu": { + "arguments": 141895, + "type": "constant_cost" + }, + "memory": { + "arguments": 32, + "type": "constant_cost" + } + }, + "headList": { + "cpu": { + "arguments": 83150, + "type": "constant_cost" + }, + "memory": { + "arguments": 32, + "type": "constant_cost" + } + }, + "iData": { + "cpu": { + "arguments": 15299, + "type": "constant_cost" + }, + "memory": { + "arguments": 32, + "type": "constant_cost" + } + }, + "ifThenElse": { + "cpu": { + "arguments": 76049, + "type": "constant_cost" + }, + "memory": { + "arguments": 1, + "type": "constant_cost" + } + }, + "indexByteString": { + "cpu": { + "arguments": 13169, + "type": "constant_cost" + }, + "memory": { + "arguments": 4, + "type": "constant_cost" + } + }, + "integerToByteString": { + "cpu": { + "arguments": { + "c0": 1293828, + "c1": 28716, + "c2": 63 + }, + "type": "quadratic_in_z" + }, + "memory": { + "arguments": { + "intercept": 0, + "slope": 1 + }, + "type": "literal_in_y_or_linear_in_z" + } + }, + "keccak_256": { + "cpu": { + "arguments": { + "intercept": 2261318, + "slope": 64571 + }, + "type": "linear_in_x" + }, + "memory": { + "arguments": 4, + "type": "constant_cost" + } + }, + "lengthOfByteString": { + "cpu": { + "arguments": 22100, + "type": "constant_cost" + }, + "memory": { + "arguments": 10, + "type": "constant_cost" + } + }, + "lessThanByteString": { + "cpu": { + "arguments": { + "intercept": 28999, + "slope": 74 + }, + "type": "min_size" + }, + "memory": { + "arguments": 1, + "type": "constant_cost" + } + }, + "lessThanEqualsByteString": { + "cpu": { + "arguments": { + "intercept": 28999, + "slope": 74 + }, + "type": "min_size" + }, + "memory": { + "arguments": 1, + "type": "constant_cost" + } + }, + "lessThanEqualsInteger": { + "cpu": { + "arguments": { + "intercept": 43285, + "slope": 552 + }, + "type": "min_size" + }, + "memory": { + "arguments": 1, + "type": "constant_cost" + } + }, + "lessThanInteger": { + "cpu": { + "arguments": { + "intercept": 44749, + "slope": 541 + }, + "type": "min_size" + }, + "memory": { + "arguments": 1, + "type": "constant_cost" + } + }, + "listData": { + "cpu": { + "arguments": 33852, + "type": "constant_cost" + }, + "memory": { + "arguments": 32, + "type": "constant_cost" + } + }, + "mapData": { + "cpu": { + "arguments": 68246, + "type": "constant_cost" + }, + "memory": { + "arguments": 32, + "type": "constant_cost" + } + }, + "mkCons": { + "cpu": { + "arguments": 72362, + "type": "constant_cost" + }, + "memory": { + "arguments": 32, + "type": "constant_cost" + } + }, + "mkNilData": { + "cpu": { + "arguments": 7243, + "type": "constant_cost" + }, + "memory": { + "arguments": 32, + "type": "constant_cost" + } + }, + "mkNilPairData": { + "cpu": { + "arguments": 7391, + "type": "constant_cost" + }, + "memory": { + "arguments": 32, + "type": "constant_cost" + } + }, + "mkPairData": { + "cpu": { + "arguments": 11546, + "type": "constant_cost" + }, + "memory": { + "arguments": 32, + "type": "constant_cost" + } + }, + "modInteger": { + "cpu": { + "arguments": { + "constant": 85848, + "model": { + "arguments": { + "c00": 123203, + "c01": 7305, + "c02": -900, + "c10": 1716, + "c11": 549, + "c20": 57, + "minimum": 85848 + }, + "type": "quadratic_in_x_and_y" + } + }, + "type": "const_above_diagonal" + }, + "memory": { + "arguments": { + "intercept": 0, + "slope": 1 + }, + "type": "linear_in_y" + } + }, + "multiplyInteger": { + "cpu": { + "arguments": { + "intercept": 90434, + "slope": 519 + }, + "type": "multiplied_sizes" + }, + "memory": { + "arguments": { + "intercept": 0, + "slope": 1 + }, + "type": "added_sizes" + } + }, + "nullList": { + "cpu": { + "arguments": 74433, + "type": "constant_cost" + }, + "memory": { + "arguments": 32, + "type": "constant_cost" + } + }, + "indexArray": { + "cpu": { + "arguments": 194922, + "type": "constant_cost" + }, + "memory": { + "arguments": 32, + "type": "constant_cost" + } + }, + "lengthOfArray": { + "cpu": { + "arguments": 198994, + "type": "constant_cost" + }, + "memory": { + "arguments": 10, + "type": "constant_cost" + } + }, + "listToArray": { + "cpu": { + "arguments": { + "intercept": 307802, + "slope": 8496 + }, + "type": "linear_in_x" + }, + "memory": { + "arguments": { + "intercept": 7, + "slope": 1 + }, + "type": "linear_in_x" + } + }, + "quotientInteger": { + "cpu": { + "arguments": { + "constant": 85848, + "model": { + "arguments": { + "c00": 123203, + "c01": 7305, + "c02": -900, + "c10": 1716, + "c11": 549, + "c20": 57, + "minimum": 85848 + }, + "type": "quadratic_in_x_and_y" + } + }, + "type": "const_above_diagonal" + }, + "memory": { + "arguments": { + "intercept": 0, + "minimum": 1, + "slope": 1 + }, + "type": "subtracted_sizes" + } + }, + "remainderInteger": { + "cpu": { + "arguments": { + "constant": 85848, + "model": { + "arguments": { + "c00": 123203, + "c01": 7305, + "c02": -900, + "c10": 1716, + "c11": 549, + "c20": 57, + "minimum": 85848 + }, + "type": "quadratic_in_x_and_y" + } + }, + "type": "const_above_diagonal" + }, + "memory": { + "arguments": { + "intercept": 0, + "slope": 1 + }, + "type": "linear_in_y" + } + }, + "serialiseData": { + "cpu": { + "arguments": { + "intercept": 955506, + "slope": 213312 + }, + "type": "linear_in_x" + }, + "memory": { + "arguments": { + "intercept": 0, + "slope": 2 + }, + "type": "linear_in_x" + } + }, + "sha2_256": { + "cpu": { + "arguments": { + "intercept": 270652, + "slope": 22588 + }, + "type": "linear_in_x" + }, + "memory": { + "arguments": 4, + "type": "constant_cost" + } + }, + "sha3_256": { + "cpu": { + "arguments": { + "intercept": 1457325, + "slope": 64566 + }, + "type": "linear_in_x" + }, + "memory": { + "arguments": 4, + "type": "constant_cost" + } + }, + "sliceByteString": { + "cpu": { + "arguments": { + "intercept": 20467, + "slope": 1 + }, + "type": "linear_in_z" + }, + "memory": { + "arguments": { + "intercept": 4, + "slope": 0 + }, + "type": "linear_in_z" + } + }, + "sndPair": { + "cpu": { + "arguments": 141992, + "type": "constant_cost" + }, + "memory": { + "arguments": 32, + "type": "constant_cost" + } + }, + "subtractInteger": { + "cpu": { + "arguments": { + "intercept": 100788, + "slope": 420 + }, + "type": "max_size" + }, + "memory": { + "arguments": { + "intercept": 1, + "slope": 1 + }, + "type": "max_size" + } + }, + "tailList": { + "cpu": { + "arguments": 81663, + "type": "constant_cost" + }, + "memory": { + "arguments": 32, + "type": "constant_cost" + } + }, + "trace": { + "cpu": { + "arguments": 59498, + "type": "constant_cost" + }, + "memory": { + "arguments": 32, + "type": "constant_cost" + } + }, + "unBData": { + "cpu": { + "arguments": 20142, + "type": "constant_cost" + }, + "memory": { + "arguments": 32, + "type": "constant_cost" + } + }, + "unConstrData": { + "cpu": { + "arguments": 24588, + "type": "constant_cost" + }, + "memory": { + "arguments": 32, + "type": "constant_cost" + } + }, + "unIData": { + "cpu": { + "arguments": 20744, + "type": "constant_cost" + }, + "memory": { + "arguments": 32, + "type": "constant_cost" + } + }, + "unListData": { + "cpu": { + "arguments": 25933, + "type": "constant_cost" + }, + "memory": { + "arguments": 32, + "type": "constant_cost" + } + }, + "unMapData": { + "cpu": { + "arguments": 24623, + "type": "constant_cost" + }, + "memory": { + "arguments": 32, + "type": "constant_cost" + } + }, + "verifyEcdsaSecp256k1Signature": { + "cpu": { + "arguments": 43053543, + "type": "constant_cost" + }, + "memory": { + "arguments": 10, + "type": "constant_cost" + } + }, + "verifyEd25519Signature": { + "cpu": { + "arguments": { + "intercept": 53384111, + "slope": 14333 + }, + "type": "linear_in_y" + }, + "memory": { + "arguments": 10, + "type": "constant_cost" + } + }, + "verifySchnorrSecp256k1Signature": { + "cpu": { + "arguments": { + "intercept": 43574283, + "slope": 26308 + }, + "type": "linear_in_y" + }, + "memory": { + "arguments": 10, + "type": "constant_cost" + } + }, + "andByteString": { + "cpu": { + "arguments": { + "intercept": 100181, + "slope1": 726, + "slope2": 719 + }, + "type": "linear_in_y_and_z" + }, + "memory": { + "arguments": { + "intercept": 0, + "slope": 1 + }, + "type": "linear_in_max_yz" + } + }, + "orByteString": { + "cpu": { + "arguments": { + "intercept": 100181, + "slope1": 726, + "slope2": 719 + }, + "type": "linear_in_y_and_z" + }, + "memory": { + "arguments": { + "intercept": 0, + "slope": 1 + }, + "type": "linear_in_max_yz" + } + }, + "xorByteString": { + "cpu": { + "arguments": { + "intercept": 100181, + "slope1": 726, + "slope2": 719 + }, + "type": "linear_in_y_and_z" + }, + "memory": { + "arguments": { + "intercept": 0, + "slope": 1 + }, + "type": "linear_in_max_yz" + } + }, + "complementByteString": { + "cpu": { + "arguments": { + "intercept": 107878, + "slope": 680 + }, + "type": "linear_in_x" + }, + "memory": { + "arguments": { + "intercept": 0, + "slope": 1 + }, + "type": "linear_in_x" + } + }, + "readBit": { + "cpu": { + "arguments": 95336, + "type": "constant_cost" + }, + "memory": { + "arguments": 1, + "type": "constant_cost" + } + }, + "writeBits": { + "cpu": { + "arguments": { + "intercept": 281145, + "slope": 18848 + }, + "type": "linear_in_y" + }, + "memory": { + "arguments": { + "intercept": 0, + "slope": 1 + }, + "type": "linear_in_x" + } + }, + "replicateByte": { + "cpu": { + "arguments": { + "intercept": 180194, + "slope": 159 + }, + "type": "linear_in_x" + }, + "memory": { + "arguments": { + "intercept": 1, + "slope": 1 + }, + "type": "linear_in_x" + } + }, + "shiftByteString": { + "cpu": { + "arguments": { + "intercept": 158519, + "slope": 8942 + }, + "type": "linear_in_x" + }, + "memory": { + "arguments": { + "intercept": 0, + "slope": 1 + }, + "type": "linear_in_x" + } + }, + "rotateByteString": { + "cpu": { + "arguments": { + "intercept": 159378, + "slope": 8813 + }, + "type": "linear_in_x" + }, + "memory": { + "arguments": { + "intercept": 0, + "slope": 1 + }, + "type": "linear_in_x" + } + }, + "countSetBits": { + "cpu": { + "arguments": { + "intercept": 107490, + "slope": 3298 + }, + "type": "linear_in_x" + }, + "memory": { + "arguments": 1, + "type": "constant_cost" + } + }, + "findFirstSetBit": { + "cpu": { + "arguments": { + "intercept": 106057, + "slope": 655 + }, + "type": "linear_in_x" + }, + "memory": { + "arguments": 1, + "type": "constant_cost" + } + }, + "ripemd_160": { + "cpu": { + "arguments": { + "intercept": 1964219, + "slope": 24520 + }, + "type": "linear_in_x" + }, + "memory": { + "arguments": 3, + "type": "constant_cost" + } + }, + "expModInteger": { + "cpu": { + "arguments": { + "coefficient00": 607153, + "coefficient11": 231697, + "coefficient12": 53144 + }, + "type": "exp_mod_cost" + }, + "memory": { + "arguments": { + "intercept": 0, + "slope": 1 + }, + "type": "linear_in_z" + } + }, + "dropList": { + "cpu": { + "arguments": { + "intercept": 116711, + "slope": 1957 + }, + "type": "linear_in_x" + }, + "memory": { + "arguments": 4, + "type": "constant_cost" + } + }, + "lookupCoin": { + "cpu": { + "arguments": { + "intercept": 179661, + "slope": 7151 + }, + "type": "linear_in_z" + }, + "memory": { + "arguments": 1, + "type": "constant_cost" + } + }, + "valueContains": { + "cpu": { + "arguments": { + "intercept": 1000, + "slope": 130383 + }, + "type": "linear_in_y" + }, + "memory": { + "arguments": 1, + "type": "constant_cost" + } + }, + "valueData": { + "cpu": { + "arguments": 153844, + "type": "constant_cost" + }, + "memory": { + "arguments": 1, + "type": "constant_cost" + } + }, + "unValueData": { + "cpu": { + "arguments": { + "intercept": 1000, + "slope": 33094 + }, + "type": "linear_in_x" + }, + "memory": { + "arguments": 1, + "type": "constant_cost" } + } } From 5c8195357d57ddee77c37fe24cbe83a1c29803df Mon Sep 17 00:00:00 2001 From: Yura Lazaryev Date: Thu, 9 Oct 2025 12:09:01 +0200 Subject: [PATCH 11/17] refactor: use GHC.Num.Integer.integerLog2 in Logarithmic instance Modernize logarithm calculation in the Logarithmic ExMemoryUsage instance by switching from the compatibility module GHC.Integer.Logarithms to the modern GHC.Num.Integer API. Changes: - Replace integerLog2# (unboxed, from GHC.Integer.Logarithms) with integerLog2 (boxed, from GHC.Num.Integer) - Simplify code by removing unboxing boilerplate: I# (integerLog2# x) becomes integerLog2 x - Keep other imports (GHC.Integer.Logarithms, GHC.Exts) as they are still used elsewhere in the file (memoryUsageInteger function) This addresses code review feedback to use the modern ghc-bignum API instead of the legacy compatibility module, while maintaining the same computational semantics. Cost model regeneration verified no regression in derived parameters. --- .../src/PlutusCore/Evaluation/Machine/ExMemoryUsage.hs | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/plutus-core/plutus-core/src/PlutusCore/Evaluation/Machine/ExMemoryUsage.hs b/plutus-core/plutus-core/src/PlutusCore/Evaluation/Machine/ExMemoryUsage.hs index 84d1b59dc5e..25c90b03e2e 100644 --- a/plutus-core/plutus-core/src/PlutusCore/Evaluation/Machine/ExMemoryUsage.hs +++ b/plutus-core/plutus-core/src/PlutusCore/Evaluation/Machine/ExMemoryUsage.hs @@ -35,11 +35,11 @@ import Data.Text qualified as T import Data.Vector.Strict (Vector) import Data.Vector.Strict qualified as Vector import Data.Word -import GHC.Exts (Int (I#)) +import GHC.Exts (Int (I#), quotInt#) import GHC.Integer import GHC.Integer.Logarithms import GHC.Natural -import GHC.Prim +import GHC.Num.Integer (integerLog2) import Universe {- @@ -411,7 +411,7 @@ instance ExMemoryUsage n => ExMemoryUsage (Logarithmic n) where CostRose size _ -> let sizeInteger :: Integer sizeInteger = fromSatInt size - logSize = I# (integerLog2# sizeInteger) + logSize = integerLog2 sizeInteger in singletonRose $ max 1 (fromIntegral (logSize + 1)) {-# INLINE memoryUsage #-} From b43bf61ead1dd624ab0e6d85f3729dcfee82f319 Mon Sep 17 00:00:00 2001 From: Yura Lazaryev Date: Thu, 9 Oct 2025 12:24:05 +0200 Subject: [PATCH 12/17] refactor: use consistent size measure wrappers for Value builtins Address Kenneth's review comment by ensuring builtins use the same size measure wrappers as their budgeting benchmarks. Changes: - Add LogValueOuterOrMaxInner newtype combining logarithmic transformation with outer/max inner size measurement - Update lookupCoin and valueContains to use size measure wrappers - Add KnownTypeAst instances for ValueTotalSize and LogValueOuterOrMaxInner - Update benchmarks to use new combined wrapper type This ensures the cost model accurately reflects runtime behavior by using identical size measures in both denotations and benchmarks. --- .../budgeting-bench/Benchmarks/Values.hs | 8 +++--- .../src/PlutusCore/Default/Builtins.hs | 14 +++++----- .../src/PlutusCore/Default/Universe.hs | 26 ++++++++++++++++++- .../Evaluation/Machine/ExMemoryUsage.hs | 20 ++++++++++++++ 4 files changed, 57 insertions(+), 11 deletions(-) diff --git a/plutus-core/cost-model/budgeting-bench/Benchmarks/Values.hs b/plutus-core/cost-model/budgeting-bench/Benchmarks/Values.hs index 87a58f467dd..3abd3a2548f 100644 --- a/plutus-core/cost-model/budgeting-bench/Benchmarks/Values.hs +++ b/plutus-core/cost-model/budgeting-bench/Benchmarks/Values.hs @@ -11,7 +11,7 @@ import Control.Monad (replicateM) import Criterion.Main (Benchmark) import Data.ByteString (ByteString) import PlutusCore (DefaultFun (LookupCoin, UnValueData, ValueContains, ValueData)) -import PlutusCore.Evaluation.Machine.ExMemoryUsage (Logarithmic (..), ValueOuterOrMaxInner (..), +import PlutusCore.Evaluation.Machine.ExMemoryUsage (LogValueOuterOrMaxInner (..), ValueTotalSize (..)) import PlutusCore.Value (K, Value) import PlutusCore.Value qualified as Value @@ -34,7 +34,7 @@ makeBenchmarks gen = lookupCoinBenchmark :: StdGen -> Benchmark lookupCoinBenchmark gen = createThreeTermBuiltinBenchElementwiseWithWrappers - (id, id, Logarithmic . ValueOuterOrMaxInner) -- Wrap Value argument to report outer/max inner size + (id, id, LogValueOuterOrMaxInner) -- Wrap Value argument to report outer/max inner size with log LookupCoin -- the builtin fun [] -- no type arguments needed (monomorphic builtin) (lookupCoinArgs gen) -- the argument combos to generate benchmarks for @@ -102,8 +102,8 @@ generateRandomLookupTest g = do valueContainsBenchmark :: StdGen -> Benchmark valueContainsBenchmark gen = createTwoTermBuiltinBenchElementwiseWithWrappers - (Logarithmic . ValueOuterOrMaxInner, ValueTotalSize) - -- Container: outer/maxInner, Contained: totalSize + (LogValueOuterOrMaxInner, ValueTotalSize) + -- Container: outer/maxInner with log, Contained: totalSize ValueContains -- the builtin fun [] -- no type arguments needed (monomorphic builtin) (valueContainsArgs gen) -- the argument combos to generate benchmarks for diff --git a/plutus-core/plutus-core/src/PlutusCore/Default/Builtins.hs b/plutus-core/plutus-core/src/PlutusCore/Default/Builtins.hs index 8cf1fdf4739..26a3416762f 100644 --- a/plutus-core/plutus-core/src/PlutusCore/Default/Builtins.hs +++ b/plutus-core/plutus-core/src/PlutusCore/Default/Builtins.hs @@ -24,8 +24,9 @@ import PlutusCore.Default.Universe import PlutusCore.Evaluation.Machine.BuiltinCostModel import PlutusCore.Evaluation.Machine.ExBudgetStream (ExBudgetStream) import PlutusCore.Evaluation.Machine.ExMemoryUsage (ExMemoryUsage, IntegerCostedLiterally (..), - NumBytesCostedAsNumWords (..), memoryUsage, - singletonRose) + LogValueOuterOrMaxInner (..), + NumBytesCostedAsNumWords (..), + ValueTotalSize (..), memoryUsage, singletonRose) import PlutusCore.Pretty (PrettyConfigPlc) import PlutusCore.Value (Value) import PlutusCore.Value qualified as Value @@ -2055,8 +2056,8 @@ instance uni ~ DefaultUni => ToBuiltinMeaning uni DefaultFun where (runCostingFunFourArguments . unimplementedCostingFun) toBuiltinMeaning _semvar LookupCoin = - let lookupCoinDenotation :: ByteString -> ByteString -> Value -> Integer - lookupCoinDenotation = Value.lookupCoin + let lookupCoinDenotation :: ByteString -> ByteString -> LogValueOuterOrMaxInner -> Integer + lookupCoinDenotation p t (LogValueOuterOrMaxInner v) = Value.lookupCoin p t v {-# INLINE lookupCoinDenotation #-} in makeBuiltinMeaning lookupCoinDenotation @@ -2071,8 +2072,9 @@ instance uni ~ DefaultUni => ToBuiltinMeaning uni DefaultFun where (runCostingFunTwoArguments . unimplementedCostingFun) toBuiltinMeaning _semvar ValueContains = - let valueContainsDenotation :: Value -> Value -> BuiltinResult Bool - valueContainsDenotation = Value.valueContains + let valueContainsDenotation :: LogValueOuterOrMaxInner -> ValueTotalSize -> BuiltinResult Bool + valueContainsDenotation (LogValueOuterOrMaxInner v1) (ValueTotalSize v2) = + Value.valueContains v1 v2 {-# INLINE valueContainsDenotation #-} in makeBuiltinMeaning valueContainsDenotation diff --git a/plutus-core/plutus-core/src/PlutusCore/Default/Universe.hs b/plutus-core/plutus-core/src/PlutusCore/Default/Universe.hs index 1cb022be55f..61e176d4f03 100644 --- a/plutus-core/plutus-core/src/PlutusCore/Default/Universe.hs +++ b/plutus-core/plutus-core/src/PlutusCore/Default/Universe.hs @@ -52,7 +52,9 @@ import PlutusCore.Crypto.BLS12_381.G2 qualified as BLS12_381.G2 import PlutusCore.Crypto.BLS12_381.Pairing qualified as BLS12_381.Pairing import PlutusCore.Data (Data) import PlutusCore.Evaluation.Machine.ExMemoryUsage (IntegerCostedLiterally (..), - NumBytesCostedAsNumWords (..)) + LogValueOuterOrMaxInner (..), + NumBytesCostedAsNumWords (..), + ValueTotalSize (..)) import PlutusCore.Pretty.Extra (juxtRenderContext) import PlutusCore.Value (Value) @@ -566,6 +568,28 @@ instance KnownBuiltinTypeIn DefaultUni term Integer => readKnown = readKnownCoerce @Integer {-# INLINE readKnown #-} +deriving newtype instance + KnownTypeAst tyname DefaultUni ValueTotalSize +instance KnownBuiltinTypeIn DefaultUni term Value => + MakeKnownIn DefaultUni term ValueTotalSize where + makeKnown = makeKnownCoerce @Value + {-# INLINE makeKnown #-} +instance KnownBuiltinTypeIn DefaultUni term Value => + ReadKnownIn DefaultUni term ValueTotalSize where + readKnown = readKnownCoerce @Value + {-# INLINE readKnown #-} + +deriving newtype instance + KnownTypeAst tyname DefaultUni LogValueOuterOrMaxInner +instance KnownBuiltinTypeIn DefaultUni term Value => + MakeKnownIn DefaultUni term LogValueOuterOrMaxInner where + makeKnown = makeKnownCoerce @Value + {-# INLINE makeKnown #-} +instance KnownBuiltinTypeIn DefaultUni term Value => + ReadKnownIn DefaultUni term LogValueOuterOrMaxInner where + readKnown = readKnownCoerce @Value + {-# INLINE readKnown #-} + deriving via AsInteger Natural instance KnownTypeAst tyname DefaultUni Natural instance KnownBuiltinTypeIn DefaultUni term Integer => diff --git a/plutus-core/plutus-core/src/PlutusCore/Evaluation/Machine/ExMemoryUsage.hs b/plutus-core/plutus-core/src/PlutusCore/Evaluation/Machine/ExMemoryUsage.hs index 25c90b03e2e..590d886a655 100644 --- a/plutus-core/plutus-core/src/PlutusCore/Evaluation/Machine/ExMemoryUsage.hs +++ b/plutus-core/plutus-core/src/PlutusCore/Evaluation/Machine/ExMemoryUsage.hs @@ -15,6 +15,7 @@ module PlutusCore.Evaluation.Machine.ExMemoryUsage , ValueTotalSize(..) , ValueOuterOrMaxInner(..) , Logarithmic(..) + , LogValueOuterOrMaxInner(..) ) where import PlutusCore.Crypto.BLS12_381.G1 as BLS12_381.G1 @@ -415,6 +416,25 @@ instance ExMemoryUsage n => ExMemoryUsage (Logarithmic n) where in singletonRose $ max 1 (fromIntegral (logSize + 1)) {-# INLINE memoryUsage #-} +{-| A combined wrapper for Value that measures size using outer/max inner map sizes +with logarithmic transformation. This is equivalent to @Logarithmic ValueOuterOrMaxInner@ +but defined as a single newtype for simpler type instances and better error messages. + +Used for builtins like lookupCoin and valueContains where the cost depends on +O(log max(m, k)) where m is the number of policies and k is the max tokens per policy. + +If this is used to wrap an argument in the denotation of a builtin then it *MUST* also +be used to wrap the same argument in the relevant budgeting benchmark. +-} +newtype LogValueOuterOrMaxInner = LogValueOuterOrMaxInner { unLogValueOuterOrMaxInner :: Value } + +instance ExMemoryUsage LogValueOuterOrMaxInner where + memoryUsage (LogValueOuterOrMaxInner v) = + let size = Map.size (Value.unpack v) `max` Value.maxInnerSize v + logSize = integerLog2 (toInteger size) + in singletonRose $ max 1 (fromIntegral (logSize + 1)) + {-# INLINE memoryUsage #-} + {- Note [Costing constant-size types] The memory usage of each of the BLS12-381 types is constant, so we may be able to optimise things a little by ensuring that we don't re-compute the size of From 92d18851ad8017771c79b78883e2569a0e555746 Mon Sep 17 00:00:00 2001 From: Yura Lazaryev Date: Thu, 9 Oct 2025 13:30:13 +0200 Subject: [PATCH 13/17] feat: update benchmark data and cost model parameters for Value builtins Regenerate cost model parameters based on fresh benchmark runs for the four Value-related built-in functions: lookupCoin, valueContains, valueData, and unValueData. New cost models: - lookupCoin: linear_in_z (intercept: 209937, slope: 7181) - valueContains: linear_in_y (intercept: 1000, slope: 131959) - valueData: constant_cost (182815) - unValueData: linear_in_x (intercept: 1000, slope: 33361) The benchmark data includes 350 measurement points across varying input sizes to ensure accurate cost estimation. All three cost model variants (A, B, C) have been updated consistently with identical parameters. --- .../cost-model/data/benching-conway.csv | 700 +++++++++--------- .../cost-model/data/builtinCostModelA.json | 10 +- .../cost-model/data/builtinCostModelB.json | 10 +- .../cost-model/data/builtinCostModelC.json | 10 +- 4 files changed, 365 insertions(+), 365 deletions(-) diff --git a/plutus-core/cost-model/data/benching-conway.csv b/plutus-core/cost-model/data/benching-conway.csv index 82ec7c52650..078c8affec0 100644 --- a/plutus-core/cost-model/data/benching-conway.csv +++ b/plutus-core/cost-model/data/benching-conway.csv @@ -12294,353 +12294,353 @@ Bls12_381_G2_multiScalarMul/97/97,6.90522012785712e-3,6.901544208299667e-3,6.918 Bls12_381_G2_multiScalarMul/98/98,6.9597205589059085e-3,6.9554579231546464e-3,6.963825444927238e-3,1.230537047747648e-5,9.828399035508776e-6,1.581113740579338e-5 Bls12_381_G2_multiScalarMul/99/99,6.998605748330429e-3,6.993956045528542e-3,7.003564931628933e-3,1.3941888558415054e-5,1.1848281516892752e-5,1.8598404587423643e-5 Bls12_381_G2_multiScalarMul/100/100,7.090569654857228e-3,7.08876305884669e-3,7.093035056145744e-3,6.187076669186285e-6,4.689206191622249e-6,8.297705725121281e-6 -LookupCoin/4/4/1,1.1534472901399238e-6,1.1524112485300528e-6,1.1547714765589249e-6,4.0641621926718e-9,3.5452038180553337e-9,4.940445527575718e-9 -LookupCoin/4/4/4,1.1610866397454247e-6,1.1604563749532721e-6,1.1617063429991664e-6,2.017385982146994e-9,1.7121017071566048e-9,2.465151601504615e-9 -LookupCoin/4/4/4,1.1774005815816455e-6,1.1757529390389185e-6,1.179176847539009e-6,5.658757651279759e-9,4.644228857340083e-9,6.611495473612035e-9 -LookupCoin/4/4/6,1.1916918928618511e-6,1.190422907748009e-6,1.193173839698956e-6,4.665977313866328e-9,3.6631933897168235e-9,5.907467979461302e-9 -LookupCoin/4/4/7,1.2081228008186858e-6,1.2075792823969807e-6,1.2087450470879218e-6,2.1007936976091115e-9,1.7416127415560338e-9,2.5734618148224033e-9 -LookupCoin/4/4/9,1.22186256897354e-6,1.22079638986199e-6,1.2228174375924155e-6,3.297746327386577e-9,2.839091055846269e-9,3.821333117747494e-9 -LookupCoin/4/4/10,1.2190771032840023e-6,1.2182323802927799e-6,1.2204703608998758e-6,3.679007873778502e-9,2.5664700856261745e-9,5.709716144647835e-9 -LookupCoin/4/4/3,1.1760034998696908e-6,1.1749764160005035e-6,1.1773987433390327e-6,4.134618566929028e-9,3.4983131522155535e-9,4.846099138284671e-9 -LookupCoin/4/4/4,1.1724389842513614e-6,1.171202474639233e-6,1.1736212940968032e-6,4.060397866264552e-9,3.3911098606443696e-9,4.874063846777242e-9 -LookupCoin/4/4/5,1.186276670542198e-6,1.1849660027412163e-6,1.1877881978386803e-6,4.746233008575273e-9,3.96889048330745e-9,6.169049327002083e-9 -LookupCoin/4/4/7,1.1985154329655813e-6,1.1977012560461198e-6,1.1998861807550411e-6,3.5356660936590374e-9,2.199240326494903e-9,6.085998058416401e-9 -LookupCoin/4/4/10,1.212044503566453e-6,1.2112549781307214e-6,1.2132939641287698e-6,3.085806921876905e-9,2.1491725020386978e-9,4.274791294719317e-9 -LookupCoin/4/4/9,1.2197458596870582e-6,1.2188660580397794e-6,1.2208428419766672e-6,3.3842947898904777e-9,2.8668608524608777e-9,4.0727782723269836e-9 -LookupCoin/4/4/9,1.2010997264914224e-6,1.200106382607801e-6,1.2023171386855648e-6,3.431246601005009e-9,2.867932018216361e-9,4.0822590889582006e-9 -LookupCoin/4/4/10,1.2348766962338111e-6,1.2339246262576525e-6,1.2357811788641032e-6,3.2816607860449476e-9,2.857535355670083e-9,3.780985674266283e-9 -LookupCoin/4/4/9,1.2144090697470449e-6,1.2131084097130315e-6,1.2156572132531938e-6,4.304814734381262e-9,3.6577989003638705e-9,5.042081882140313e-9 -LookupCoin/4/4/10,1.209618422286151e-6,1.2084066754067936e-6,1.2111073368850447e-6,4.371855457335534e-9,3.3656545268840697e-9,5.779470032895302e-9 -LookupCoin/4/4/10,1.210165342950211e-6,1.2090749210374545e-6,1.2113250291719528e-6,3.788921550293763e-9,3.2155320868767343e-9,4.6269499754478604e-9 -LookupCoin/4/4/10,1.2235940789270705e-6,1.2225606057299341e-6,1.2246289196011864e-6,3.400679978557537e-9,2.8011107626270736e-9,4.613236340246698e-9 -LookupCoin/4/4/10,1.2230668561970737e-6,1.2221937446410287e-6,1.2237095716104843e-6,2.475674557308414e-9,1.9626501907285127e-9,3.7071967743530107e-9 -LookupCoin/4/4/9,1.1889029156920706e-6,1.1880053862709033e-6,1.1900374917253151e-6,3.3478126043567047e-9,2.7289049311982276e-9,4.855469961787361e-9 -LookupCoin/4/4/10,1.227862756358173e-6,1.2267847329829582e-6,1.228962269773679e-6,3.6921321326127223e-9,3.139000902274087e-9,4.687705887612031e-9 -LookupCoin/4/4/10,1.2072638717824325e-6,1.2065372351649394e-6,1.2080603606433759e-6,2.5605379801492863e-9,2.130719335261522e-9,3.342840436529004e-9 -LookupCoin/4/4/9,1.2048640045178505e-6,1.2041040836384836e-6,1.206053529944406e-6,3.1152890266742653e-9,2.2986310562366542e-9,4.9659107627078964e-9 -LookupCoin/4/4/9,1.2170554214680805e-6,1.2158461767462672e-6,1.218250184207636e-6,4.05936816577866e-9,3.4099039201076022e-9,4.9708528153023505e-9 -LookupCoin/4/4/9,1.2116410991702124e-6,1.2110855372022904e-6,1.2123167194971357e-6,2.110680574196297e-9,1.5738372055536842e-9,3.1795340192951133e-9 -LookupCoin/4/4/9,1.2200438970276316e-6,1.2189933591524046e-6,1.221305925182948e-6,3.7037679394520034e-9,3.1290372975654653e-9,4.551229486028815e-9 -LookupCoin/4/4/10,1.2173088998090225e-6,1.2165042326120895e-6,1.2181983291801061e-6,2.8029973454960424e-9,2.37231637695913e-9,3.4604317606972556e-9 -LookupCoin/4/4/9,1.2017126423022042e-6,1.200632281748984e-6,1.202903116044268e-6,3.781045240585668e-9,2.9397025316566446e-9,4.946098843185507e-9 -LookupCoin/4/4/10,1.2304983791984658e-6,1.2299797841357625e-6,1.2309998972246447e-6,1.7068516958025802e-9,1.4729426671866016e-9,2.033510242377355e-9 -LookupCoin/4/4/8,1.213066221159993e-6,1.2116525285687004e-6,1.215071690889799e-6,5.3617662326851e-9,3.935749632031287e-9,7.901580396978991e-9 -LookupCoin/4/4/9,1.2253324093752865e-6,1.2240369347052394e-6,1.2264504879254988e-6,3.88427355225941e-9,2.968318109520233e-9,5.133414413710082e-9 -LookupCoin/4/4/10,1.2311475932985818e-6,1.2299045696058998e-6,1.232424953162509e-6,4.129560644494372e-9,3.4953810297482135e-9,5.366496584623623e-9 -LookupCoin/4/4/10,1.2349346616905418e-6,1.2336204242442853e-6,1.236189233621282e-6,4.010625806071552e-9,3.4640917847106747e-9,4.803344725349452e-9 -LookupCoin/4/4/10,1.2197488623106857e-6,1.218870714132973e-6,1.220587553143493e-6,2.9601116205664266e-9,2.511249230129429e-9,3.4768164681892435e-9 -LookupCoin/4/4/9,1.2087709881874945e-6,1.2075273290853454e-6,1.2099009737387109e-6,3.887060104710359e-9,3.3371957867118426e-9,4.511098188658732e-9 -LookupCoin/4/4/10,1.2300092057070488e-6,1.2290346373801981e-6,1.2308991882796534e-6,3.064016089741907e-9,2.583419648104346e-9,3.79983204057076e-9 -LookupCoin/4/4/9,1.2059029078447557e-6,1.2052928651550498e-6,1.2065914611136291e-6,2.1010403170160913e-9,1.7796349524022461e-9,2.652918769719015e-9 -LookupCoin/4/4/10,1.2132412510204579e-6,1.2121888809755203e-6,1.2149708146143543e-6,4.232696012011695e-9,3.0783915523862898e-9,6.910426954285835e-9 -LookupCoin/4/4/7,1.1988345585365298e-6,1.1978472369136555e-6,1.1999495924891883e-6,3.6450023936990258e-9,3.2413028652772947e-9,4.418496031279859e-9 -LookupCoin/4/4/9,1.214519533779959e-6,1.2136575736660475e-6,1.2159919307151074e-6,3.7050313705220404e-9,2.3354419165849325e-9,6.5731886027933965e-9 -LookupCoin/4/4/8,1.2020350986276132e-6,1.201218193546641e-6,1.2026925436305998e-6,2.467081687777941e-9,1.8043871359229474e-9,3.3392450543947458e-9 -LookupCoin/4/4/10,1.2222679020181828e-6,1.220905632495155e-6,1.2246266737260014e-6,5.679227279774581e-9,3.727096530858876e-9,9.523614827378908e-9 -LookupCoin/4/4/9,1.2135489900544324e-6,1.2126793816267723e-6,1.2144133815929518e-6,3.023744411916157e-9,2.5780024526158883e-9,3.596657852145017e-9 -LookupCoin/4/4/8,1.2197908538280475e-6,1.2180956604588496e-6,1.2217632683497774e-6,6.084910617903105e-9,5.435179776000006e-9,7.073790751341013e-9 -LookupCoin/4/4/9,1.212007864598544e-6,1.2113330398221342e-6,1.2126660609808017e-6,2.308335843355634e-9,1.915042172033909e-9,2.774023536063372e-9 -LookupCoin/4/4/8,1.2212852306980274e-6,1.2201513163209499e-6,1.2224841849159272e-6,3.953112459758078e-9,3.16437124868229e-9,5.026939221050529e-9 -LookupCoin/4/4/10,1.2353131845776723e-6,1.233941986574437e-6,1.2370980165559903e-6,5.530757184850481e-9,4.753838675200683e-9,6.442169482481464e-9 -LookupCoin/4/4/9,1.1793206086375916e-6,1.178584733986701e-6,1.179961860665618e-6,2.4267020853651928e-9,1.959651496291369e-9,3.3470155014444936e-9 -LookupCoin/4/4/8,1.204870645799376e-6,1.2036139668967718e-6,1.205886776594027e-6,3.727968380828233e-9,3.0891533145762463e-9,4.467331996571003e-9 -LookupCoin/4/4/10,1.2178982336014464e-6,1.2169471540437263e-6,1.2191283317440976e-6,3.7112786514496762e-9,2.935318707378828e-9,5.140744984906639e-9 -LookupCoin/4/4/10,1.2188458213877058e-6,1.2179859338278188e-6,1.2199100722773312e-6,3.3422795823639585e-9,2.7411903970205664e-9,4.636506287545538e-9 -LookupCoin/4/4/9,1.214638995454963e-6,1.213708813972099e-6,1.2160569047240595e-6,3.7490605869356555e-9,2.9160780648119563e-9,5.229456441325402e-9 -LookupCoin/4/4/10,1.2225433614748636e-6,1.2215482375269644e-6,1.2237754976291384e-6,3.629038618997282e-9,3.0305032419436265e-9,4.414320498812328e-9 -LookupCoin/4/4/10,1.2275498051888786e-6,1.2264323478666893e-6,1.2286517276695741e-6,3.6702369088252977e-9,3.3133800555606663e-9,4.176629006390668e-9 -LookupCoin/4/4/8,1.2016804483751465e-6,1.2011310435585076e-6,1.2023378701823055e-6,1.937509982283731e-9,1.5303199131455102e-9,2.4570647348392655e-9 -LookupCoin/4/4/10,1.2112570026879238e-6,1.2101568608309042e-6,1.212360063064909e-6,3.717319310167394e-9,2.9194951052602018e-9,4.970362447163203e-9 -LookupCoin/4/4/9,1.2188977630170537e-6,1.2178359601285404e-6,1.2201188282513097e-6,3.769356684584986e-9,3.149442271264225e-9,4.772762980433492e-9 -LookupCoin/4/4/10,1.2323943829237225e-6,1.2315382548194777e-6,1.2337680234645939e-6,3.561426918764251e-9,2.28979787786825e-9,6.099199160825918e-9 -LookupCoin/4/4/10,1.2298650745956071e-6,1.229110859787272e-6,1.230744307303272e-6,2.806991300904623e-9,2.2927922205537944e-9,3.7754207967714976e-9 -LookupCoin/4/4/7,1.193032734889915e-6,1.19178202411572e-6,1.1947430231611674e-6,4.869158030513213e-9,3.931740250825642e-9,6.177773842346549e-9 -LookupCoin/4/4/9,1.216371198408557e-6,1.2158361401488627e-6,1.2168538849375672e-6,1.7697403817443696e-9,1.3963436510638211e-9,2.27239285508568e-9 -LookupCoin/4/4/10,1.2325742846654678e-6,1.231734878079346e-6,1.2346106018503925e-6,4.183543302328641e-9,2.1037526600700003e-9,7.804656639944263e-9 -LookupCoin/4/4/11,1.237407537657278e-6,1.2356528408070078e-6,1.2392376472775964e-6,5.821969594412085e-9,5.16630720838863e-9,6.586214451160239e-9 -LookupCoin/4/4/5,1.1856258433419084e-6,1.1842069572543944e-6,1.187178673161659e-6,5.1846898288680965e-9,4.409310187551346e-9,6.254192759844087e-9 -LookupCoin/4/4/11,1.2155008424622768e-6,1.2146757827742595e-6,1.2164111476274816e-6,2.899675672525393e-9,2.441539784366106e-9,3.512372279146876e-9 -LookupCoin/4/4/10,1.2065546917201032e-6,1.2046172722692515e-6,1.2090198796299678e-6,7.545930799225587e-9,5.9688206286642834e-9,1.1089470895454683e-8 -LookupCoin/4/4/10,1.2196360708625704e-6,1.2184040276358496e-6,1.2213006834303905e-6,4.802926137384681e-9,3.757626126043643e-9,6.290923368477043e-9 -LookupCoin/4/4/11,1.224974987541705e-6,1.223160938351159e-6,1.2311246718525401e-6,1.013385284774211e-8,4.07257074376166e-9,1.971828248431561e-8 -LookupCoin/4/4/8,1.2011736531568869e-6,1.200438396722228e-6,1.2020688899348711e-6,2.6751216897864477e-9,2.2604525350603145e-9,3.388947160952035e-9 -LookupCoin/4/4/11,1.2184304981837817e-6,1.2166589664240896e-6,1.22329905903681e-6,8.97842151304465e-9,3.728768405784872e-9,1.889722867283809e-8 -LookupCoin/4/4/8,1.2067816840543925e-6,1.206361748517341e-6,1.2075703192123119e-6,1.9068537051218633e-9,1.4189981821104017e-9,2.8939086084684083e-9 -LookupCoin/4/4/8,1.2125223673672614e-6,1.211204434430315e-6,1.2160943051154748e-6,7.288770169418742e-9,2.485098578436094e-9,1.5025899876584037e-8 -LookupCoin/4/4/11,1.2205219527129726e-6,1.2192549402163512e-6,1.2215892353197644e-6,3.8614757915982414e-9,3.1992058613565774e-9,5.063023013505288e-9 -LookupCoin/4/4/10,1.2300843789497594e-6,1.2290438497712692e-6,1.2311008897226012e-6,3.5227882086061747e-9,2.7499034147861968e-9,4.810875970489256e-9 -LookupCoin/4/4/10,1.2013929562744759e-6,1.200481607647232e-6,1.202504870822784e-6,3.2751923244814385e-9,2.1168456634541903e-9,5.8109592636043915e-9 -LookupCoin/4/4/10,1.2305977876473265e-6,1.2294905496966056e-6,1.2318603561077214e-6,4.0711509166902646e-9,3.378055077358201e-9,4.9481380681675515e-9 -LookupCoin/4/4/11,1.2288881103180648e-6,1.2282348118217263e-6,1.2296516339789366e-6,2.377608466835124e-9,1.982176930726083e-9,2.9684094818468865e-9 -LookupCoin/4/4/11,1.2350331861787772e-6,1.233964666618698e-6,1.2362266144993453e-6,3.732233729284558e-9,3.1991169653336913e-9,4.476369285213807e-9 -LookupCoin/4/4/10,1.2209007387611954e-6,1.2202357876462576e-6,1.2221044179899346e-6,3.0047569336565615e-9,1.6387754598225905e-9,4.949949437006407e-9 -LookupCoin/4/4/11,1.2375217358339814e-6,1.2367125703734653e-6,1.2384104957761834e-6,2.9578146690622734e-9,2.373257191219735e-9,3.641735250392075e-9 -LookupCoin/4/4/11,1.231512711706511e-6,1.2304143879197356e-6,1.2325937237500649e-6,3.5919239356151746e-9,2.787931962181056e-9,5.207498544217727e-9 -LookupCoin/4/4/11,1.2332103660304604e-6,1.2324095784582703e-6,1.2340205232095756e-6,2.703178647844072e-9,2.207595315547423e-9,3.3698139708385147e-9 -LookupCoin/4/4/10,1.2151010613053054e-6,1.2139069708297562e-6,1.2171063042801e-6,4.881478217634782e-9,3.5874051362365304e-9,7.992433034555917e-9 -LookupCoin/4/4/11,1.2290435369298266e-6,1.2269191688897788e-6,1.230921245801445e-6,6.574508748365292e-9,5.607199588352304e-9,7.77862262124682e-9 -LookupCoin/4/4/10,1.2091823523230104e-6,1.2084458834186694e-6,1.2104132057142133e-6,3.1511186351630638e-9,2.0381734613969673e-9,5.324717673383524e-9 -LookupCoin/4/4/10,1.2120435917234926e-6,1.2106595211874085e-6,1.21343947039997e-6,4.463333369427232e-9,3.999211413752267e-9,5.065051826522262e-9 -LookupCoin/4/4/10,1.2115496386333912e-6,1.2107029499384152e-6,1.212711881455988e-6,3.3007519858248528e-9,2.4441693312056897e-9,5.1149851260605535e-9 -LookupCoin/4/4/10,1.2150987387014107e-6,1.2144473549563434e-6,1.2155839955357989e-6,1.9583246105665682e-9,1.5801607100607197e-9,2.671433754728061e-9 -LookupCoin/4/4/9,1.2208167607196566e-6,1.2191459373986416e-6,1.222880466312901e-6,6.255260576547086e-9,4.994336110190262e-9,9.083471646866714e-9 -LookupCoin/4/4/11,1.2358513536522013e-6,1.2352265536976772e-6,1.2366449353576938e-6,2.3451142257690808e-9,1.7693730410291272e-9,3.5932198647789172e-9 -LookupCoin/4/4/11,1.2257651415075026e-6,1.2248368995463083e-6,1.2271096253059002e-6,3.541646825146961e-9,2.5912654373993167e-9,4.65583839066808e-9 -LookupCoin/4/4/10,1.189168503538572e-6,1.188508588087873e-6,1.1898835184581933e-6,2.3638681236668316e-9,1.95397492832121e-9,2.982019185548157e-9 -LookupCoin/4/4/10,1.2145997780830431e-6,1.2125174055568225e-6,1.2175875014853785e-6,8.092910767610745e-9,6.236989087716155e-9,1.1448673234348647e-8 -LookupCoin/4/4/10,1.195433386129742e-6,1.1939042519461409e-6,1.1970554349787428e-6,4.914528778264369e-9,4.188980683740096e-9,5.745555946414595e-9 -LookupCoin/4/4/10,1.1928666809369907e-6,1.1916103904744267e-6,1.195695686873602e-6,5.7476910522975475e-9,3.558187498450454e-9,1.0467393690289418e-8 -LookupCoin/4/4/8,1.203582653497446e-6,1.202423914671103e-6,1.2047152726294545e-6,3.664306628139334e-9,3.104264253142358e-9,4.318388775789471e-9 -LookupCoin/4/4/10,1.2084679827135482e-6,1.206996019622262e-6,1.214027836858732e-6,8.226948327647268e-9,2.5153713838484612e-9,1.696432659805014e-8 -LookupCoin/4/4/10,1.2267797289998131e-6,1.2262703098660658e-6,1.2274384057461149e-6,1.9698454215779976e-9,1.6576190632875758e-9,2.5665926112104314e-9 -LookupCoin/4/4/9,1.217240806072733e-6,1.215964834128526e-6,1.2202844236669054e-6,6.107061895278018e-9,3.2397793222663967e-9,1.3099167126308328e-8 -LookupCoin/4/4/10,1.2056710515306366e-6,1.204254538908951e-6,1.206733200031426e-6,4.110966465288715e-9,3.252502432967364e-9,5.030311055395879e-9 -LookupCoin/4/4/11,1.2223353980960082e-6,1.2209166862802165e-6,1.2252746353501009e-6,6.480951807842912e-9,3.5034487409886137e-9,1.1574221631620568e-8 -LookupCoin/4/4/11,1.2381906860640788e-6,1.2373816720875036e-6,1.2390309550000634e-6,2.8631615772459806e-9,2.584711595331991e-9,3.2912099452583487e-9 -LookupCoin/4/4/9,1.2041700063443865e-6,1.202723266979627e-6,1.2079953584787903e-6,7.970720318115764e-9,2.6455179323248265e-9,1.4875884319605539e-8 -LookupCoin/4/4/11,1.2206119738308772e-6,1.2193183542760845e-6,1.2219578402103584e-6,4.421091993181346e-9,3.5314140955497563e-9,5.24459337396916e-9 -LookupCoin/4/4/10,1.198688570671991e-6,1.1968092788731975e-6,1.2002881672968227e-6,6.2467596841419095e-9,4.8838727318866745e-9,8.577949540828311e-9 -LookupCoin/4/4/9,1.2232712816681831e-6,1.222385109292051e-6,1.2243819421118973e-6,3.3287527982165607e-9,2.6530086716414487e-9,4.259887685515721e-9 -LookupCoin/4/4/10,1.2319188457093468e-6,1.231387927634095e-6,1.232453405915841e-6,1.8550053754712164e-9,1.5485091332345065e-9,2.2575283281189487e-9 -LookupCoin/4/4/11,1.2259649685593469e-6,1.2246129154364666e-6,1.2281652455358455e-6,5.816142161858434e-9,3.8951489061387544e-9,9.646584992867164e-9 -LookupCoin/4/4/9,1.220142726511326e-6,1.2189261873190347e-6,1.2213994758036873e-6,4.396649594965005e-9,3.778505570958797e-9,5.324803083927569e-9 -LookupCoin/4/4/11,1.2323923802385869e-6,1.2314441308735349e-6,1.2334798069320034e-6,3.490723498014477e-9,2.973056637385596e-9,4.581233410471864e-9 -LookupCoin/4/4/11,1.2157910391410865e-6,1.2144861124759398e-6,1.2172171945348252e-6,4.69167039176928e-9,4.107982909033791e-9,5.419100776764417e-9 -LookupCoin/4/4/11,1.2328985154623782e-6,1.231888251912911e-6,1.2338849794884602e-6,3.440244761247414e-9,2.9487504128928588e-9,4.095042364806446e-9 -LookupCoin/4/4/10,1.2125476453531075e-6,1.2115571273688314e-6,1.213813380078619e-6,3.838510243393416e-9,2.9102832815809218e-9,5.171613800260002e-9 -LookupCoin/4/4/11,1.2311677618980396e-6,1.2297267327679114e-6,1.232241892736664e-6,4.263137256955254e-9,3.4722101552463757e-9,5.727556907342786e-9 -ValueContains/4/1,1.108631478585558e-6,1.1077652148756856e-6,1.1095780707507516e-6,2.962047278539296e-9,2.4162243025980203e-9,3.6314232245633624e-9 -ValueContains/4/0,1.0225226778070809e-6,1.021594419066775e-6,1.0233771220888523e-6,2.903386621690029e-9,2.3700337419464644e-9,3.764812542120098e-9 -ValueContains/4/10,1.7251097731022483e-6,1.7217077584311812e-6,1.7290432063745155e-6,1.2504176745196251e-8,1.0689538466640446e-8,1.496722555714063e-8 -ValueContains/7/0,1.0235784262974995e-6,1.0227465999855973e-6,1.0244906985278278e-6,2.8917566010951786e-9,2.5231122576095735e-9,3.3727234776056936e-9 -ValueContains/7/0,1.0226450157806123e-6,1.0219602483898282e-6,1.0233104732466841e-6,2.245538471635945e-9,1.9317147620264348e-9,2.605014466382995e-9 -ValueContains/7/100,1.123983377436773e-5,1.1222673975558804e-5,1.1254568730097023e-5,5.2545069499185855e-8,4.2203479105756465e-8,6.81581825686575e-8 -ValueContains/10/0,1.0234815356516939e-6,1.0230323184094808e-6,1.0239782481409003e-6,1.6788403190347666e-9,1.3441788715659217e-9,2.3066110647896127e-9 -ValueContains/10/0,1.022244619801779e-6,1.0216088163183763e-6,1.0229490704321379e-6,2.2613060048559777e-9,1.9185721869678515e-9,2.7029739563952686e-9 -ValueContains/10/0,1.0187419478061535e-6,1.0180992699422179e-6,1.0194600390407757e-6,2.139824337180833e-9,1.6898653373863045e-9,2.626277907225411e-9 -ValueContains/10/1000,1.4095585241474237e-4,1.40817663844188e-4,1.4113608222739038e-4,5.341300107272371e-7,3.422739478520462e-7,7.303955664486585e-7 -ValueContains/5/200,1.750832958011064e-5,1.7483324946348768e-5,1.7531721338028892e-5,8.510690895587012e-8,7.098396376367275e-8,1.0344742833746426e-7 -ValueContains/1/0,1.020592742026185e-6,1.0195509509947287e-6,1.0217298205535592e-6,3.6166590105004055e-9,2.868519802715473e-9,5.003483216788357e-9 -ValueContains/4/0,1.0231213517874792e-6,1.0222083712608126e-6,1.0238784207289675e-6,2.7288594177355198e-9,2.1989322634766497e-9,3.4454860180383572e-9 -ValueContains/7/0,1.019703897420794e-6,1.0187441603659637e-6,1.021204124435237e-6,4.0538660814804425e-9,2.7584878102639575e-9,6.677707647772776e-9 -ValueContains/10/0,1.0206037033135496e-6,1.0200419460920349e-6,1.0211692962911852e-6,1.9432013088163367e-9,1.6471240403324677e-9,2.380931488825781e-9 -ValueContains/12/110,1.47200444837102e-5,1.470742072091629e-5,1.4735858043877813e-5,4.677837546673136e-8,4.061882525635276e-8,6.191283791581553e-8 -ValueContains/12/1313,1.7126666241371247e-4,1.7099080545307678e-4,1.7157898192302426e-4,9.68202018105592e-7,8.242358907525413e-7,1.1807674208216776e-6 -ValueContains/12/731,9.111141935328779e-5,9.089197590201364e-5,9.132384112555336e-5,7.192499505891549e-7,6.228624593803585e-7,8.584991672857017e-7 -ValueContains/12/3039,3.914054205241898e-4,3.904410118270601e-4,3.922776629299477e-4,3.087938735099823e-6,2.8023718189301774e-6,3.5020103424802864e-6 -ValueContains/8/29,3.53257811940542e-6,3.52865120291237e-6,3.5358542503453723e-6,1.2617613719759917e-8,1.0488847962062658e-8,1.5039190078498538e-8 -ValueContains/12/1387,1.7694455888490418e-4,1.767281190836957e-4,1.7716181771349444e-4,7.60547601643498e-7,6.586865242973147e-7,8.743651755609427e-7 -ValueContains/13/3588,4.7962670255488073e-4,4.787679277093584e-4,4.802711879365964e-4,2.609712886280009e-6,2.095427255079846e-6,3.1730649897826924e-6 -ValueContains/10/338,3.980823325383313e-5,3.974294686041632e-5,3.991431540039092e-5,2.869470839788121e-7,2.2147806515839266e-7,3.9098843554983166e-7 -ValueContains/12/2500,3.156930700588844e-4,3.153512578350851e-4,3.1608346679380553e-4,1.216935995051478e-6,1.0060533134261604e-6,1.4129709113305515e-6 -ValueContains/7/64,6.1035335386966655e-6,6.092514189843279e-6,6.1146805902651605e-6,3.752745203736218e-8,3.0816926658117025e-8,4.689103628448276e-8 -ValueContains/12/3182,4.10425232177756e-4,4.0978424672677785e-4,4.1100941942771976e-4,2.1224795575404285e-6,1.725067418676846e-6,2.8846629766683404e-6 -ValueContains/12/2076,2.591879470344235e-4,2.5894433377232303e-4,2.595175156188034e-4,9.487716829141452e-7,8.168184243920077e-7,1.109150937413403e-6 -ValueContains/12/1961,2.4850180952223173e-4,2.48326818085388e-4,2.487268295474985e-4,6.625368533225912e-7,5.448690968949389e-7,8.364963932806562e-7 -ValueContains/12/2980,3.809153778711491e-4,3.80474288223098e-4,3.8139115048989086e-4,1.5739831516032031e-6,1.320058965715184e-6,1.8193675785828874e-6 -ValueContains/11/205,2.5166582970979212e-5,2.508722790097956e-5,2.5232680826483777e-5,2.548368685620478e-7,2.1610800831303402e-7,2.9195695702762577e-7 -ValueContains/12/594,7.673364632125908e-5,7.665367709406551e-5,7.681009691834373e-5,2.607765906000331e-7,2.1370603129064027e-7,3.3549853027091536e-7 -ValueContains/13/3484,4.6410319453403715e-4,4.6352240032246974e-4,4.6466177647826575e-4,1.9822881797750665e-6,1.5041935527871901e-6,2.6046263177698874e-6 -ValueContains/13/33,4.8026691322994296e-6,4.797899512108592e-6,4.806995809846416e-6,1.532867093004693e-8,1.3252964970782209e-8,1.8330647941339627e-8 -ValueContains/10/144,1.6113413799843423e-5,1.6088900211313373e-5,1.6138758232005147e-5,8.455665267697632e-8,6.807650199999726e-8,1.066701763474308e-7 -ValueContains/12/2000,2.509994622932922e-4,2.5058199061113147e-4,2.513872301160663e-4,1.388573091390673e-6,1.182968307382935e-6,1.6605794288165797e-6 -ValueContains/13/2818,3.822259955150316e-4,3.813812302617948e-4,3.8284964292651405e-4,2.4073636397134105e-6,1.8388313198246135e-6,3.0702784321357275e-6 -ValueContains/12/1073,1.3256797382621142e-4,1.3244611935063065e-4,1.3270153786615604e-4,4.183392260824016e-7,3.5758255811849654e-7,4.992325654739546e-7 -ValueContains/11/1653,2.0171575123535486e-4,2.0130163845224583e-4,2.0208630582881662e-4,1.3722072907616494e-6,1.1703381245781852e-6,1.5637685576960973e-6 -ValueContains/13/1290,1.6512335952874338e-4,1.6494787773835452e-4,1.6527942337550919e-4,5.385093568127713e-7,4.4597118979784986e-7,6.74039437079728e-7 -ValueContains/12/1931,2.450869679238732e-4,2.447834902360666e-4,2.454533985092889e-4,1.1906080631538036e-6,9.653767871673086e-7,1.5841348439079563e-6 -ValueContains/12/113,1.4796083273877808e-5,1.4782517877194369e-5,1.4810289038988382e-5,4.903953145522286e-8,4.1858748560837425e-8,6.038102833364655e-8 -ValueContains/11/1466,1.7847298578394394e-4,1.7822258494108463e-4,1.7870184591731365e-4,8.261047563844038e-7,7.072730209232701e-7,9.673451728187376e-7 -ValueContains/12/243,2.912490900665435e-5,2.9089466363409e-5,2.9163214775750145e-5,1.2747698899741995e-7,1.092683913894289e-7,1.475739080764433e-7 -ValueContains/12/2725,3.5637934324297255e-4,3.555965345136923e-4,3.5712722853321747e-4,2.5189582340500527e-6,2.2113499787592496e-6,2.843821038015072e-6 -ValueContains/8/16,2.35511207934695e-6,2.3509261679096494e-6,2.3600084734896943e-6,1.5801598817434442e-8,1.2949378720804634e-8,2.193354996893263e-8 -ValueContains/11/1092,1.3551024067092528e-4,1.3528473912369104e-4,1.3574569731652835e-4,7.927947394548566e-7,6.224871129328504e-7,1.024184593891981e-6 -ValueContains/12/940,1.1546863743962826e-4,1.1531637820652565e-4,1.1568324418859595e-4,5.98922036386318e-7,5.057760604153949e-7,7.12357072934672e-7 -ValueContains/11/151,1.8906076066984876e-5,1.888605286651995e-5,1.892546686882719e-5,6.528839694424791e-8,5.551952808949426e-8,7.70546638326298e-8 -ValueContains/13/174,2.1718554560470205e-5,2.1688747834500112e-5,2.1759546711082756e-5,1.1509401305820709e-7,8.560452494599941e-8,1.8420460364946676e-7 -ValueContains/13/2449,3.23381191757996e-4,3.2304395484226116e-4,3.23865504904467e-4,1.3445274737734421e-6,9.809378950827171e-7,2.0706376713102894e-6 -ValueContains/12/2376,2.9768745493160816e-4,2.9709750010639663e-4,2.982641475913256e-4,1.97185260463418e-6,1.7263299212532655e-6,2.277879313627657e-6 -ValueContains/9/261,2.8124375075753676e-5,2.8076223121234054e-5,2.8179584052987132e-5,1.7441868120971644e-7,1.5610723993862283e-7,2.19321137505491e-7 -ValueContains/12/2011,2.545145959529957e-4,2.5414989211875556e-4,2.548397339152954e-4,1.1118180145894015e-6,9.172919101252035e-7,1.3906023094523358e-6 -ValueContains/13/3321,4.326743531138778e-4,4.3219164206709124e-4,4.3314184948469917e-4,1.637321748147985e-6,1.4308402728774026e-6,1.9454261689476855e-6 -ValueContains/12/1957,2.4444228524223726e-4,2.4414177372526606e-4,2.447615994648408e-4,1.037669844413743e-6,8.626781895343198e-7,1.299332016839317e-6 -ValueContains/12/144,1.8683203713856623e-5,1.8660725343598865e-5,1.8707839589944395e-5,7.657795393951314e-8,6.524837319600728e-8,9.255694497951914e-8 -ValueContains/11/47,5.943223770706193e-6,5.939942333033249e-6,5.9468407461967824e-6,1.1495571184973524e-8,9.450564677686707e-9,1.5318444359792727e-8 -ValueContains/12/1333,1.6572830370516635e-4,1.6550763129061263e-4,1.6610644552462428e-4,9.088824843141705e-7,5.400858217117058e-7,1.3835082448700263e-6 -ValueContains/13/4466,5.883552562353645e-4,5.877883356318053e-4,5.889456000900964e-4,2.0600754658523784e-6,1.837504876567189e-6,2.3998936154702603e-6 -ValueContains/12/483,6.211720183600771e-5,6.205000004948712e-5,6.222546127321215e-5,2.9302848770815617e-7,1.9395773199602564e-7,5.092671308489676e-7 -ValueContains/10/367,4.290681112071325e-5,4.283524055173336e-5,4.298151308282174e-5,2.418540264711245e-7,1.9804423368519547e-7,3.119019270822064e-7 -ValueContains/13/2280,3.001734441359379e-4,2.9964097767535305e-4,3.006303532594835e-4,1.7266774979727402e-6,1.5267491734511754e-6,2.062086789150401e-6 -ValueContains/10/836,9.757156053037398e-5,9.749455952320636e-5,9.766478670277101e-5,2.918808129765305e-7,2.411994749602096e-7,3.64682005836559e-7 -ValueContains/12/3712,4.8345409303365903e-4,4.8287458174537203e-4,4.8407638545173087e-4,2.11436941802913e-6,1.7748853284884427e-6,2.819296668716201e-6 -ValueContains/12/735,9.380987162873078e-5,9.370656738311049e-5,9.391220743009741e-5,3.291930700990749e-7,2.637603735476657e-7,4.4035632702576677e-7 -ValueContains/11/69,8.740065703800622e-6,8.73206918897248e-6,8.748144563675079e-6,2.7645984900076896e-8,2.4655318056668294e-8,3.200696702993197e-8 -ValueContains/13/2164,2.8226614728641016e-4,2.819592503007586e-4,2.825339221471438e-4,9.35048304631259e-7,7.830738177269742e-7,1.101422722293502e-6 -ValueContains/12/1681,2.0722746077054513e-4,2.067364561772548e-4,2.0783380144606467e-4,1.8476919280218599e-6,1.5917684248372793e-6,2.4035623332525304e-6 -ValueContains/12/74,9.751052467014276e-6,9.738153518141473e-6,9.769135587772237e-6,5.104564367509155e-8,4.137263888631603e-8,6.784579429681918e-8 -ValueContains/10/139,1.6490135612515683e-5,1.646480703042599e-5,1.6520899999498563e-5,9.386934931557386e-8,7.67497822489482e-8,1.1829754375337699e-7 -ValueContains/12/2017,2.666065542828511e-4,2.6634135768148617e-4,2.668356320274318e-4,8.068964397686883e-7,6.711601209431939e-7,1.0002714710368192e-6 -ValueContains/12/2345,3.065589415214533e-4,3.0600730248579386e-4,3.07235797718338e-4,2.1656848744943406e-6,1.6035862037654688e-6,3.3945380729893793e-6 -ValueContains/8/86,9.484026691964886e-6,9.4598571284918e-6,9.510257836634471e-6,8.318439396788857e-8,7.377201987458882e-8,9.645150938140082e-8 -ValueContains/13/1354,1.822301161569283e-4,1.8201339281833105e-4,1.8251883577336103e-4,8.601085159361935e-7,5.058945823465912e-7,1.4933572773367855e-6 -ValueContains/12/926,1.1739513464620693e-4,1.1728372233638402e-4,1.1750491914580553e-4,3.77534300353773e-7,3.166540812652804e-7,4.750385461143361e-7 -ValueContains/12/2090,2.59202825156191e-4,2.587524049856163e-4,2.5977063394204327e-4,1.6346722534750102e-6,1.228784598695743e-6,2.4281127075343204e-6 -ValueContains/9/32,4.2459803191325445e-6,4.242026073286432e-6,4.251233958314122e-6,1.4944535148921693e-8,1.0547364744468492e-8,2.381590299881724e-8 -ValueContains/11/127,1.4893903500281279e-5,1.4879635368636673e-5,1.4908393629647666e-5,4.9157868851736634e-8,4.05166848312878e-8,6.036358174975088e-8 -ValueContains/11/878,1.0625910363342736e-4,1.0619531477260937e-4,1.0631636611290635e-4,2.0157250984174788e-7,1.70722343760839e-7,2.388625189810645e-7 -ValueContains/12/178,2.2385596549019208e-5,2.2344359901498833e-5,2.2443371435391062e-5,1.6096578924614795e-7,1.0912652844682803e-7,2.677203076358949e-7 -ValueContains/11/18,2.840118752821919e-6,2.837080391571991e-6,2.8427475559187277e-6,9.808708515015208e-9,7.406932957825681e-9,1.2961147988223096e-8 -ValueContains/12/1823,2.2947306907293607e-4,2.2891246475553203e-4,2.3074600169947687e-4,2.7163159662133814e-6,1.3788317105269304e-6,5.278763202725306e-6 -ValueContains/13/3143,4.185460854876617e-4,4.180554359077283e-4,4.190122304553418e-4,1.6566285473210499e-6,1.274473801595235e-6,2.222609809552533e-6 -ValueContains/11/475,5.586002120314921e-5,5.57855068885348e-5,5.606353660949901e-5,3.7252999192278584e-7,1.8639352637885462e-7,7.537942536898368e-7 -ValueContains/12/899,1.0911510543915941e-4,1.0893985999913757e-4,1.0932246198183435e-4,6.461828497683495e-7,5.348516081396722e-7,7.701515408934036e-7 -ValueContains/11/496,6.038313848337131e-5,6.02934891081398e-5,6.0591102825611974e-5,4.4336132755104704e-7,2.0828679783401164e-7,8.575229338742292e-7 -ValueContains/11/361,4.261425919476745e-5,4.257334183453867e-5,4.2666218004492606e-5,1.4705722177034502e-7,1.1327731924623607e-7,2.1601785681198762e-7 -ValueContains/10/821,9.519906689615632e-5,9.50482279406412e-5,9.55544384289624e-5,7.585266683581104e-7,4.436027670088501e-7,1.4502570669156058e-6 -ValueContains/12/2360,2.9806416148304705e-4,2.976577021595465e-4,2.984329220097875e-4,1.3496905134254881e-6,1.1552122805976157e-6,1.6341921730276273e-6 -ValueContains/11/1385,1.6646542946938453e-4,1.6623537738069108e-4,1.669575587698667e-4,1.1053250292718617e-6,4.953007173179001e-7,2.134754554413376e-6 -ValueContains/11/1103,1.3070946562038287e-4,1.305995674430096e-4,1.3083698940945848e-4,3.9193902361530565e-7,3.4024189405871164e-7,4.795878958318945e-7 -ValueContains/12/698,8.937994899368279e-5,8.911848251141686e-5,9.000803198469786e-5,1.355470540757024e-6,5.400287598884221e-7,2.6474069137052814e-6 -ValueContains/11/554,6.627601682268413e-5,6.608794162470003e-5,6.651053743806329e-5,6.794380013654803e-7,5.919530415753716e-7,7.609734147094929e-7 -ValueContains/11/1462,1.7723794398198577e-4,1.7690560315032882e-4,1.780857235488939e-4,1.6320172898599461e-6,7.160673407762405e-7,3.38611869498516e-6 -ValueContains/12/3929,5.114683189390875e-4,5.108823344846136e-4,5.120638208675391e-4,1.932961928418717e-6,1.64601870345476e-6,2.2485445520791425e-6 -ValueContains/11/1501,1.8265889163916692e-4,1.824032717647174e-4,1.8319969887632852e-4,1.2075749286827018e-6,3.95646164331573e-7,1.971307347766472e-6 -ValueContains/12/2644,3.4395582842133246e-4,3.4325705139035396e-4,3.445663440351393e-4,2.2459324776977035e-6,1.9802970747187393e-6,2.6732846278087163e-6 -ValueContains/13/1710,2.2630468090120153e-4,2.2602447716197943e-4,2.266339650610043e-4,1.0092740699134108e-6,8.228956305963694e-7,1.192691783695068e-6 -ValueContains/12/2106,2.675136709449191e-4,2.6728519659863584e-4,2.678663190479629e-4,9.628740894834272e-7,7.145739340741488e-7,1.4617072197248056e-6 -ValueContains/12/1609,2.0673038091264975e-4,2.0635716210327303e-4,2.0767854207862254e-4,1.9902928646007943e-6,7.930160612545927e-7,4.187729151592018e-6 -ValueContains/11/218,2.558938785812943e-5,2.5573825772138e-5,2.560817331740303e-5,5.8839114721490037e-8,4.754059305360504e-8,7.466670389950067e-8 -ValueContains/13/2594,3.3996222275771686e-4,3.3938141060966236e-4,3.405730256196416e-4,2.0263240635596373e-6,1.849561163456103e-6,2.296176935049034e-6 -ValueContains/12/1074,1.4359801626900707e-4,1.4329196353462137e-4,1.4391744904026694e-4,1.0203786682314504e-6,8.723331275963217e-7,1.2293953659787833e-6 -ValueContains/12/2131,2.777805228279675e-4,2.773621617840402e-4,2.7818633853963153e-4,1.3442693284744144e-6,1.1440005022797041e-6,1.6111600957444925e-6 -ValueContains/13/1281,1.6251881979095228e-4,1.6240943290812208e-4,1.6264116305182474e-4,3.727089935119192e-7,3.1532670897460217e-7,4.5228713429259585e-7 -ValueContains/11/1650,2.0118004766971022e-4,2.0086339114876303e-4,2.0147528510632495e-4,1.0236706875408362e-6,9.290949238324031e-7,1.1654207959215543e-6 -ValueContains/9/31,4.2781508693801835e-6,4.269785122686407e-6,4.2862243167611635e-6,2.7783251437423314e-8,2.4200749761328568e-8,3.149628938222245e-8 -ValueContains/12/216,2.8241964850588032e-5,2.822599079371751e-5,2.826278147487947e-5,6.029384063373202e-8,4.712657894246709e-8,8.27284120655479e-8 -ValueContains/12/2165,2.736051884812679e-4,2.732775118521652e-4,2.7384602030101977e-4,9.913766064438774e-7,8.679131113234608e-7,1.1449757050205114e-6 -ValueContains/7/33,3.5450273448522575e-6,3.5426547002066714e-6,3.547478093019328e-6,8.56684391017993e-9,7.0940981903321665e-9,1.0350576327528435e-8 -ValueContains/9/390,4.341681285153536e-5,4.33652900440057e-5,4.347880175083487e-5,2.1029490564358867e-7,1.8254976974209643e-7,2.389207340295556e-7 -ValueContains/12/2883,3.6897212131933735e-4,3.6834144196343336e-4,3.695181587765242e-4,1.931807293907194e-6,1.7186713005105091e-6,2.283301180763716e-6 -ValueContains/11/706,8.395902905029007e-5,8.389215479156398e-5,8.402358160098535e-5,2.3131221739509136e-7,1.9956461239921385e-7,2.7884440531254544e-7 -ValueContains/12/1963,2.5456959977743844e-4,2.5438013013151067e-4,2.547825898452976e-4,6.669701647543044e-7,5.826304504253809e-7,7.844446853575884e-7 -ValueContains/12/1478,1.86861615625485e-4,1.8663747224495622e-4,1.871659571681982e-4,8.863695523773327e-7,7.105816352313534e-7,1.1626576023954886e-6 -ValueData/0,8.244454201615579e-7,8.23433293501754e-7,8.256213678834717e-7,3.742260219943055e-9,3.0812603017279235e-9,4.4146686349114295e-9 -ValueData/10,8.22117499973743e-7,8.211243746799455e-7,8.230308035842674e-7,3.0946590753686337e-9,2.610092909583127e-9,3.866927719317043e-9 -ValueData/100,8.221819452453929e-7,8.21048270247861e-7,8.233528399357892e-7,4.039505590682658e-9,3.5797568158276e-9,4.590950630092258e-9 -ValueData/500,8.163397290707937e-7,8.15773335425612e-7,8.169363817983215e-7,1.9366759680442005e-9,1.6074863504670616e-9,2.5286798414998783e-9 -ValueData/1000,8.202725937332094e-7,8.195662314381959e-7,8.209489335990944e-7,2.343092667215858e-9,1.866780979986148e-9,2.9344997517981207e-9 -ValueData/5000,8.161768980975118e-7,8.152867065992876e-7,8.171227681739271e-7,3.0743792985235683e-9,2.560499413734067e-9,3.905128238295594e-9 -ValueData/10000,8.186813343151185e-7,8.18190746694553e-7,8.1923209635009e-7,1.7785247185136356e-9,1.5296591921807378e-9,2.0944121326572294e-9 -ValueData/12,8.193056821477145e-7,8.184430190229789e-7,8.203090609240571e-7,3.1122913487637987e-9,2.6442795306026595e-9,3.664646733366502e-9 -ValueData/132,8.212467144493349e-7,8.199889551578968e-7,8.228647531471329e-7,4.560769672924292e-9,3.743388186459986e-9,5.544331817222215e-9 -ValueData/400,8.205709408140604e-7,8.196287165179266e-7,8.215035594245682e-7,3.2079146580475585e-9,2.8857475081103714e-9,3.7035076364625423e-9 -ValueData/2988,8.201412297157129e-7,8.194534771379229e-7,8.208311526198327e-7,2.2066286828884032e-9,1.8519239429052266e-9,2.744954445779122e-9 -ValueData/89540,8.20872414590064e-7,8.199366938198826e-7,8.219862584692773e-7,3.3544584077178134e-9,2.7271437719638854e-9,4.057235122642681e-9 -ValueData/72320,8.224876982589812e-7,8.217298357183517e-7,8.234034779155377e-7,2.814181928775027e-9,2.3008078917358744e-9,3.6703684541045173e-9 -ValueData/27300,8.185074530743931e-7,8.177207414511934e-7,8.195166970852875e-7,2.8747827840376272e-9,2.228274244115483e-9,3.767679517871087e-9 -ValueData/244570,8.20454645354226e-7,8.194943063222285e-7,8.215223282266286e-7,3.521570631049841e-9,2.8542659819307667e-9,4.4007321696312755e-9 -ValueData/44448,8.239843871228996e-7,8.229408304588001e-7,8.250463066111123e-7,3.6072233159518366e-9,3.1863501594039706e-9,4.239201330338147e-9 -ValueData/170352,8.2455779180604e-7,8.230398608899784e-7,8.263277645365452e-7,5.4439937195030216e-9,4.7440924636577775e-9,6.047871371268118e-9 -ValueData/218152,8.230271914413192e-7,8.21546465127632e-7,8.245481566758423e-7,4.872994695985695e-9,4.236411658578428e-9,5.739916731984539e-9 -ValueData/425952,8.203457569797886e-7,8.19608072590304e-7,8.212784742976612e-7,2.743008529127879e-9,2.1674535399962145e-9,3.6588883550751806e-9 -ValueData/279538,8.195474882132555e-7,8.182573637368075e-7,8.209206901647557e-7,4.7165491844897005e-9,3.994039576916133e-9,5.677341148669239e-9 -ValueData/39820,8.208435129037743e-7,8.203007288065669e-7,8.214118615989832e-7,1.8935718234671093e-9,1.5489949847948677e-9,2.3821560679490826e-9 -ValueData/83636,8.201310288599092e-7,8.191933907563492e-7,8.214508364266832e-7,3.844975905778905e-9,2.5203152536153045e-9,5.552414853322374e-9 -ValueData/299398,8.232310397117945e-7,8.224220181220569e-7,8.240706777609594e-7,2.7912162770180534e-9,2.2671647291529514e-9,3.52962515306279e-9 -ValueData/54530,8.27603661647116e-7,8.260768510784006e-7,8.289428648332192e-7,4.643217215145481e-9,3.908397149790088e-9,5.43553475182136e-9 -ValueData/18886,8.215021753586944e-7,8.207844208954321e-7,8.223623732542666e-7,2.769837818117766e-9,2.3351167741817255e-9,3.2881789082136985e-9 -ValueData/93450,8.204190446392335e-7,8.192333752020768e-7,8.215388016131464e-7,3.936176937364659e-9,3.503796320690723e-9,4.4439553879784326e-9 -ValueData/228542,8.208423266679402e-7,8.202045502020515e-7,8.215538621190297e-7,2.1588137621830542e-9,1.81563676458015e-9,2.597167509087378e-9 -ValueData/150792,8.235605511246239e-7,8.22789421905344e-7,8.244472970345505e-7,2.8627335498439904e-9,2.416784539573174e-9,3.4745986889503555e-9 -ValueData/49024,8.246790078242883e-7,8.235423991738796e-7,8.257851883468644e-7,3.7053305326945513e-9,3.1156817522826614e-9,4.495466587739984e-9 -ValueData/132328,8.270862423730109e-7,8.260851651326046e-7,8.281607063752865e-7,3.6126580953983926e-9,3.0769289521676575e-9,4.3619589383346215e-9 -ValueData/18864,8.214483124148549e-7,8.203312994013875e-7,8.225392862725836e-7,3.728587256896244e-9,3.3352565281065484e-9,4.299462069024661e-9 -ValueData/71208,8.203695247082273e-7,8.198937044013412e-7,8.210256490927769e-7,1.8923463489600707e-9,1.5012479670306166e-9,2.4545288715178135e-9 -ValueData/211508,8.266460926647436e-7,8.258964350034215e-7,8.272677997383069e-7,2.320109563559006e-9,2.0228007978372696e-9,2.7652169008190787e-9 -ValueData/56516,8.24615190392142e-7,8.238369406932445e-7,8.257196357657181e-7,3.171398965448706e-9,2.625831068963112e-9,3.9824482222818364e-9 -ValueData/48298,8.229631222484406e-7,8.217398931360068e-7,8.244732355896116e-7,4.500108807130222e-9,3.6629535584917373e-9,5.61723215800674e-9 -ValueData/13362,8.222133015780036e-7,8.21342126417965e-7,8.23148488231374e-7,2.9388660991135616e-9,2.415861094485281e-9,3.6074160877605393e-9 -ValueData/126555,8.199337600220388e-7,8.192821802956436e-7,8.206784815869801e-7,2.3218368437302743e-9,1.9517863055085853e-9,2.756340032781499e-9 -ValueData/51465,8.25975433176981e-7,8.250203522209206e-7,8.268473970007414e-7,3.0255571985196647e-9,2.4781397761879002e-9,3.6916506509221513e-9 -ValueData/231702,8.268449630882003e-7,8.261046060231018e-7,8.279694674047836e-7,3.02152797067613e-9,2.336918651658897e-9,3.86203520866395e-9 -ValueData/316,8.332810715075529e-7,8.317957238737365e-7,8.343598788636821e-7,4.23958540939879e-9,3.329696694775728e-9,5.2126610397838e-9 -ValueData/83655,8.300648237861331e-7,8.292977837361904e-7,8.30911931674328e-7,2.684590380801402e-9,2.2286786714087038e-9,3.19334125980831e-9 -ValueData/27500,8.252076029896516e-7,8.244011763404174e-7,8.258718545881323e-7,2.41302974832356e-9,1.9691337749911034e-9,2.9578090599609055e-9 -ValueData/234494,8.224910899592814e-7,8.218633796931829e-7,8.230605742960272e-7,1.993440465547803e-9,1.7361391040241124e-9,2.3066368259341814e-9 -ValueData/71959,8.293806091070653e-7,8.285684459368036e-7,8.303841255915646e-7,3.0245687195475286e-9,2.1494130161949623e-9,3.847952146552444e-9 -ValueData/2187,8.224824664247516e-7,8.218106719402002e-7,8.235446002173017e-7,2.6992902993182545e-9,2.0680735821154223e-9,4.183177881307455e-9 -ValueData/57951,8.280962854762504e-7,8.273096515559853e-7,8.292096572984379e-7,3.0648220168982696e-9,2.3634004258585118e-9,3.8444551113794714e-9 -ValueData/30744,8.326082276323256e-7,8.316342915216535e-7,8.335562323476703e-7,3.2862066836587618e-9,2.792643869494247e-9,3.994537454396677e-9 -ValueData/62122,8.233358171747173e-7,8.22710641085643e-7,8.241742614788164e-7,2.3582069481678468e-9,1.6105514488019716e-9,3.765127064703871e-9 -ValueData/9807,8.271909739306661e-7,8.26031957297151e-7,8.282322603567579e-7,3.6986066654931186e-9,3.1762089140800916e-9,4.468497957034641e-9 -ValueData/22116,8.256482182069902e-7,8.245441581830742e-7,8.269202063096741e-7,3.963698026375453e-9,3.325220536382015e-9,4.6280316916492655e-9 -ValueData/116298,8.224519503002362e-7,8.217488428876309e-7,8.231750165689685e-7,2.3146032600676372e-9,1.866144095262344e-9,3.0358759884507236e-9 -ValueData/337953,8.255115322491715e-7,8.24668725228097e-7,8.266546206408221e-7,3.260357656962594e-9,2.541021079907588e-9,4.055745705991836e-9 -ValueData/7905,8.330641809091734e-7,8.322898310300378e-7,8.338620508706807e-7,2.665723602996034e-9,2.3305267033388244e-9,3.518143536635139e-9 -ValueData/134090,8.261427399950324e-7,8.251366006904944e-7,8.272431352068293e-7,3.5507224178490417e-9,3.1785415138412026e-9,3.992986123698293e-9 -ValueData/83006,8.254214837876659e-7,8.242247408602064e-7,8.273285790340231e-7,4.887168627229412e-9,3.842603276758196e-9,6.342713996078145e-9 -ValueData/36540,8.280149814010451e-7,8.271494631448716e-7,8.288838774486129e-7,2.9044778093717868e-9,2.2815144230384666e-9,3.7251399021511512e-9 -ValueData/306125,8.306982652566297e-7,8.297981435526217e-7,8.319348409103995e-7,3.43613287520932e-9,2.8138998792480703e-9,4.191248781773384e-9 -ValueData/139125,8.207838888057991e-7,8.194250975173603e-7,8.222616783044705e-7,4.5139079966325845e-9,3.802401973556008e-9,5.290941278704563e-9 -ValueData/274164,8.231051811599564e-7,8.223282303695108e-7,8.240756915156489e-7,2.9623909454241763e-9,2.171006494735078e-9,4.017682238102333e-9 -ValueData/114454,8.246612985793178e-7,8.236875269735684e-7,8.262534582915164e-7,3.834620588845891e-9,2.6955386866157867e-9,5.704675853113967e-9 -UnValueData/4,8.814707544381939e-7,8.804725070677484e-7,8.823471365443689e-7,2.9482977593301646e-9,2.44628385001842e-9,3.929069382146581e-9 -UnValueData/146,2.5870907863963996e-6,2.5855718088559514e-6,2.5889492970240463e-6,6.128345195836809e-9,5.023713854759932e-9,7.274702316360512e-9 -UnValueData/1424,1.7206064639310656e-5,1.7191504653194482e-5,1.722024845553145e-5,4.734386123201548e-8,3.874418654003048e-8,6.145127714531319e-8 -UnValueData/7104,8.362469167695932e-5,8.357209407036697e-5,8.367602197250932e-5,1.8895665609682302e-7,1.530185031734147e-7,2.5531833574257767e-7 -UnValueData/14204,1.704310798406903e-4,1.7025902337178755e-4,1.705781111899975e-4,5.529583631219131e-7,4.660361418782681e-7,6.810892709873758e-7 -UnValueData/71004,9.58574670300882e-4,9.536919722540894e-4,9.625114724557927e-4,1.4672996528760974e-5,1.1411848643366675e-5,1.8350279003937462e-5 -UnValueData/142004,2.342476377270298e-3,2.3291587332260034e-3,2.3517155756466873e-3,3.5285917997363786e-5,2.6968686170481196e-5,4.787044439995054e-5 -UnValueData/196,2.926389063362384e-6,2.924436663100386e-6,2.9285915595789803e-6,6.92710145446734e-9,5.9905018568068284e-9,7.89335432373771e-9 -UnValueData/1852,2.255370626227775e-5,2.254000902066636e-5,2.256952939021159e-5,4.823634389334619e-8,4.105888712808848e-8,5.8757201721543305e-8 -UnValueData/5444,6.815777869204673e-5,6.812298969192928e-5,6.818444105177809e-5,1.0411354465938307e-7,8.278938422154348e-8,1.4772807649247813e-7 -UnValueData/39280,6.47318627124663e-4,6.469757140611054e-4,6.476807669879141e-4,1.2166450200006558e-6,1.0542219006306254e-6,1.4478891009580309e-6 -UnValueData/1172904,3.0913773945298866e-2,3.0393434972703103e-2,3.1183828224595547e-2,8.037785360051158e-4,3.809514367981205e-4,1.4736308924952557e-3 -UnValueData/945588,2.39508395471181e-2,2.3600728393489128e-2,2.4202383973430504e-2,6.37108862819296e-4,4.018417348134392e-4,1.0454531348408232e-3 -UnValueData/355804,8.589346906253056e-3,8.524265366301657e-3,8.632774953118594e-3,1.5263747812641247e-4,1.083570235534613e-4,2.4500294211551426e-4 -UnValueData/3187346,0.10331826001689876,0.10062176479943215,0.1063046103860769,4.623701246221441e-3,3.3147794955261417e-3,6.810944977092971e-3 -UnValueData/583384,1.2765699904511438e-2,1.2702924340086606e-2,1.2834570607761891e-2,1.655230521421776e-4,1.2914846623880968e-4,2.2826538877161433e-4 -UnValueData/2222068,6.989666920760775e-2,6.870708700254068e-2,7.155345413608082e-2,2.5402400204450606e-3,1.2999895673927813e-3,4.329297041380369e-3 -UnValueData/2844824,9.02636660804982e-2,8.772392780249001e-2,9.149031602536087e-2,2.7553926791901644e-3,9.77971278212264e-4,4.714805068545969e-3 -UnValueData/5548516,0.18253146313751736,0.17470398537504175,0.1877387719642785,8.552592291424263e-3,3.6792108869790827e-3,1.1786526999305118e-2 -UnValueData/3640886,0.12065583245975653,0.11773332931722204,0.12304799077433667,4.2884992990610766e-3,3.128731799551303e-3,5.9372428520211564e-3 -UnValueData/518984,1.2888476639080373e-2,1.2822252847393838e-2,1.2958869372761368e-2,1.8010054490204602e-4,1.3307831273761398e-4,2.529136962109431e-4 -UnValueData/1097016,2.7437004902670075e-2,2.7103162513727724e-2,2.7624881382781043e-2,5.435083322307567e-4,2.7771501704805534e-4,8.921493500185314e-4 -UnValueData/3900362,0.12702963936067785,0.12166317274040055,0.1295020544178052,5.414563993547031e-3,2.189425127296667e-3,8.656674282930344e-3 -UnValueData/711174,1.804444737709224e-2,1.7784331353898924e-2,1.81642280071127e-2,3.834768337259202e-4,2.1407666449012728e-4,6.442796445132827e-4 -UnValueData/251486,4.702617409392112e-3,4.6735559776439894e-3,4.725891504375187e-3,7.824150976483432e-5,6.13024428523557e-5,9.973583586405014e-5 -UnValueData/1219054,3.491563529296652e-2,3.424975840783657e-2,3.607312922949248e-2,1.7601257382396946e-3,8.400178103566094e-4,2.9232166641789755e-3 -UnValueData/2976546,9.781775035065102e-2,9.54381991652082e-2,9.943876222081521e-2,3.208618717052165e-3,1.9203822695934123e-3,4.803329131698663e-3 -UnValueData/1970188,5.968214018489485e-2,5.872649675449168e-2,6.093962713876137e-2,1.978623386144956e-3,1.2055103813255286e-3,3.1743286575666332e-3 -UnValueData/638852,1.6417998928983827e-2,1.6223209933320774e-2,1.6511501737594667e-2,3.239221957399417e-4,1.5686490990686526e-4,6.141584823290552e-4 -UnValueData/1731692,5.088152643125891e-2,5.0171259261978705e-2,5.1946749241449736e-2,1.688541113403487e-3,8.588593850525171e-4,2.87150119580516e-3 -UnValueData/246964,5.3374522450953e-3,5.317564818591537e-3,5.353340740640756e-3,5.633056018805761e-5,4.4452772430179823e-5,7.595476521522324e-5 -UnValueData/928804,2.4988392961184307e-2,2.462135908570554e-2,2.5925185025086464e-2,1.2115037931675636e-3,3.7166156225736254e-4,2.239260433211775e-3 -UnValueData/2759640,8.67670032566428e-2,8.438685280603489e-2,8.840050996495559e-2,3.1872167096294863e-3,1.8750568111371311e-3,5.390424663519083e-3 -UnValueData/744264,1.6457150792767963e-2,1.6184644889171276e-2,1.6583589895754078e-2,4.07752884052212e-4,2.1850985011782092e-4,6.465703636997289e-4 -UnValueData/637226,1.3667107270261053e-2,1.3545497198704624e-2,1.372844954411446e-2,2.1996111464304513e-4,1.4250632227681524e-4,3.708315464387721e-4 -UnValueData/178426,3.3127857359065934e-3,3.300976824042302e-3,3.3215405614025763e-3,3.366884248058469e-5,2.271248059427335e-5,4.8176124234948854e-5 -UnValueData/1654423,4.8417158025112865e-2,4.785748068257738e-2,4.941144782419231e-2,1.3894597794297575e-3,6.942690917814364e-4,2.409704641006147e-3 -UnValueData/670741,1.6957949146630364e-2,1.6822310381670726e-2,1.7033353225931157e-2,2.652305922367694e-4,1.6278290234390206e-4,4.364338064389038e-4 -UnValueData/3018478,9.937505917849489e-2,9.721944732989826e-2,0.10163280513955567,3.7174569863218684e-3,2.5786680729009146e-3,5.131090948343308e-3 -UnValueData/5060,5.751885233077096e-5,5.748333393852673e-5,5.7557358593790856e-5,1.2290676381525568e-7,9.725157826066853e-8,1.5289857702614492e-7 -UnValueData/1092667,2.9660856546798665e-2,2.9355879647692627e-2,3.0306183135092528e-2,9.217230672598662e-4,4.6541204946275546e-4,1.5653003850173198e-3 -UnValueData/360504,7.663426183941959e-3,7.62956825836068e-3,7.696136881811834e-3,9.630149250118415e-5,7.297761833152014e-5,1.2816562515843873e-4 -UnValueData/3057474,9.757587071261788e-2,9.486766001653103e-2,9.949748440887089e-2,3.629152805905121e-3,1.9718028530284785e-3,5.573670378283491e-3 -UnValueData/938195,2.5516736772938316e-2,2.529523548437108e-2,2.577993551022413e-2,5.507883169090115e-4,3.861088032048023e-4,7.754657796028178e-4 -UnValueData/31351,3.794440277720582e-4,3.792986902989907e-4,3.7964085274660336e-4,5.636735065125375e-7,4.4833077870519565e-7,8.228939567060915e-7 -UnValueData/758443,1.8391077717100763e-2,1.810849422684369e-2,1.8913655447828085e-2,8.794417728764309e-4,4.5352513329323895e-4,1.4082372728346153e-3 -UnValueData/402700,8.883993653910516e-3,8.856349934916352e-3,8.915581600179811e-3,8.803255766046738e-5,6.184630473679648e-5,1.2884264703395465e-4 -UnValueData/815966,1.9293342965148588e-2,1.9042203329400716e-2,1.9793484281817646e-2,7.92549742002015e-4,3.7918566505787664e-4,1.3736516216592172e-3 -UnValueData/127747,3.1306911500748776e-3,3.1220245193965502e-3,3.1369653229303073e-3,2.466245089189588e-5,1.8400103480861507e-5,3.470525525801844e-5 -UnValueData/288676,6.645767467209073e-3,6.6207958661609724e-3,6.6699330461812475e-3,7.106967999341454e-5,5.009579306966509e-5,1.1574905918210243e-4 -UnValueData/1519546,4.4455198764938864e-2,4.3881514973162936e-2,4.5144713611423894e-2,1.2651091613634833e-3,7.713333009244095e-4,2.033757739072662e-3 -UnValueData/4404565,0.1424591612469937,0.1381316568170275,0.14481412209126923,4.674712272678646e-3,2.4120624506187415e-3,6.85872679509471e-3 -UnValueData/108349,1.7981659186657182e-3,1.794709118269817e-3,1.802130635380069e-3,1.2513170505276615e-5,9.021600874330734e-6,2.0156426360822056e-5 -UnValueData/1749534,5.321115732037697e-2,5.2342570794778116e-2,5.387104092141948e-2,1.4791590671407657e-3,9.110922030450458e-4,2.4373989399546774e-3 -UnValueData/1085550,2.837395804942373e-2,2.8186313041170894e-2,2.8571790223544384e-2,4.22142981227161e-4,3.127639213843074e-4,5.959412566434413e-4 -UnValueData/477544,1.096403937194356e-2,1.0872864607374598e-2,1.1015912021362047e-2,1.796792621482667e-4,1.1109966782409862e-4,2.9949710066597357e-4 -UnValueData/3988929,0.13036026550814442,0.12702548788372606,0.13358291170637435,5.277650991401465e-3,3.6155023029658534e-3,8.317242999952778e-3 -UnValueData/1813129,5.668536234038809e-2,5.589823921392154e-2,5.7248521915470314e-2,1.2032278475752258e-3,6.468777111526906e-4,1.9686013537490604e-3 -UnValueData/3572980,0.1156469710891889,0.11202591267259171,0.11812273848945984,4.976948988572253e-3,2.5708389602726515e-3,7.849883215477199e-3 -UnValueData/1495622,4.294574041476179e-2,4.2345256325965905e-2,4.34389490400093e-2,1.121339863668914e-3,7.021794540026286e-4,1.7051035518656247e-3 +LookupCoin/4/4/1,1.1785774616356424e-6,1.176759675417735e-6,1.1806482145561586e-6,6.518952731910493e-9,5.357289431456435e-9,7.516610936744955e-9 +LookupCoin/4/4/4,1.1915790498342047e-6,1.1904495568836964e-6,1.1929163022259065e-6,4.046963753072825e-9,3.253765563594344e-9,4.891006325615181e-9 +LookupCoin/4/4/4,1.2197204026484044e-6,1.218075576538306e-6,1.2212484144754842e-6,5.507469943923652e-9,4.712716305594179e-9,6.232237587140286e-9 +LookupCoin/4/4/6,1.2252608227748506e-6,1.2235791774580782e-6,1.2277132720598693e-6,6.957151909632548e-9,5.605938174417417e-9,9.311603666532503e-9 +LookupCoin/4/4/7,1.2418602679642457e-6,1.2407303791623337e-6,1.2431197653276957e-6,3.99250649949147e-9,3.411918822901681e-9,4.834889142361592e-9 +LookupCoin/4/4/9,1.252436317521741e-6,1.2507551577049629e-6,1.2539429485067685e-6,5.3310387004146845e-9,4.3975434417027795e-9,6.5714921376763815e-9 +LookupCoin/4/4/10,1.2537401387503317e-6,1.252648286911128e-6,1.2547423953179683e-6,3.4440238105385005e-9,2.9534534499958296e-9,4.125613685308116e-9 +LookupCoin/4/4/3,1.2057215465409478e-6,1.2044460334597588e-6,1.207164989903122e-6,4.686865699769265e-9,3.6827553294261967e-9,6.000559447477795e-9 +LookupCoin/4/4/4,1.2079863804193127e-6,1.2062767393037788e-6,1.209455432605573e-6,5.542921404445267e-9,4.568400282135385e-9,6.74255559935788e-9 +LookupCoin/4/4/5,1.2078112588041638e-6,1.2065310847461148e-6,1.2090989698102615e-6,4.2655061709200194e-9,3.589523090690231e-9,5.114850390355415e-9 +LookupCoin/4/4/10,1.251879129959111e-6,1.250448654698612e-6,1.2532910150820974e-6,4.850496728584338e-9,4.165199613881152e-9,5.683130521733482e-9 +LookupCoin/4/4/10,1.2559926083679484e-6,1.254502947718635e-6,1.2578907233923837e-6,5.566293829457432e-9,4.442793925127361e-9,6.972096189106762e-9 +LookupCoin/4/4/10,1.249098034119151e-6,1.2478638570938712e-6,1.2502401232848524e-6,3.85368192327935e-9,2.873830349334046e-9,4.877165673298007e-9 +LookupCoin/4/4/10,1.2509925558129945e-6,1.2494668973874963e-6,1.252556539885775e-6,5.337231950101119e-9,4.632577095408978e-9,6.383237841142989e-9 +LookupCoin/4/4/8,1.2233863922980728e-6,1.2217812130109416e-6,1.2253165110213577e-6,5.730758948653033e-9,4.8897490173656e-9,6.711697262501028e-9 +LookupCoin/4/4/10,1.2450032774185982e-6,1.2433505660563716e-6,1.2465189122949562e-6,5.488467504687887e-9,4.576582598573407e-9,6.894353701471729e-9 +LookupCoin/4/4/9,1.2468692466371783e-6,1.2461110966661758e-6,1.2478362619198501e-6,2.8920564681241693e-9,2.140996026586959e-9,4.042383292140468e-9 +LookupCoin/4/4/9,1.2645472621553918e-6,1.2628552137734403e-6,1.266814826437389e-6,6.692994388511391e-9,4.682033831438571e-9,1.114015606044514e-8 +LookupCoin/4/4/10,1.2566114821524705e-6,1.2557979400132496e-6,1.2574416492611602e-6,2.8610749903932396e-9,2.370368893421804e-9,3.5957306026909866e-9 +LookupCoin/4/4/10,1.2446254571928705e-6,1.2432512446989087e-6,1.2462616356472978e-6,5.177873574907882e-9,4.251966011717402e-9,6.355357327734962e-9 +LookupCoin/4/4/9,1.2444712146667099e-6,1.2422851093807456e-6,1.2470313061995245e-6,8.194720226422199e-9,7.417313720403413e-9,9.047922562422956e-9 +LookupCoin/4/4/10,1.2452922783829327e-6,1.2426782389000752e-6,1.2478871011039333e-6,8.69536851787927e-9,7.561027447830772e-9,1.0288038570035432e-8 +LookupCoin/4/4/10,1.2569093085899734e-6,1.2550653565207963e-6,1.2587022251705878e-6,6.3185708688609255e-9,5.514510441474091e-9,6.972988202607048e-9 +LookupCoin/4/4/10,1.2489826143715561e-6,1.2469685265561477e-6,1.2511630328057974e-6,7.100201363756892e-9,6.062358859136152e-9,8.66780270137926e-9 +LookupCoin/4/4/10,1.2452307795244152e-6,1.2444393916136893e-6,1.2461276908911376e-6,2.8381522217855915e-9,2.3872805232416765e-9,3.541533286949262e-9 +LookupCoin/4/4/5,1.2116606690899845e-6,1.209339198220783e-6,1.214589099273679e-6,9.032701335084981e-9,6.469230446272719e-9,1.590705235161601e-8 +LookupCoin/4/4/10,1.2710664848979752e-6,1.270126409383351e-6,1.2718915282049792e-6,2.8805540126875373e-9,2.3609698581581498e-9,3.467537330202418e-9 +LookupCoin/4/4/10,1.247569773426005e-6,1.245984275441814e-6,1.2496340754585717e-6,6.178591924990118e-9,4.9687538625385045e-9,7.447855996720255e-9 +LookupCoin/4/4/10,1.2595327258856138e-6,1.257935347781212e-6,1.2615465574208554e-6,5.995181661489849e-9,5.303650389083819e-9,6.79076639044681e-9 +LookupCoin/4/4/10,1.2491519336150866e-6,1.2472836812943233e-6,1.2511186254134189e-6,6.405006746538472e-9,5.695303745282024e-9,7.511945087364079e-9 +LookupCoin/4/4/9,1.2330398815253764e-6,1.2314827124398794e-6,1.234667542374372e-6,5.0953014783408485e-9,4.314569061537632e-9,6.431816983040218e-9 +LookupCoin/4/4/10,1.2584576728692458e-6,1.2566493818869613e-6,1.2598562714729147e-6,5.431724556407445e-9,4.75170101830403e-9,6.114342715438356e-9 +LookupCoin/4/4/8,1.2413153539822471e-6,1.2399259325158052e-6,1.2425207755239365e-6,4.445393838925636e-9,3.557600260889822e-9,5.453093256078417e-9 +LookupCoin/4/4/9,1.2546261146504752e-6,1.2536158679696334e-6,1.255661903024827e-6,3.5541084290018065e-9,2.9669833365451164e-9,4.456939978811789e-9 +LookupCoin/4/4/10,1.2520819257388385e-6,1.2508517263032954e-6,1.253314810552611e-6,4.18853433645004e-9,3.2375446221573444e-9,5.46068233337296e-9 +LookupCoin/4/4/9,1.2023990095945583e-6,1.2010986638653741e-6,1.2033492056604433e-6,3.607898542791623e-9,2.8144313526293303e-9,4.761587244004819e-9 +LookupCoin/4/4/10,1.250352076611688e-6,1.2489617040094347e-6,1.2516956063426574e-6,4.343586475072123e-9,3.6373382379341278e-9,5.352167899921192e-9 +LookupCoin/4/4/10,1.2531302054775177e-6,1.251180583674485e-6,1.2550644175453815e-6,6.3689806774659485e-9,5.543418685211649e-9,7.406072641207062e-9 +LookupCoin/4/4/9,1.2607861639944634e-6,1.2591039391746295e-6,1.262376754456549e-6,5.631413910392014e-9,4.873286642434556e-9,6.670239708059327e-9 +LookupCoin/4/4/10,1.2472815190346465e-6,1.2459804024642142e-6,1.2485571798697857e-6,4.357007238786791e-9,3.2631443656846903e-9,6.32552917556167e-9 +LookupCoin/4/4/9,1.2322042458451905e-6,1.230834730587035e-6,1.2336578108589346e-6,4.62169481769082e-9,3.632231204787403e-9,6.239122053129638e-9 +LookupCoin/4/4/9,1.2335733297697559e-6,1.2322460575702047e-6,1.2351153263372751e-6,4.847298295614193e-9,4.0828339383388015e-9,5.5874083333866524e-9 +LookupCoin/4/4/8,1.233413928611683e-6,1.2320348630372408e-6,1.2351257625156452e-6,5.003040272936572e-9,3.6701757631765112e-9,7.430463710167003e-9 +LookupCoin/4/4/9,1.2417609266633647e-6,1.2403519493393569e-6,1.2434541566079187e-6,5.031564754217582e-9,4.0240365091248306e-9,7.0840199812251356e-9 +LookupCoin/4/4/10,1.2531833500305536e-6,1.251925739940696e-6,1.2547792104092452e-6,4.630799965369312e-9,3.6914495833890097e-9,5.8681985579824406e-9 +LookupCoin/4/4/10,1.2462406348076252e-6,1.2439528066883627e-6,1.248600103616122e-6,8.013281486073616e-9,7.0979163851705234e-9,9.118216596200202e-9 +LookupCoin/4/4/8,1.2391228982048233e-6,1.2371343815590253e-6,1.241158101936117e-6,6.403733178552462e-9,5.596147443935133e-9,7.60968388905787e-9 +LookupCoin/4/4/9,1.2487485103365863e-6,1.2468732027369702e-6,1.2505639777254846e-6,6.184300800812291e-9,5.289566799969568e-9,7.158283370012036e-9 +LookupCoin/4/4/10,1.2429739536371046e-6,1.2414013103601145e-6,1.24574610236691e-6,6.948148263932397e-9,4.631343316733535e-9,1.1325999463368464e-8 +LookupCoin/4/4/10,1.2470182416765948e-6,1.2449623677385142e-6,1.2490389144770656e-6,7.140056517797011e-9,6.273113025798219e-9,8.234385642190435e-9 +LookupCoin/4/4/9,1.2180874857009812e-6,1.2170583876488178e-6,1.219913566991649e-6,4.4581934270227975e-9,3.1166224970646416e-9,7.18505389207211e-9 +LookupCoin/4/4/9,1.2419777826748983e-6,1.241153111207899e-6,1.242896719498676e-6,2.9101524915145297e-9,2.440436622888798e-9,3.673617181095772e-9 +LookupCoin/4/4/10,1.2416648688754131e-6,1.2403751130458364e-6,1.24309182764266e-6,4.385889790965116e-9,3.465870149371959e-9,5.937415720897578e-9 +LookupCoin/4/4/8,1.2317755110963195e-6,1.2296147412105458e-6,1.2337141754094538e-6,6.889872441606145e-9,6.1250358935872e-9,8.481318132612718e-9 +LookupCoin/4/4/10,1.2415389402914188e-6,1.2401643773486892e-6,1.242919629240299e-6,4.563755951362882e-9,3.769687443084677e-9,6.0684952291023795e-9 +LookupCoin/4/4/9,1.2475874527185102e-6,1.246416870807616e-6,1.2485656602935343e-6,3.671091402713257e-9,2.844615768485536e-9,4.673756345684205e-9 +LookupCoin/4/4/10,1.2492509162384606e-6,1.2476284092128534e-6,1.2510902029115656e-6,5.521799485791726e-9,4.677685901772419e-9,6.527274147220636e-9 +LookupCoin/4/4/10,1.2427450026656707e-6,1.2407219410327528e-6,1.244694170970827e-6,6.478591779094514e-9,5.774544148817447e-9,7.457783845616137e-9 +LookupCoin/4/4/10,1.2405678380218471e-6,1.239472517052258e-6,1.2419806027735965e-6,4.180190975320986e-9,3.2529654074885624e-9,6.4637540624838414e-9 +LookupCoin/4/4/9,1.2470985656204953e-6,1.2451911356361358e-6,1.2505604396142339e-6,8.64952179853078e-9,5.499440603862215e-9,1.6950749190632643e-8 +LookupCoin/4/4/7,1.2211888003478062e-6,1.2190011158181976e-6,1.2240882033814619e-6,8.080707957074064e-9,6.305138297317099e-9,1.1776649274884938e-8 +LookupCoin/4/4/9,1.246219310561986e-6,1.245437450978012e-6,1.246809450611543e-6,2.412046931433032e-9,1.8927550130235225e-9,3.0625303338979937e-9 +LookupCoin/4/4/10,1.2435562259612564e-6,1.2408279711741978e-6,1.2473329572788982e-6,1.0375907802602415e-8,7.558591085578553e-9,1.6619301178051737e-8 +LookupCoin/4/4/11,1.2566593790245024e-6,1.2547745390633302e-6,1.2580461459342272e-6,5.177468241484571e-9,4.4732163055357475e-9,5.97641360247158e-9 +LookupCoin/4/4/5,1.2222850423977606e-6,1.2198634245527795e-6,1.2245354078111845e-6,7.633968696095189e-9,6.5335072332637135e-9,9.542295348113819e-9 +LookupCoin/4/4/11,1.250724884648928e-6,1.2493655966439506e-6,1.2520092544978692e-6,4.525402933405244e-9,3.2639556504411075e-9,5.800440213532362e-9 +LookupCoin/4/4/10,1.2068371041422458e-6,1.2042905831069772e-6,1.2116967214131046e-6,1.1463478005529737e-8,5.926027070607464e-9,2.003439982144368e-8 +LookupCoin/4/4/11,1.249978109654377e-6,1.2485166300238452e-6,1.25129900312455e-6,4.5522270648791855e-9,3.779068074537687e-9,5.760482059895065e-9 +LookupCoin/4/4/11,1.2475821002420454e-6,1.2463425589908768e-6,1.248865157618701e-6,4.418533688654753e-9,3.831743248913124e-9,5.1355594110117185e-9 +LookupCoin/4/4/11,1.2824686538244592e-6,1.2806454501654126e-6,1.2835954633486922e-6,4.553276855116181e-9,3.2065092593393655e-9,6.510056588005699e-9 +LookupCoin/4/4/11,1.2476285657224824e-6,1.2458184354685831e-6,1.2493532691780388e-6,5.923501300843389e-9,4.982009348860194e-9,6.560467377310131e-9 +LookupCoin/4/4/10,1.255662696176642e-6,1.2545942315210734e-6,1.2570827230105889e-6,4.232617540673662e-9,3.122484000734275e-9,6.004940118545869e-9 +LookupCoin/4/4/11,1.2632371956169925e-6,1.262087452884752e-6,1.2646611536769036e-6,4.214692293096922e-9,3.6497836477963984e-9,4.99841094675237e-9 +LookupCoin/4/4/9,1.2263133139798144e-6,1.2249150844327286e-6,1.2280707543272765e-6,5.217563533857947e-9,4.248988064921147e-9,6.850915601279552e-9 +LookupCoin/4/4/10,1.267580407468345e-6,1.2664251919122808e-6,1.2695814693671906e-6,5.060835604571611e-9,3.2744441882488892e-9,7.801696075872192e-9 +LookupCoin/4/4/10,1.2702550540307273e-6,1.2690361316721864e-6,1.271785886281737e-6,4.709580062307059e-9,3.9172281586586234e-9,5.760859480023366e-9 +LookupCoin/4/4/11,1.2772109439969944e-6,1.2752148793757192e-6,1.2786659829042811e-6,5.310849216638733e-9,3.836083745065901e-9,6.7941489720876594e-9 +LookupCoin/4/4/10,1.2429060453469263e-6,1.241245013919552e-6,1.245271552789436e-6,6.453920574459102e-9,5.463370128053782e-9,8.250494923386193e-9 +LookupCoin/4/4/11,1.2594845920498652e-6,1.258829512116578e-6,1.260081082924469e-6,2.1840304469199286e-9,1.929810006251522e-9,2.5721154106385036e-9 +LookupCoin/4/4/7,1.2449795444125502e-6,1.2438519079844736e-6,1.2460009518989505e-6,3.72631134649154e-9,3.0567838293096365e-9,4.601298942970308e-9 +LookupCoin/4/4/10,1.2587275547920323e-6,1.2580585680492439e-6,1.259294861967665e-6,2.1665285788944064e-9,1.7655283969560557e-9,2.8149181705908985e-9 +LookupCoin/4/4/11,1.2671369502797785e-6,1.266381262906568e-6,1.2682294936447123e-6,3.0391615578004883e-9,2.237439249413991e-9,4.726796071503188e-9 +LookupCoin/4/4/9,1.2460256783078088e-6,1.2448213298091874e-6,1.2474381416771475e-6,4.247057528773148e-9,3.565074908939502e-9,5.109792473606806e-9 +LookupCoin/4/4/11,1.2625785490051976e-6,1.2603402876663008e-6,1.264523471792608e-6,6.7216716870891865e-9,4.822707811606611e-9,9.658444882223709e-9 +LookupCoin/4/4/11,1.2601724350236416e-6,1.2586076567572118e-6,1.2614463262986e-6,4.646575684248816e-9,3.8569144585025716e-9,5.701170676573042e-9 +LookupCoin/4/4/11,1.2594666014956414e-6,1.2569066914216517e-6,1.2620469447074957e-6,8.113755699691054e-9,7.0889147017881055e-9,9.790857188751279e-9 +LookupCoin/4/4/11,1.2483322547313684e-6,1.246922398829055e-6,1.2494618661208718e-6,4.227096626061319e-9,3.2964584498552177e-9,5.176462746379732e-9 +LookupCoin/4/4/10,1.2507030318964978e-6,1.2497114457152014e-6,1.2518263125459921e-6,3.514907595086918e-9,3.0336391285036447e-9,4.049502069340815e-9 +LookupCoin/4/4/11,1.2659144388382993e-6,1.2640341608364966e-6,1.267648709453335e-6,5.736216813757631e-9,5.160343354957749e-9,6.481641342850583e-9 +LookupCoin/4/4/10,1.2400762810239897e-6,1.2391963219245801e-6,1.241097346130724e-6,3.135263351241175e-9,2.7279430658895024e-9,3.748231837374052e-9 +LookupCoin/4/4/11,1.263973766364745e-6,1.2618998592797444e-6,1.266156012888118e-6,6.702539803669301e-9,5.986254231935802e-9,7.679041022313684e-9 +LookupCoin/4/4/11,1.2518657549321e-6,1.249698041364627e-6,1.2543520787819552e-6,8.21492363743867e-9,7.502152116069559e-9,9.032819253550832e-9 +LookupCoin/4/4/11,1.2447452163543908e-6,1.2432615426074351e-6,1.24614768243031e-6,4.508507282143032e-9,3.6427744855388576e-9,5.5518638783273744e-9 +LookupCoin/4/4/10,1.2547778124119448e-6,1.2531725308913239e-6,1.256177821583896e-6,5.004623276948704e-9,4.2643369888211545e-9,6.5759544545108475e-9 +LookupCoin/4/4/11,1.262101773693123e-6,1.260538976123052e-6,1.263577789695053e-6,4.97866214878748e-9,4.164670845113131e-9,6.300658435484918e-9 +LookupCoin/4/4/10,1.2494335719693193e-6,1.2476880983976523e-6,1.2514891224272283e-6,6.418555268694696e-9,5.366391848815581e-9,7.513651464226535e-9 +LookupCoin/4/4/11,1.2387548743791755e-6,1.237845436760153e-6,1.2405509071249566e-6,4.28984778905161e-9,2.9691107844361234e-9,7.046837709689141e-9 +LookupCoin/4/4/11,1.2677106259147114e-6,1.265969981450797e-6,1.2691891201905115e-6,5.163314212047524e-9,4.1805760847750965e-9,6.592570331142436e-9 +LookupCoin/4/4/11,1.2567718001024835e-6,1.2544537416887077e-6,1.2597352116935727e-6,8.85986967326852e-9,7.398492441824828e-9,1.2428211768407896e-8 +LookupCoin/4/4/10,1.2389168105488148e-6,1.2375955513750582e-6,1.2400231775571017e-6,4.008816976653277e-9,3.2399733821715353e-9,4.987886471339023e-9 +LookupCoin/4/4/10,1.2509606088835598e-6,1.249057560262197e-6,1.2533980097055831e-6,7.0078540806729966e-9,5.515720387811593e-9,1.0425137894541599e-8 +LookupCoin/4/4/10,1.2560702825481937e-6,1.254182357902354e-6,1.2578364303624702e-6,6.3074612066411135e-9,5.402658501938011e-9,7.1755182224242935e-9 +LookupCoin/4/4/11,1.261477281509439e-6,1.2598608323447094e-6,1.2645048495194436e-6,7.3215983161567294e-9,5.06978493862556e-9,1.2070413799448123e-8 +LookupCoin/4/4/11,1.2505703363027947e-6,1.2485366337552197e-6,1.2525612822110055e-6,6.7275076765512455e-9,5.656662242601031e-9,8.177635928720666e-9 +LookupCoin/4/4/10,1.252750231643778e-6,1.2519391911460776e-6,1.25370618678725e-6,2.9367119134048805e-9,2.3846107743696134e-9,4.452664454286303e-9 +LookupCoin/4/4/11,1.2651209512343535e-6,1.2640485350872299e-6,1.2665477595295832e-6,4.445028596926021e-9,3.5798373563486984e-9,5.613910810172365e-9 +LookupCoin/4/4/9,1.2380226585104609e-6,1.2362900280118667e-6,1.2394597324025156e-6,5.098746547729719e-9,4.0008517314912585e-9,6.17440360947907e-9 +LookupCoin/4/4/11,1.2703297022532047e-6,1.2682373544251785e-6,1.2725687697034899e-6,7.1697855080640995e-9,6.362672547516085e-9,7.955775896416468e-9 +LookupCoin/4/4/9,1.2512604199844874e-6,1.2492795128279614e-6,1.2524030795580555e-6,4.9877478857470085e-9,2.6403970450768774e-9,7.84666258604664e-9 +LookupCoin/4/4/11,1.25530062493191e-6,1.2538911148269256e-6,1.256762557605688e-6,4.89632318090818e-9,4.121922806649131e-9,5.647847583992622e-9 +LookupCoin/4/4/11,1.244886197896722e-6,1.2442984295041443e-6,1.2455696642306306e-6,2.1744201587193866e-9,1.8222381766251497e-9,2.7778320145962305e-9 +LookupCoin/4/4/9,1.2399591441601689e-6,1.2389190944878488e-6,1.241535033732355e-6,4.328263567193719e-9,3.0591536458771003e-9,7.148980702975058e-9 +LookupCoin/4/4/11,1.2486555145560358e-6,1.246992527911053e-6,1.2499947696601263e-6,5.260233301569391e-9,4.470520683516049e-9,6.335261171113161e-9 +LookupCoin/4/4/11,1.2474333744884636e-6,1.2463055183966161e-6,1.2488613195097239e-6,4.384271706272338e-9,3.3913447781582296e-9,5.620648578678502e-9 +LookupCoin/4/4/8,1.2334567415991134e-6,1.232841971210817e-6,1.2340915474552801e-6,2.0301269087575176e-9,1.6381181131674423e-9,2.574270880546165e-9 +ValueContains/4/1,1.105434543510619e-6,1.104761669698638e-6,1.1063157641412615e-6,2.5006074729243277e-9,1.9669982721380314e-9,3.4335626539358642e-9 +ValueContains/4/0,1.0306397386859852e-6,1.028800477510463e-6,1.0326739767127572e-6,6.616346473915064e-9,6.193309934090764e-9,7.092235734931024e-9 +ValueContains/4/10,1.820720834681636e-6,1.8191253437797686e-6,1.8232358592510541e-6,6.763821102008429e-9,4.673938452762895e-9,1.0315848552337634e-8 +ValueContains/7/0,1.0252209862077256e-6,1.024618617182076e-6,1.0258351403077722e-6,2.1175286634167027e-9,1.8802323738637716e-9,2.3741920511291424e-9 +ValueContains/7/0,1.0280232194067423e-6,1.026147003532159e-6,1.0299502826838859e-6,6.6761800893311246e-9,5.844848366093946e-9,7.621882989357328e-9 +ValueContains/7/100,1.214555391020298e-5,1.2113948799568427e-5,1.2168651147537038e-5,9.779236859850173e-8,7.466824051239605e-8,1.290089244182694e-7 +ValueContains/10/0,1.0285184266132384e-6,1.0270438056630502e-6,1.0297528205450551e-6,4.695725307334156e-9,3.6900650397944465e-9,6.236441473384819e-9 +ValueContains/10/0,1.0263040164773018e-6,1.0248999834722293e-6,1.0281672020073887e-6,5.2621977948493825e-9,3.920032953487552e-9,6.786795094325855e-9 +ValueContains/10/0,1.0223050687143138e-6,1.0214652962394742e-6,1.02428431951749e-6,4.320538557649969e-9,2.1763514970030737e-9,8.183340862647313e-9 +ValueContains/10/1000,1.3293093433683166e-4,1.328007675682534e-4,1.330761492549652e-4,4.6952283865058516e-7,3.797641833707987e-7,5.965668337160833e-7 +ValueContains/5/200,1.6503035639538536e-5,1.6492615656743238e-5,1.652001562155218e-5,4.719531447553505e-8,3.116649329387387e-8,7.663918693214212e-8 +ValueContains/1/0,1.0140103329349797e-6,1.0133749711003663e-6,1.0146722566964554e-6,2.2098469290476243e-9,1.7252381027510976e-9,3.0448743578033727e-9 +ValueContains/4/0,1.0243604560021716e-6,1.0221135174097028e-6,1.0265054031795115e-6,6.995648455944508e-9,5.896134154624651e-9,8.338092410022835e-9 +ValueContains/7/0,1.0306611958595134e-6,1.0282909768284086e-6,1.032360391015259e-6,6.4096520173214514e-9,4.613845016528073e-9,7.985244408860542e-9 +ValueContains/10/0,1.0246081379431291e-6,1.0226349717738905e-6,1.0272466609220711e-6,7.336532498054823e-9,6.2703178287046045e-9,9.543486985491354e-9 +ValueContains/10/646,7.441283070704394e-5,7.43784527236331e-5,7.445334613303153e-5,1.2652896884550386e-7,9.682926240156536e-8,1.6517639740827547e-7 +ValueContains/12/1358,1.6815208792024118e-4,1.6801249062461747e-4,1.683697543385396e-4,5.683078446110742e-7,3.6254491417830065e-7,1.0188119073030313e-6 +ValueContains/12/1165,1.488730510294422e-4,1.4883083320586053e-4,1.4894906949057245e-4,1.7525791994769714e-7,1.2028745351972862e-7,2.904692560082104e-7 +ValueContains/11/1291,1.5744929873441713e-4,1.5733887209082092e-4,1.576521837252153e-4,4.778509795564433e-7,3.2166058589942764e-7,7.738721371331961e-7 +ValueContains/10/998,1.1769401376810234e-4,1.175866182768469e-4,1.1779423082385351e-4,3.644027956706522e-7,3.1439828134125906e-7,4.1708799263704205e-7 +ValueContains/11/977,1.1597171501481696e-4,1.1590377470108519e-4,1.1611919805174089e-4,3.3555975827259076e-7,1.684220641376806e-7,6.274138667382754e-7 +ValueContains/13/370,4.9042983606935425e-5,4.901990115467035e-5,4.9072765036134805e-5,9.315363198270772e-8,6.571454491625358e-8,1.410408886683234e-7 +ValueContains/12/3033,3.954000098741814e-4,3.9505425268160485e-4,3.9600008358255974e-4,1.4748756053438227e-6,8.927150332810167e-7,2.6335053757918597e-6 +ValueContains/13/2884,3.820988400883808e-4,3.820432673545169e-4,3.8216145711987326e-4,2.0065292972365346e-7,1.6677728225330086e-7,2.5293391932034945e-7 +ValueContains/7/61,5.724093459596734e-6,5.712072631283652e-6,5.737850135956423e-6,4.292519299064555e-8,3.583252164197087e-8,5.685966772277251e-8 +ValueContains/12/596,7.276195428181185e-5,7.27292343015308e-5,7.281506484537547e-5,1.3941999073003655e-7,8.516005638835006e-8,2.178771895942148e-7 +ValueContains/12/1042,1.326226108648041e-4,1.3249750443789052e-4,1.330446334034546e-4,6.807757078902529e-7,1.9096025943030226e-7,1.3866327183932838e-6 +ValueContains/7/45,4.531518268866434e-6,4.526054255525554e-6,4.539353846578104e-6,2.2055581276136084e-8,1.9124314926478775e-8,2.641271749763396e-8 +ValueContains/12/843,1.047847990246496e-4,1.0469850850759846e-4,1.0517405993592751e-4,5.163085093891324e-7,1.029915924970202e-7,1.15964961296233e-6 +ValueContains/12/2476,3.206175835857794e-4,3.2054668126016233e-4,3.2072027577290655e-4,2.871260879068344e-7,2.0686047545757418e-7,4.0564344814662266e-7 +ValueContains/10/905,1.060932626401992e-4,1.0603241495905132e-4,1.0625809058707843e-4,3.0425668238843574e-7,1.3872548253346558e-7,5.768341435609618e-7 +ValueContains/13/1853,2.398676338723237e-4,2.3982315100902393e-4,2.3992903068258532e-4,1.6787080994715174e-7,1.272986305753252e-7,2.562178324460746e-7 +ValueContains/9/211,2.3241070684104172e-5,2.3219853813195678e-5,2.3267199165385782e-5,7.916610845106641e-8,5.678895369841774e-8,1.2844030824010097e-7 +ValueContains/12/3149,4.053205885826389e-4,4.052364280370845e-4,4.054533293956877e-4,3.483064322018529e-7,2.386353952377759e-7,5.100052812828452e-7 +ValueContains/11/997,1.1979601908866435e-4,1.1964607048393313e-4,1.2019172120249887e-4,8.007959364807597e-7,4.268431968692829e-7,1.468850226791584e-6 +ValueContains/12/63,8.477595458556624e-6,8.469514037945754e-6,8.48870380587104e-6,3.289714464788442e-8,2.8027260298508268e-8,4.04664755206175e-8 +ValueContains/11/833,1.0019015554687506e-4,1.0011840782240724e-4,1.0032847381252279e-4,3.2048950930382616e-7,1.9607669251094275e-7,5.558785603702673e-7 +ValueContains/12/1396,1.791641752310758e-4,1.790648874977756e-4,1.792906943941706e-4,3.910369867417785e-7,2.9055353677751513e-7,4.943280688124263e-7 +ValueContains/11/999,1.1960282097559351e-4,1.1952034354510336e-4,1.1989610054844092e-4,4.387334699430444e-7,1.75347492797394e-7,9.489745653188127e-7 +ValueContains/12/377,4.9268527063048286e-5,4.92458556144685e-5,4.930304872085852e-5,8.547419940709613e-8,6.144316820489737e-8,1.1435969493440315e-7 +ValueContains/11/375,4.502966455405575e-5,4.4996404789337704e-5,4.5103226489301955e-5,1.543294999693142e-7,7.141805309458704e-8,3.0580115765887084e-7 +ValueContains/13/2268,2.9853066805901585e-4,2.984288596048085e-4,2.987156786493456e-4,4.4334013044019857e-7,3.1213691628991156e-7,6.309871710987987e-7 +ValueContains/8/156,1.6435523637515978e-5,1.642570000016781e-5,1.6444351496447234e-5,3.199701420893554e-8,2.6320257705438826e-8,4.113050725667119e-8 +ValueContains/11/953,1.1254710757347861e-4,1.1251409678969029e-4,1.1259323161640841e-4,1.3247832019796597e-7,1.0481391039741116e-7,1.6317952880011978e-7 +ValueContains/13/531,6.722172127439049e-5,6.7141806531495e-5,6.758557600845466e-5,4.797650396818759e-7,1.052597340557341e-7,1.0706484974322888e-6 +ValueContains/12/2298,2.9534540322019836e-4,2.9476549321575383e-4,2.968912027074983e-4,2.7264220973975565e-6,2.564165051847216e-7,5.425325609838385e-6 +ValueContains/12/390,4.803131363004283e-5,4.7991037693599024e-5,4.814213019798374e-5,1.9784949880825503e-7,9.084699751568076e-8,3.8402545346945097e-7 +ValueContains/11/90,1.0964518538526184e-5,1.0956047380495303e-5,1.0973930920667138e-5,3.0220549623052384e-8,2.5451127869939373e-8,3.689602601711146e-8 +ValueContains/12/1765,2.2191669166752722e-4,2.2171853222201495e-4,2.2242359166528946e-4,1.0196637342158027e-6,4.739033004648279e-7,2.0226821395999575e-6 +ValueContains/8/138,1.4059720594516508e-5,1.4051939255563339e-5,1.4071461179695633e-5,3.0636780375753266e-8,2.090202202749129e-8,4.321581009323182e-8 +ValueContains/12/1818,2.424236552202903e-4,2.4222666660322738e-4,2.4303811894505544e-4,1.0407167560159624e-6,4.000641517049369e-7,2.0672745947498194e-6 +ValueContains/13/3251,4.287348073060723e-4,4.2859131672895294e-4,4.289712803376432e-4,6.296789036808865e-7,4.164747058995414e-7,1.0300660804876753e-6 +ValueContains/9/375,4.2127877178920495e-5,4.208522745503054e-5,4.22177746390498e-5,2.026686870691483e-7,1.0598115655851085e-7,3.998411429342358e-7 +ValueContains/12/415,5.1223984617488054e-5,5.1200368120805436e-5,5.1250291238085066e-5,8.784310981732528e-8,6.264693948228433e-8,1.4712070847594412e-7 +ValueContains/13/1497,1.987664901375959e-4,1.9852875412114182e-4,1.9952989050732664e-4,1.3357046915971355e-6,4.232048833454561e-7,2.690932419150629e-6 +ValueContains/12/588,7.609657701697021e-5,7.60704189672081e-5,7.61302074615819e-5,9.707686719213686e-8,8.193430682587038e-8,1.206116106566066e-7 +ValueContains/12/1079,1.3282491359168218e-4,1.3278256702678074e-4,1.3287295880426772e-4,1.5162208469969725e-7,1.21731971058478e-7,2.0652890452078913e-7 +ValueContains/13/2290,3.0017499838337397e-4,3.0009808624299414e-4,3.002733886994872e-4,2.979611803890221e-7,2.3292533684262637e-7,3.9405349548164203e-7 +ValueContains/10/45,5.887778235971029e-6,5.882112081863332e-6,5.893851931166322e-6,2.01279437294267e-8,1.702777980890875e-8,2.599683733803629e-8 +ValueContains/11/742,9.131898189290163e-5,9.12757401951564e-5,9.136409750554772e-5,1.481028947911416e-7,1.2096382212492334e-7,1.8312611699589294e-7 +ValueContains/10/298,3.533820991336732e-5,3.532230857317866e-5,3.535444863431016e-5,5.286330819841384e-8,4.3823959909992985e-8,6.43855767534137e-8 +ValueContains/12/515,6.738708848391595e-5,6.735189737115322e-5,6.741837286038623e-5,1.0564164187449367e-7,8.916338903006408e-8,1.2330582038591818e-7 +ValueContains/12/489,5.99591026385554e-5,5.992211308955975e-5,6.001279979970592e-5,1.5116792038111816e-7,9.253121526527911e-8,2.265785823242215e-7 +ValueContains/13/2291,3.1149480339926015e-4,3.112743669968882e-4,3.1204881853179686e-4,1.037230082693866e-6,5.18940645889787e-7,1.890466739075077e-6 +ValueContains/12/184,2.3282846136456296e-5,2.3255417267824355e-5,2.331506926535788e-5,1.0091162302207955e-7,8.70753354986584e-8,1.1583240073582862e-7 +ValueContains/11/1622,1.9812267667886877e-4,1.9802036488066814e-4,1.9826799056670618e-4,3.9089080404453247e-7,2.941462537295892e-7,5.616758128592064e-7 +ValueContains/11/1103,1.3043614696358626e-4,1.303836848282631e-4,1.304929533429926e-4,1.8325946113827698e-7,1.4252476107083352e-7,2.464251219431128e-7 +ValueContains/12/833,1.0243524009510309e-4,1.0240408969358041e-4,1.0248056007238512e-4,1.22568392180608e-7,9.352560290740514e-8,1.7106802473446964e-7 +ValueContains/10/166,1.8807292208057004e-5,1.8782664632152158e-5,1.8832642314387125e-5,8.505942756167824e-8,7.390178728552626e-8,9.993723382366903e-8 +ValueContains/12/1270,1.6295986438092945e-4,1.6289830167437184e-4,1.6306011112165262e-4,2.8263817997579223e-7,1.9475736964171977e-7,4.928254794077895e-7 +ValueContains/11/287,3.521145389839651e-5,3.518599530249471e-5,3.5256452151419566e-5,1.166283369349522e-7,7.992628995786976e-8,1.927854012616892e-7 +ValueContains/10/912,1.071642176152517e-4,1.0708505345588232e-4,1.0746464358857595e-4,4.4590841007547816e-7,1.125591676639726e-7,9.227484266041511e-7 +ValueContains/12/1892,2.4434978476151856e-4,2.4430678593079436e-4,2.4440644018393646e-4,1.6783993154812263e-7,1.3583143838326006e-7,2.2285878765144933e-7 +ValueContains/12/1863,2.3608685664246537e-4,2.3603195757177634e-4,2.3617656726364477e-4,2.4081722466297496e-7,1.6857087371863572e-7,3.5876027011889764e-7 +ValueContains/10/577,6.60213853409024e-5,6.59978372496058e-5,6.605862283578572e-5,9.651005007816427e-8,7.026133825107891e-8,1.5485715967503996e-7 +ValueContains/12/1231,1.593963366747364e-4,1.5933680121769334e-4,1.594565359346893e-4,1.9786660178980482e-7,1.5361444979162913e-7,2.650700982126226e-7 +ValueContains/12/2931,3.722377996327141e-4,3.7205561267537505e-4,3.7248410813460887e-4,6.865993893471296e-7,5.373982811138052e-7,9.494962627994329e-7 +ValueContains/13/4382,5.814563169246447e-4,5.813342500148208e-4,5.816325702849465e-4,5.094744549521182e-7,3.8306107926475136e-7,8.167624785920538e-7 +ValueContains/12/1565,1.9923057588953856e-4,1.9917579510814635e-4,1.992989897592509e-4,1.9768045522226999e-7,1.62120079585953e-7,2.959690651991732e-7 +ValueContains/11/56,7.049112065774829e-6,7.041332035193911e-6,7.056127465548296e-6,2.505808622301429e-8,2.0508139111524797e-8,3.193362898655345e-8 +ValueContains/11/372,4.2994661318304265e-5,4.297774695404077e-5,4.3016054077768e-5,6.40259121611655e-8,5.342079873707793e-8,8.193141363157006e-8 +ValueContains/12/1409,1.8298640251247647e-4,1.828956388989965e-4,1.831225937031092e-4,3.6755011456854844e-7,2.419447623751336e-7,6.077541441558001e-7 +ValueContains/12/2411,3.144557275816184e-4,3.1433530606879016e-4,3.146722906304664e-4,5.403181114817953e-7,3.929803869702245e-7,7.897920675234983e-7 +ValueContains/12/2022,2.5625710548620497e-4,2.561676036513246e-4,2.563470391509658e-4,3.0049331661144854e-7,2.567272449637465e-7,3.676583526502356e-7 +ValueContains/8/169,1.7567833586422405e-5,1.7537519109719872e-5,1.7606200569759918e-5,1.1265019366997327e-7,9.717704176025805e-8,1.3195230018012848e-7 +ValueContains/12/2128,2.699247947339283e-4,2.698240077337551e-4,2.701565976749698e-4,4.651855280997162e-7,2.711381101183825e-7,8.77842077493533e-7 +ValueContains/11/984,1.1937167865455437e-4,1.1928473503062602e-4,1.1967742707817802e-4,5.008963833613214e-7,1.4061253764269697e-7,1.0296267731926103e-6 +ValueContains/11/262,3.1544192277398865e-5,3.15095266680693e-5,3.158007062905678e-5,1.1764242238434015e-7,1.0128604715566369e-7,1.3934900641952566e-7 +ValueContains/13/1362,1.7908436398682647e-4,1.7901920469637036e-4,1.792162858046282e-4,2.9150352884122645e-7,1.5708689878298075e-7,5.206287603533956e-7 +ValueContains/13/3396,4.4285323819141055e-4,4.4268075065829717e-4,4.430977340159761e-4,6.896050060773073e-7,4.496001729624406e-7,1.1434657060778898e-6 +ValueContains/12/845,1.1222378575879455e-4,1.1217748665402018e-4,1.1227615614207284e-4,1.604006691837945e-7,1.2727793390926994e-7,2.1030416112254738e-7 +ValueContains/13/3273,4.331549571719631e-4,4.328868162395225e-4,4.334481397429046e-4,9.392917286548258e-7,6.89113913639228e-7,1.403638475432845e-6 +ValueContains/10/503,5.743197405717264e-5,5.7379791535214774e-5,5.7509040694888954e-5,1.978597540887674e-7,1.487696747366074e-7,2.5917502875732304e-7 +ValueContains/11/421,4.9284396577657796e-5,4.924871756163534e-5,4.9324237123028804e-5,1.2514542238741243e-7,1.0366933208028346e-7,1.565381916787151e-7 +ValueContains/11/88,1.0997944692881061e-5,1.0976417633640176e-5,1.102884717031259e-5,8.153902360416276e-8,6.290666182681504e-8,1.0133976895898452e-7 +ValueContains/12/2096,2.695700404524966e-4,2.694899225900187e-4,2.6976295760082583e-4,3.892841130919495e-7,2.135037546528592e-7,6.987062420690264e-7 +ValueContains/12/958,1.2775525674266257e-4,1.277236828615857e-4,1.278013960537453e-4,1.2479726066035998e-7,9.26071656390998e-8,1.9392807499720426e-7 +ValueContains/12/2635,3.4406649791623057e-4,3.4399273206417767e-4,3.44216954510562e-4,3.616196961263488e-7,1.9102208009623364e-7,6.550070593423511e-7 +ValueContains/7/54,5.331028378799725e-6,5.327189332578184e-6,5.334778869443724e-6,1.3495644741628291e-8,1.1246036301715161e-8,1.5989744242932852e-8 +ValueContains/12/3154,4.063129808051071e-4,4.061286928451106e-4,4.066708017503966e-4,8.699231488189299e-7,4.823254059562437e-7,1.6881632390449117e-6 +ValueContains/13/3744,5.016773266714847e-4,5.01589233851217e-4,5.017989967578292e-4,3.530234641028672e-7,2.716653085568384e-7,4.890190946962745e-7 +ValueContains/11/355,4.180919772508725e-5,4.178547778650308e-5,4.1840456224693724e-5,9.000584786498028e-8,7.364125269427776e-8,1.2389877930887057e-7 +ValueContains/11/980,1.2275675690234686e-4,1.2267487588957997e-4,1.2284925514429059e-4,2.9684048482151794e-7,2.3492153821048423e-7,3.825219659316146e-7 +ValueContains/13/3350,4.429107862668096e-4,4.427642322701703e-4,4.431400153255526e-4,6.006361097385757e-7,3.9545434226110795e-7,9.71636201816491e-7 +ValueContains/13/2294,3.0339158169837086e-4,3.033114381472984e-4,3.034836585298028e-4,2.940425264542992e-7,2.3676491577331085e-7,3.8139540522221467e-7 +ValueContains/13/4444,5.962139868447767e-4,5.959720657251243e-4,5.966065129669149e-4,1.055438883627953e-6,7.139647588747463e-7,1.7257747081792733e-6 +ValueContains/12/1882,2.3371214655523747e-4,2.335936618456013e-4,2.3383204858605503e-4,3.768029448605273e-7,3.022341201904928e-7,4.753401461074988e-7 +ValueContains/12/1262,1.642018935406448e-4,1.640671385807914e-4,1.6435845252788618e-4,4.966588324910747e-7,3.819941467699423e-7,8.033481132996157e-7 +ValueContains/11/657,7.792025571447051e-5,7.789441602608649e-5,7.794886611340072e-5,9.17920692696743e-8,7.390091468742131e-8,1.3985276267618588e-7 +ValueContains/12/2180,2.713135309176018e-4,2.711645227193468e-4,2.714849915155506e-4,5.468013004134306e-7,4.0954215109699106e-7,7.382800322293021e-7 +ValueContains/13/728,1.0143838523683126e-4,1.0140438327118037e-4,1.0149493728776178e-4,1.4194640230833648e-7,8.794872412714315e-8,2.100494976780515e-7 +ValueContains/12/1296,1.6374830773475144e-4,1.636295451404291e-4,1.6390825706682273e-4,4.5512986164665656e-7,3.7695923281399107e-7,6.060230167904003e-7 +ValueContains/11/701,8.469772846558616e-5,8.468168710623024e-5,8.472143871798954e-5,6.716883242925578e-8,5.030538318708717e-8,9.885784695058379e-8 +ValueContains/13/2528,3.3662004066964337e-4,3.3647921660858853e-4,3.3701721396276325e-4,7.531951114588133e-7,2.257640172910717e-7,1.5339742876432358e-6 +ValueContains/10/662,7.799822503281861e-5,7.795432920805907e-5,7.804605390057409e-5,1.606065609463777e-7,1.354602544006714e-7,2.0584373791285545e-7 +ValueData/0,8.491889096596671e-7,8.474502971660789e-7,8.506137758572909e-7,5.111329214539667e-9,4.303481093916784e-9,6.103052824928771e-9 +ValueData/10,8.536772612315314e-7,8.530765418662205e-7,8.542350819040113e-7,1.90548352139756e-9,1.5398189665210485e-9,2.4639909342920807e-9 +ValueData/100,8.509232117281916e-7,8.497187371872595e-7,8.517056976917077e-7,3.2050058154741175e-9,2.1397215304619156e-9,5.201039230687773e-9 +ValueData/500,8.535831001721129e-7,8.528371095228981e-7,8.542402261485153e-7,2.404886756201847e-9,2.0544097108108714e-9,2.9019636521671364e-9 +ValueData/1000,8.503620064745987e-7,8.492727336826363e-7,8.510805271844457e-7,2.8523021844990105e-9,1.9000300247769356e-9,4.26410511879433e-9 +ValueData/5000,8.456274218841898e-7,8.434758384943089e-7,8.479169679014288e-7,7.424813273560543e-9,6.40171810297941e-9,8.937594000856933e-9 +ValueData/10000,8.521692129306124e-7,8.513322986331105e-7,8.531729305605561e-7,3.202011936525637e-9,2.735499160701126e-9,3.964043367095772e-9 +ValueData/12,8.524782650799322e-7,8.512324940367628e-7,8.534868930559195e-7,3.739378699190234e-9,2.8622783185580692e-9,5.2189586336573326e-9 +ValueData/132,8.518641219101371e-7,8.507891638164795e-7,8.527095166578669e-7,3.2454116569304947e-9,2.0934930961657703e-9,5.3010300557355035e-9 +ValueData/400,8.54326239312973e-7,8.528276147764191e-7,8.555584486601825e-7,4.622817473100502e-9,3.5885124332449724e-9,5.917490002383504e-9 +ValueData/97532,8.489894926417452e-7,8.474776994716881e-7,8.504797114711922e-7,5.127756013958843e-9,4.224490647801043e-9,6.562485085015828e-9 +ValueData/123234,8.488610377944512e-7,8.47673801911665e-7,8.496679184721956e-7,3.165447605683565e-9,2.4018248420673443e-9,4.097120827889815e-9 +ValueData/132651,8.460488190258313e-7,8.436234137841776e-7,8.48436781383805e-7,8.00695104798979e-9,7.454630075244634e-9,8.720049228981087e-9 +ValueData/79831,8.485348608351178e-7,8.461059410035796e-7,8.506551319448549e-7,7.697358258650205e-9,6.606599734036178e-9,9.00424372423834e-9 +ValueData/2567,8.483417275201465e-7,8.467567740805494e-7,8.502071625127907e-7,5.599541868537745e-9,4.7200368542944335e-9,6.586885642878378e-9 +ValueData/225250,8.532659084334731e-7,8.51873555571226e-7,8.542710206695556e-7,4.036718793141761e-9,3.3330587637839835e-9,5.575281453774376e-9 +ValueData/129168,8.49479175968378e-7,8.479710437711364e-7,8.510627145459614e-7,4.904750554473975e-9,4.183501090301991e-9,5.660288839845393e-9 +ValueData/95589,8.573919525058234e-7,8.569312609324598e-7,8.57810924025367e-7,1.4331309086456993e-9,1.211848017419693e-9,1.7173749291641115e-9 +ValueData/393828,8.529246771173438e-7,8.507038170606696e-7,8.547144273387028e-7,6.695902076329811e-9,5.173610038449872e-9,8.074646533519432e-9 +ValueData/277103,8.559638658317148e-7,8.554274139829204e-7,8.564846690487816e-7,1.7153070255380866e-9,1.4850532000337766e-9,2.0865932283322898e-9 +ValueData/149732,8.568952213150124e-7,8.55779559386523e-7,8.583202337440934e-7,4.058932224433089e-9,2.920609176400781e-9,6.10364063175426e-9 +ValueData/20295,8.592090895241722e-7,8.585468566287558e-7,8.597103679598852e-7,1.9589461127960793e-9,1.5020961846565704e-9,2.53245151603325e-9 +ValueData/274721,8.556310346575752e-7,8.545182575729657e-7,8.570085156588638e-7,4.072983231227863e-9,2.9894065840915132e-9,6.650854252738855e-9 +ValueData/234360,8.495773315849466e-7,8.485095898533361e-7,8.508590560485591e-7,3.945885261239193e-9,3.3307796278669102e-9,4.88263922439458e-9 +ValueData/435575,8.554316016970627e-7,8.538057251650714e-7,8.571822727065235e-7,5.22165775590414e-9,3.822225646271991e-9,7.912659649938424e-9 +ValueData/325,8.575383560860995e-7,8.551456054417133e-7,8.598318890975003e-7,7.301228301796286e-9,5.898989793599207e-9,9.170285573277641e-9 +ValueData/309672,8.455838662678522e-7,8.438929583098089e-7,8.481128496280869e-7,6.693508880581244e-9,4.4891910590555004e-9,1.137117018751179e-8 +ValueData/35730,8.503165857726503e-7,8.481929705257501e-7,8.516384413851961e-7,5.7155624436964685e-9,4.5511453783585685e-9,6.997453715992399e-9 +ValueData/140014,8.497151545708349e-7,8.47665192217661e-7,8.525789066401396e-7,7.826592793711272e-9,5.2974447055560445e-9,1.2683466835836368e-8 +ValueData/204540,8.547612676005635e-7,8.541325977717021e-7,8.554903718929581e-7,2.2527957694464155e-9,1.8667067331724525e-9,2.773592456121547e-9 +ValueData/162450,8.487506984701391e-7,8.465771829739707e-7,8.521365758677206e-7,8.841224778102471e-9,6.6926023509893566e-9,1.3281905024646752e-8 +ValueData/173264,8.562504495480041e-7,8.545357665578781e-7,8.574980439256358e-7,5.189153572955064e-9,3.812114301485482e-9,6.801955327270975e-9 +ValueData/34804,8.488094176189896e-7,8.471112077894535e-7,8.518703990459759e-7,7.368614047478343e-9,4.7738497483993025e-9,1.2861751838021989e-8 +ValueData/101238,8.491653203365375e-7,8.471167463151252e-7,8.513892668592282e-7,7.011704217750554e-9,6.246082809121775e-9,7.85427874561324e-9 +ValueData/10857,8.53340260023185e-7,8.51733021923939e-7,8.577891620108842e-7,8.56880225654526e-9,3.7036805227047417e-9,1.6894879950523497e-8 +ValueData/842,8.518487603033034e-7,8.512686060694756e-7,8.52466383127732e-7,2.045925927265305e-9,1.7231537556893947e-9,2.541823788150579e-9 +ValueData/283434,8.491846975222256e-7,8.473914983974797e-7,8.510037925216556e-7,5.79124519501295e-9,4.8451434866888664e-9,6.80761433065066e-9 +ValueData/148255,8.576744946811667e-7,8.556633506862432e-7,8.589271508500057e-7,5.31799961973457e-9,2.732711973241952e-9,8.2684315303086e-9 +ValueData/15156,8.591817798288072e-7,8.583380706837744e-7,8.600590146665929e-7,3.0807725325311505e-9,2.5585140848634544e-9,4.025859681159594e-9 +ValueData/382000,8.541321699516358e-7,8.527137261554062e-7,8.552649289279874e-7,4.5241113374891385e-9,3.787714480600488e-9,5.5478834939184535e-9 +ValueData/205387,8.59263880232035e-7,8.58394258768979e-7,8.600854353488695e-7,2.719065044164826e-9,2.3486986410915696e-9,3.3109672681863356e-9 +ValueData/126392,8.567038496798349e-7,8.56128655177015e-7,8.572978285568135e-7,1.942320811100465e-9,1.658531814482164e-9,2.307633975208863e-9 +ValueData/33839,8.540435375808689e-7,8.522309860198086e-7,8.554138627735398e-7,5.432763905741997e-9,4.07731200095926e-9,7.373001030160369e-9 +ValueData/93500,8.531396796344981e-7,8.525776732804758e-7,8.539021868313024e-7,2.210481853251166e-9,1.5357810025607828e-9,3.0182731425311144e-9 +ValueData/241072,8.556277272730625e-7,8.545950063697891e-7,8.566615470273197e-7,3.382119487888055e-9,2.4695089147116096e-9,5.137339329802755e-9 +ValueData/100606,8.536011014867612e-7,8.524537273969687e-7,8.54726329722913e-7,4.090430838007471e-9,3.3817103295117896e-9,4.901613057818376e-9 +ValueData/15408,8.459468636671925e-7,8.444682305735465e-7,8.472235741334678e-7,4.657080535366424e-9,4.060014962865163e-9,5.509147432714346e-9 +ValueData/69616,8.566448782136618e-7,8.549481754753083e-7,8.574310290639088e-7,3.769537190659225e-9,1.987277360101976e-9,7.140286693043567e-9 +ValueData/304521,8.525787369865922e-7,8.513599351989442e-7,8.537279119368074e-7,3.753510914131666e-9,3.3120583034234087e-9,4.4210015913725766e-9 +ValueData/263198,8.509502296963885e-7,8.489638139041335e-7,8.524589667958955e-7,5.522654208857717e-9,4.191146928016306e-9,6.377548167908616e-9 +ValueData/22260,8.574593081727456e-7,8.569059330882079e-7,8.579716188604812e-7,1.7699769087714066e-9,1.5248074379518592e-9,2.1119148517269495e-9 +ValueData/100352,8.514725924159434e-7,8.501517235480839e-7,8.523989560528702e-7,3.801156560219798e-9,2.82823135305191e-9,4.828535769309876e-9 +ValueData/1773,8.532731677901347e-7,8.513579922650547e-7,8.549742207857545e-7,6.278170410522051e-9,5.043967589585777e-9,7.673213331197956e-9 +ValueData/15330,8.576833934483828e-7,8.563030828770634e-7,8.587431773518986e-7,4.047518878506176e-9,2.7416772650740688e-9,6.000208471479928e-9 +ValueData/176988,8.499643734628492e-7,8.486570355678265e-7,8.511384191783384e-7,4.15135516176567e-9,3.5169318252247064e-9,5.202750690282858e-9 +ValueData/72385,8.558698154904479e-7,8.548736837103324e-7,8.56983593168842e-7,3.4481228223688745e-9,2.729452831934385e-9,4.476737051064749e-9 +ValueData/235037,8.557381138303279e-7,8.542117800971427e-7,8.570984376997041e-7,4.765293488248609e-9,4.00776827567388e-9,5.50668697363528e-9 +ValueData/95940,8.527513288545138e-7,8.504947634870435e-7,8.542552992416777e-7,6.2197153210891185e-9,4.37624817217445e-9,8.418819112463073e-9 +ValueData/103200,8.479903631242557e-7,8.461970775528324e-7,8.497129989311023e-7,5.9024748365191916e-9,5.123371730822309e-9,6.9017623164474515e-9 +ValueData/123816,8.463906341117494e-7,8.444667455341365e-7,8.487137092173759e-7,7.282933356419484e-9,6.309327218991049e-9,8.807160603512193e-9 +UnValueData/4,9.013950914141455e-7,8.998310604752979e-7,9.030685882488825e-7,5.512364943540312e-9,4.653201611803667e-9,6.47512273336601e-9 +UnValueData/146,2.6949717546797696e-6,2.6929457624387185e-6,2.6969263184348243e-6,6.4963161689037006e-9,5.486385356337939e-9,7.903034149953178e-9 +UnValueData/1424,1.7907472683032777e-5,1.7902658268731024e-5,1.7912900682501594e-5,1.7030564686088553e-8,1.3739405874666239e-8,2.235702394823734e-8 +UnValueData/7104,8.723466638282224e-5,8.716778413126838e-5,8.739787957227999e-5,3.227634726193636e-7,1.7190914159487133e-7,6.403529007213577e-7 +UnValueData/14204,1.7629954435655664e-4,1.762349459970134e-4,1.7637827841013271e-4,2.4073648638990344e-7,1.9359582750372447e-7,3.1784683202462695e-7 +UnValueData/71004,9.946969395157833e-4,9.900353441417433e-4,9.999746858039172e-4,1.6185331467772357e-5,1.2962056012188339e-5,2.083933197891671e-5 +UnValueData/142004,2.397080011982262e-3,2.3874266903145874e-3,2.4054034603446426e-3,3.064690617529184e-5,2.384999626785536e-5,4.1279743653245695e-5 +UnValueData/196,3.0199827263550725e-6,3.017306789987222e-6,3.024693062411046e-6,1.1745346040213685e-8,7.283896149278244e-9,2.022058416407555e-8 +UnValueData/1852,2.29141633470779e-5,2.2901937018727813e-5,2.2926753458055604e-5,4.069431060261231e-8,3.060102035322918e-8,5.5071879810478866e-8 +UnValueData/5444,7.063156263358334e-5,7.057804157123944e-5,7.069859342276232e-5,1.996238140884392e-7,1.542720492926638e-7,2.4926521264495196e-7 +UnValueData/1275828,3.538882524236411e-2,3.478603513038184e-2,3.5932591351741185e-2,1.183941554805216e-3,7.744330568201735e-4,1.6523449296964045e-3 +UnValueData/1612534,4.737926376316742e-2,4.62776779509303e-2,4.8709034001214624e-2,2.4348585639314647e-3,1.5746940731853952e-3,3.9328173667833935e-3 +UnValueData/1734871,5.169557410313174e-2,5.04682756532513e-2,5.2880732401104205e-2,2.4318040000490286e-3,1.6238618054290877e-3,3.525916787897464e-3 +UnValueData/1047683,2.641131128597946e-2,2.5918685360555124e-2,2.6709702790024464e-2,7.695329072491731e-4,4.298971335444454e-4,1.332825756720731e-3 +UnValueData/33579,6.152426455998624e-4,6.148176875504924e-4,6.157060469860077e-4,1.5261796251918345e-6,1.288644080255388e-6,1.796888503460542e-6 +UnValueData/2939066,9.26512901297552e-2,9.023907482566565e-2,9.506057565571902e-2,3.998642818583841e-3,2.783073014538003e-3,6.727900341426262e-3 +UnValueData/1684804,5.1487146112206776e-2,5.0502978309739155e-2,5.2652781690950654e-2,2.091384208180315e-3,1.4675335874434114e-3,3.280664969660972e-3 +UnValueData/1247305,3.459056548895746e-2,3.412487858496163e-2,3.489230387579992e-2,7.677741055204657e-4,4.47621044576403e-4,1.1583840895400715e-3 +UnValueData/5130412,0.16981458419864223,0.16325395088642836,0.17271223401200966,6.016863028255257e-3,1.9548767624741675e-3,9.299252409692128e-3 +UnValueData/3609171,0.11841349425002201,0.11602325454420809,0.12104833646070412,4.081346296375948e-3,2.926312950107069e-3,5.494254156111412e-3 +UnValueData/1950504,6.320052693321689e-2,6.206578748869477e-2,6.439125182122434e-2,2.0702897863452336e-3,1.513519277421885e-3,3.3145439156368577e-3 +UnValueData/271219,5.031523948159418e-3,5.004123806872513e-3,5.052210004663146e-3,7.306414479334599e-5,5.0912722379372435e-5,1.0991753223006613e-4 +UnValueData/3580509,0.11745919117473975,0.11377198422754493,0.12064254725354702,5.25111169031894e-3,3.585995810264577e-3,7.687502014415927e-3 +UnValueData/3057844,9.653946980168776e-2,9.408781219461056e-2,9.780864584846077e-2,2.8770118126227847e-3,1.2885996102524905e-3,4.556584505851217e-3 +UnValueData/5673483,0.19078302505270886,0.18456831483894753,0.19503182816422648,7.061850089992917e-3,3.8511126574441645e-3,1.0086965889737357e-2 +UnValueData/4529,5.625718368900359e-5,5.623774328452426e-5,5.629127231353821e-5,8.678094600698326e-8,5.488153364553722e-8,1.491449287144414e-7 +UnValueData/4034848,0.13457402487041517,0.12930228858853557,0.1367327969776289,5.036560760839139e-3,1.5513411387421015e-3,7.899560240646458e-3 +UnValueData/474022,9.805654390060441e-3,9.753899276753719e-3,9.859140308874604e-3,1.4180011864017576e-4,1.0811060695524623e-4,1.8860835375446178e-4 +UnValueData/1831694,5.4992708895459506e-2,5.3810050151133465e-2,5.6280690193825374e-2,2.341608645119063e-3,1.3074225970835772e-3,3.94235789815771e-3 +UnValueData/2670712,8.26651621592926e-2,8.138630474348449e-2,8.431409838321131e-2,2.576492254751651e-3,1.2573055311387187e-3,4.44932088444523e-3 +UnValueData/2117254,6.863611344774988e-2,6.720114102994305e-2,6.94921848416342e-2,1.9754774895120383e-3,1.1332767466359756e-3,3.1940716312409095e-3 +UnValueData/2261844,7.048193999585929e-2,6.914867769720803e-2,7.146712106398562e-2,2.109635769978593e-3,1.2475559370112653e-3,3.3765680126158683e-3 +UnValueData/455168,1.0449800699444808e-2,1.0400068849978404e-2,1.0491944938338344e-2,1.2202157938707612e-4,8.986403452445767e-5,1.6712388985635403e-4 +UnValueData/1319482,3.950063670287641e-2,3.883719935405675e-2,4.0251589232390854e-2,1.4594368726337176e-3,9.261067520744372e-4,2.3081120539885105e-3 +UnValueData/152989,2.5965329380654386e-3,2.5838396408271727e-3,2.6051057952206714e-3,3.414947791954888e-5,2.5300625886029688e-5,4.76689285949758e-5 +UnValueData/10974,2.2697574332799172e-4,2.2683659999458297e-4,2.272447562959622e-4,6.057397762368306e-7,3.845644747906495e-7,1.0749201209116146e-6 +UnValueData/3691630,0.12319773742180717,0.12001946693663264,0.1260003725185968,4.406698122037507e-3,2.917801104444502e-3,6.276373978235909e-3 +UnValueData/1939259,5.8617135278751016e-2,5.702482455092231e-2,5.933012497948886e-2,1.7921968622351299e-3,7.721450142221724e-4,3.2390124987271168e-3 +UnValueData/202084,3.7703821813843386e-3,3.759376500364373e-3,3.7791312531530014e-3,3.439621073325981e-5,2.746593956654542e-5,4.404686468031192e-5 +UnValueData/4977464,0.16588871036086003,0.16072344034910202,0.17091598903418198,7.476364872295917e-3,4.69137783649583e-3,1.1944210928733824e-2 +UnValueData/2675807,8.77234403006289e-2,8.569994060943524e-2,8.85390866139815e-2,2.1492565120412623e-3,6.053499624658883e-4,3.6332337932161733e-3 +UnValueData/1646652,5.1892095547350296e-2,5.1256377560672535e-2,5.2457293943654074e-2,1.21240508552964e-3,9.395777310174762e-4,1.7311997357392101e-3 +UnValueData/442875,1.0217844956572268e-2,1.01606788886645e-2,1.0273542205872678e-2,1.4970650455225067e-4,1.1806841943842336e-4,1.9486376067482752e-4 +UnValueData/1218804,3.549055977064392e-2,3.5009643010831065e-2,3.595800491653723e-2,9.764448630159033e-4,6.293937019350363e-4,1.5894944475261681e-3 +UnValueData/3143456,0.10080232521111715,9.842218463333748e-2,0.10219765393592325,2.996856871256996e-3,1.4768703771080765e-3,4.710209046701973e-3 +UnValueData/1314338,3.7279427758090386e-2,3.6829950773914516e-2,3.768657982896742e-2,9.112051286569823e-4,6.313747519712489e-4,1.3543938646120163e-3 +UnValueData/201592,4.380088179555611e-3,4.370509130895144e-3,4.389290959128947e-3,3.022455726361525e-5,2.4408953433486835e-5,3.9399788029737926e-5 +UnValueData/910508,2.351005395746229e-2,2.3235037084557975e-2,2.41903310127284e-2,9.062658011207139e-4,3.6989662586122156e-4,1.693000534947892e-3 +UnValueData/3969013,0.1300488320723941,0.1266004712108822,0.1332678787293844,5.135393369043468e-3,3.440452006778816e-3,8.322783973869336e-3 +UnValueData/3429846,0.11217209955793805,0.10898463778236571,0.11529797055603316,4.779718065167384e-3,2.9571761719117337e-3,7.883906432417116e-3 +UnValueData/290104,7.187295906219642e-3,7.154558198153695e-3,7.216326370950873e-3,8.762410918099477e-5,5.972690566620994e-5,1.3214128640280976e-4 +UnValueData/1309284,3.84539475102095e-2,3.781680300899196e-2,3.907831123847283e-2,1.2818704971530644e-3,8.847947267276011e-4,2.040408084729673e-3 +UnValueData/30145,4.0607192508357564e-4,4.058249861764727e-4,4.0638758622843333e-4,9.274747513906685e-7,6.682446858137631e-7,1.3748319482782774e-6 +UnValueData/201814,4.103992603376012e-3,4.088651000708487e-3,4.1128834364904535e-3,3.43360316581495e-5,2.2758963126485183e-5,5.8545732644850565e-5 +UnValueData/2307904,7.358309062585765e-2,7.218055283709032e-2,7.556175181482923e-2,2.972594826418836e-3,1.7564457039264782e-3,5.108224053769436e-3 +UnValueData/942869,2.645375524770737e-2,2.6295833915344537e-2,2.658400715372948e-2,3.0238803368070027e-4,2.0658911742334137e-4,4.554496864733326e-4 +UnValueData/3066633,9.714020909860605e-2,9.408058526837866e-2,9.868559868442883e-2,3.398024340113775e-3,1.5939510685882108e-3,5.088663729577467e-3 +UnValueData/1256080,3.465983354970306e-2,3.419705321044698e-2,3.5023144250937804e-2,9.019721216417195e-4,3.984352477224662e-4,1.4786623858695051e-3 +UnValueData/1348804,3.832256070634588e-2,3.776391157830391e-2,3.876221402943205e-2,1.0372502062233494e-3,6.511066805053482e-4,1.68453125674602e-3 +UnValueData/1612828,5.086401175192149e-2,4.9854595441005824e-2,5.1837199296619715e-2,1.8245221979116828e-3,1.162131919470242e-3,3.944316792234646e-3 diff --git a/plutus-core/cost-model/data/builtinCostModelA.json b/plutus-core/cost-model/data/builtinCostModelA.json index 71443fee763..fbe4c0a3218 100644 --- a/plutus-core/cost-model/data/builtinCostModelA.json +++ b/plutus-core/cost-model/data/builtinCostModelA.json @@ -1209,8 +1209,8 @@ "lookupCoin": { "cpu": { "arguments": { - "intercept": 179661, - "slope": 7151 + "intercept": 209937, + "slope": 7181 }, "type": "linear_in_z" }, @@ -1223,7 +1223,7 @@ "cpu": { "arguments": { "intercept": 1000, - "slope": 130383 + "slope": 131959 }, "type": "linear_in_y" }, @@ -1234,7 +1234,7 @@ }, "valueData": { "cpu": { - "arguments": 153844, + "arguments": 182815, "type": "constant_cost" }, "memory": { @@ -1246,7 +1246,7 @@ "cpu": { "arguments": { "intercept": 1000, - "slope": 33094 + "slope": 33361 }, "type": "linear_in_x" }, diff --git a/plutus-core/cost-model/data/builtinCostModelB.json b/plutus-core/cost-model/data/builtinCostModelB.json index 76d7e47535c..43080c3de3d 100644 --- a/plutus-core/cost-model/data/builtinCostModelB.json +++ b/plutus-core/cost-model/data/builtinCostModelB.json @@ -1209,8 +1209,8 @@ "lookupCoin": { "cpu": { "arguments": { - "intercept": 179661, - "slope": 7151 + "intercept": 209937, + "slope": 7181 }, "type": "linear_in_z" }, @@ -1223,7 +1223,7 @@ "cpu": { "arguments": { "intercept": 1000, - "slope": 130383 + "slope": 131959 }, "type": "linear_in_y" }, @@ -1234,7 +1234,7 @@ }, "valueData": { "cpu": { - "arguments": 153844, + "arguments": 182815, "type": "constant_cost" }, "memory": { @@ -1246,7 +1246,7 @@ "cpu": { "arguments": { "intercept": 1000, - "slope": 33094 + "slope": 33361 }, "type": "linear_in_x" }, diff --git a/plutus-core/cost-model/data/builtinCostModelC.json b/plutus-core/cost-model/data/builtinCostModelC.json index 620f98d462d..dabd53de9f9 100644 --- a/plutus-core/cost-model/data/builtinCostModelC.json +++ b/plutus-core/cost-model/data/builtinCostModelC.json @@ -1227,8 +1227,8 @@ "lookupCoin": { "cpu": { "arguments": { - "intercept": 179661, - "slope": 7151 + "intercept": 209937, + "slope": 7181 }, "type": "linear_in_z" }, @@ -1241,7 +1241,7 @@ "cpu": { "arguments": { "intercept": 1000, - "slope": 130383 + "slope": 131959 }, "type": "linear_in_y" }, @@ -1252,7 +1252,7 @@ }, "valueData": { "cpu": { - "arguments": 153844, + "arguments": 182815, "type": "constant_cost" }, "memory": { @@ -1264,7 +1264,7 @@ "cpu": { "arguments": { "intercept": 1000, - "slope": 33094 + "slope": 33361 }, "type": "linear_in_x" }, From 6afef509d550a29f5e5733fe197148200d9bba2c Mon Sep 17 00:00:00 2001 From: Yura Lazaryev Date: Thu, 9 Oct 2025 13:45:04 +0200 Subject: [PATCH 14/17] docs: add changelog entry for Value builtin cost model updates Document the regeneration of benchmark data and cost model parameters for the four Value-related built-in functions following fresh benchmark measurements. --- ...26_Yuriy.Lazaryev_costing_builtin_value.md | 40 +++++++++++++++++++ 1 file changed, 40 insertions(+) create mode 100644 plutus-core/changelog.d/20251009_134326_Yuriy.Lazaryev_costing_builtin_value.md diff --git a/plutus-core/changelog.d/20251009_134326_Yuriy.Lazaryev_costing_builtin_value.md b/plutus-core/changelog.d/20251009_134326_Yuriy.Lazaryev_costing_builtin_value.md new file mode 100644 index 00000000000..65ca6532176 --- /dev/null +++ b/plutus-core/changelog.d/20251009_134326_Yuriy.Lazaryev_costing_builtin_value.md @@ -0,0 +1,40 @@ + + + + +### Changed + +- Updated benchmark data and cost model parameters for Value-related builtins (lookupCoin, valueContains, valueData, unValueData) based on fresh benchmark measurements. + + + From 3cee663bb0517882a7356f39de388af3053ae41f Mon Sep 17 00:00:00 2001 From: Yura Lazaryev Date: Thu, 9 Oct 2025 17:39:45 +0200 Subject: [PATCH 15/17] feat: regenerate cost models after rebase to account for validation overhead Regenerate cost model parameters based on fresh benchmark runs after rebasing on master. This accounts for the negative amount validation added to valueContains in commit 531f1b8d80. Updated cost models: - lookupCoin: linear_in_z (intercept: 203599, slope: 7256) - valueContains: linear_in_y (intercept: 1000, slope: 130720) - valueData: constant_cost (156990) - unValueData: linear_in_x (intercept: 1000, slope: 36194) The benchmark data includes 350 measurement points across varying input sizes. All three cost model variants (A, B, C) have been updated consistently with identical parameters. --- .../cost-model/data/benching-conway.csv | 700 +++++++++--------- .../cost-model/data/builtinCostModelA.json | 10 +- .../cost-model/data/builtinCostModelB.json | 10 +- .../cost-model/data/builtinCostModelC.json | 10 +- 4 files changed, 365 insertions(+), 365 deletions(-) diff --git a/plutus-core/cost-model/data/benching-conway.csv b/plutus-core/cost-model/data/benching-conway.csv index 078c8affec0..d70abe04906 100644 --- a/plutus-core/cost-model/data/benching-conway.csv +++ b/plutus-core/cost-model/data/benching-conway.csv @@ -12294,353 +12294,353 @@ Bls12_381_G2_multiScalarMul/97/97,6.90522012785712e-3,6.901544208299667e-3,6.918 Bls12_381_G2_multiScalarMul/98/98,6.9597205589059085e-3,6.9554579231546464e-3,6.963825444927238e-3,1.230537047747648e-5,9.828399035508776e-6,1.581113740579338e-5 Bls12_381_G2_multiScalarMul/99/99,6.998605748330429e-3,6.993956045528542e-3,7.003564931628933e-3,1.3941888558415054e-5,1.1848281516892752e-5,1.8598404587423643e-5 Bls12_381_G2_multiScalarMul/100/100,7.090569654857228e-3,7.08876305884669e-3,7.093035056145744e-3,6.187076669186285e-6,4.689206191622249e-6,8.297705725121281e-6 -LookupCoin/4/4/1,1.1785774616356424e-6,1.176759675417735e-6,1.1806482145561586e-6,6.518952731910493e-9,5.357289431456435e-9,7.516610936744955e-9 -LookupCoin/4/4/4,1.1915790498342047e-6,1.1904495568836964e-6,1.1929163022259065e-6,4.046963753072825e-9,3.253765563594344e-9,4.891006325615181e-9 -LookupCoin/4/4/4,1.2197204026484044e-6,1.218075576538306e-6,1.2212484144754842e-6,5.507469943923652e-9,4.712716305594179e-9,6.232237587140286e-9 -LookupCoin/4/4/6,1.2252608227748506e-6,1.2235791774580782e-6,1.2277132720598693e-6,6.957151909632548e-9,5.605938174417417e-9,9.311603666532503e-9 -LookupCoin/4/4/7,1.2418602679642457e-6,1.2407303791623337e-6,1.2431197653276957e-6,3.99250649949147e-9,3.411918822901681e-9,4.834889142361592e-9 -LookupCoin/4/4/9,1.252436317521741e-6,1.2507551577049629e-6,1.2539429485067685e-6,5.3310387004146845e-9,4.3975434417027795e-9,6.5714921376763815e-9 -LookupCoin/4/4/10,1.2537401387503317e-6,1.252648286911128e-6,1.2547423953179683e-6,3.4440238105385005e-9,2.9534534499958296e-9,4.125613685308116e-9 -LookupCoin/4/4/3,1.2057215465409478e-6,1.2044460334597588e-6,1.207164989903122e-6,4.686865699769265e-9,3.6827553294261967e-9,6.000559447477795e-9 -LookupCoin/4/4/4,1.2079863804193127e-6,1.2062767393037788e-6,1.209455432605573e-6,5.542921404445267e-9,4.568400282135385e-9,6.74255559935788e-9 -LookupCoin/4/4/5,1.2078112588041638e-6,1.2065310847461148e-6,1.2090989698102615e-6,4.2655061709200194e-9,3.589523090690231e-9,5.114850390355415e-9 -LookupCoin/4/4/10,1.251879129959111e-6,1.250448654698612e-6,1.2532910150820974e-6,4.850496728584338e-9,4.165199613881152e-9,5.683130521733482e-9 -LookupCoin/4/4/10,1.2559926083679484e-6,1.254502947718635e-6,1.2578907233923837e-6,5.566293829457432e-9,4.442793925127361e-9,6.972096189106762e-9 -LookupCoin/4/4/10,1.249098034119151e-6,1.2478638570938712e-6,1.2502401232848524e-6,3.85368192327935e-9,2.873830349334046e-9,4.877165673298007e-9 -LookupCoin/4/4/10,1.2509925558129945e-6,1.2494668973874963e-6,1.252556539885775e-6,5.337231950101119e-9,4.632577095408978e-9,6.383237841142989e-9 -LookupCoin/4/4/8,1.2233863922980728e-6,1.2217812130109416e-6,1.2253165110213577e-6,5.730758948653033e-9,4.8897490173656e-9,6.711697262501028e-9 -LookupCoin/4/4/10,1.2450032774185982e-6,1.2433505660563716e-6,1.2465189122949562e-6,5.488467504687887e-9,4.576582598573407e-9,6.894353701471729e-9 -LookupCoin/4/4/9,1.2468692466371783e-6,1.2461110966661758e-6,1.2478362619198501e-6,2.8920564681241693e-9,2.140996026586959e-9,4.042383292140468e-9 -LookupCoin/4/4/9,1.2645472621553918e-6,1.2628552137734403e-6,1.266814826437389e-6,6.692994388511391e-9,4.682033831438571e-9,1.114015606044514e-8 -LookupCoin/4/4/10,1.2566114821524705e-6,1.2557979400132496e-6,1.2574416492611602e-6,2.8610749903932396e-9,2.370368893421804e-9,3.5957306026909866e-9 -LookupCoin/4/4/10,1.2446254571928705e-6,1.2432512446989087e-6,1.2462616356472978e-6,5.177873574907882e-9,4.251966011717402e-9,6.355357327734962e-9 -LookupCoin/4/4/9,1.2444712146667099e-6,1.2422851093807456e-6,1.2470313061995245e-6,8.194720226422199e-9,7.417313720403413e-9,9.047922562422956e-9 -LookupCoin/4/4/10,1.2452922783829327e-6,1.2426782389000752e-6,1.2478871011039333e-6,8.69536851787927e-9,7.561027447830772e-9,1.0288038570035432e-8 -LookupCoin/4/4/10,1.2569093085899734e-6,1.2550653565207963e-6,1.2587022251705878e-6,6.3185708688609255e-9,5.514510441474091e-9,6.972988202607048e-9 -LookupCoin/4/4/10,1.2489826143715561e-6,1.2469685265561477e-6,1.2511630328057974e-6,7.100201363756892e-9,6.062358859136152e-9,8.66780270137926e-9 -LookupCoin/4/4/10,1.2452307795244152e-6,1.2444393916136893e-6,1.2461276908911376e-6,2.8381522217855915e-9,2.3872805232416765e-9,3.541533286949262e-9 -LookupCoin/4/4/5,1.2116606690899845e-6,1.209339198220783e-6,1.214589099273679e-6,9.032701335084981e-9,6.469230446272719e-9,1.590705235161601e-8 -LookupCoin/4/4/10,1.2710664848979752e-6,1.270126409383351e-6,1.2718915282049792e-6,2.8805540126875373e-9,2.3609698581581498e-9,3.467537330202418e-9 -LookupCoin/4/4/10,1.247569773426005e-6,1.245984275441814e-6,1.2496340754585717e-6,6.178591924990118e-9,4.9687538625385045e-9,7.447855996720255e-9 -LookupCoin/4/4/10,1.2595327258856138e-6,1.257935347781212e-6,1.2615465574208554e-6,5.995181661489849e-9,5.303650389083819e-9,6.79076639044681e-9 -LookupCoin/4/4/10,1.2491519336150866e-6,1.2472836812943233e-6,1.2511186254134189e-6,6.405006746538472e-9,5.695303745282024e-9,7.511945087364079e-9 -LookupCoin/4/4/9,1.2330398815253764e-6,1.2314827124398794e-6,1.234667542374372e-6,5.0953014783408485e-9,4.314569061537632e-9,6.431816983040218e-9 -LookupCoin/4/4/10,1.2584576728692458e-6,1.2566493818869613e-6,1.2598562714729147e-6,5.431724556407445e-9,4.75170101830403e-9,6.114342715438356e-9 -LookupCoin/4/4/8,1.2413153539822471e-6,1.2399259325158052e-6,1.2425207755239365e-6,4.445393838925636e-9,3.557600260889822e-9,5.453093256078417e-9 -LookupCoin/4/4/9,1.2546261146504752e-6,1.2536158679696334e-6,1.255661903024827e-6,3.5541084290018065e-9,2.9669833365451164e-9,4.456939978811789e-9 -LookupCoin/4/4/10,1.2520819257388385e-6,1.2508517263032954e-6,1.253314810552611e-6,4.18853433645004e-9,3.2375446221573444e-9,5.46068233337296e-9 -LookupCoin/4/4/9,1.2023990095945583e-6,1.2010986638653741e-6,1.2033492056604433e-6,3.607898542791623e-9,2.8144313526293303e-9,4.761587244004819e-9 -LookupCoin/4/4/10,1.250352076611688e-6,1.2489617040094347e-6,1.2516956063426574e-6,4.343586475072123e-9,3.6373382379341278e-9,5.352167899921192e-9 -LookupCoin/4/4/10,1.2531302054775177e-6,1.251180583674485e-6,1.2550644175453815e-6,6.3689806774659485e-9,5.543418685211649e-9,7.406072641207062e-9 -LookupCoin/4/4/9,1.2607861639944634e-6,1.2591039391746295e-6,1.262376754456549e-6,5.631413910392014e-9,4.873286642434556e-9,6.670239708059327e-9 -LookupCoin/4/4/10,1.2472815190346465e-6,1.2459804024642142e-6,1.2485571798697857e-6,4.357007238786791e-9,3.2631443656846903e-9,6.32552917556167e-9 -LookupCoin/4/4/9,1.2322042458451905e-6,1.230834730587035e-6,1.2336578108589346e-6,4.62169481769082e-9,3.632231204787403e-9,6.239122053129638e-9 -LookupCoin/4/4/9,1.2335733297697559e-6,1.2322460575702047e-6,1.2351153263372751e-6,4.847298295614193e-9,4.0828339383388015e-9,5.5874083333866524e-9 -LookupCoin/4/4/8,1.233413928611683e-6,1.2320348630372408e-6,1.2351257625156452e-6,5.003040272936572e-9,3.6701757631765112e-9,7.430463710167003e-9 -LookupCoin/4/4/9,1.2417609266633647e-6,1.2403519493393569e-6,1.2434541566079187e-6,5.031564754217582e-9,4.0240365091248306e-9,7.0840199812251356e-9 -LookupCoin/4/4/10,1.2531833500305536e-6,1.251925739940696e-6,1.2547792104092452e-6,4.630799965369312e-9,3.6914495833890097e-9,5.8681985579824406e-9 -LookupCoin/4/4/10,1.2462406348076252e-6,1.2439528066883627e-6,1.248600103616122e-6,8.013281486073616e-9,7.0979163851705234e-9,9.118216596200202e-9 -LookupCoin/4/4/8,1.2391228982048233e-6,1.2371343815590253e-6,1.241158101936117e-6,6.403733178552462e-9,5.596147443935133e-9,7.60968388905787e-9 -LookupCoin/4/4/9,1.2487485103365863e-6,1.2468732027369702e-6,1.2505639777254846e-6,6.184300800812291e-9,5.289566799969568e-9,7.158283370012036e-9 -LookupCoin/4/4/10,1.2429739536371046e-6,1.2414013103601145e-6,1.24574610236691e-6,6.948148263932397e-9,4.631343316733535e-9,1.1325999463368464e-8 -LookupCoin/4/4/10,1.2470182416765948e-6,1.2449623677385142e-6,1.2490389144770656e-6,7.140056517797011e-9,6.273113025798219e-9,8.234385642190435e-9 -LookupCoin/4/4/9,1.2180874857009812e-6,1.2170583876488178e-6,1.219913566991649e-6,4.4581934270227975e-9,3.1166224970646416e-9,7.18505389207211e-9 -LookupCoin/4/4/9,1.2419777826748983e-6,1.241153111207899e-6,1.242896719498676e-6,2.9101524915145297e-9,2.440436622888798e-9,3.673617181095772e-9 -LookupCoin/4/4/10,1.2416648688754131e-6,1.2403751130458364e-6,1.24309182764266e-6,4.385889790965116e-9,3.465870149371959e-9,5.937415720897578e-9 -LookupCoin/4/4/8,1.2317755110963195e-6,1.2296147412105458e-6,1.2337141754094538e-6,6.889872441606145e-9,6.1250358935872e-9,8.481318132612718e-9 -LookupCoin/4/4/10,1.2415389402914188e-6,1.2401643773486892e-6,1.242919629240299e-6,4.563755951362882e-9,3.769687443084677e-9,6.0684952291023795e-9 -LookupCoin/4/4/9,1.2475874527185102e-6,1.246416870807616e-6,1.2485656602935343e-6,3.671091402713257e-9,2.844615768485536e-9,4.673756345684205e-9 -LookupCoin/4/4/10,1.2492509162384606e-6,1.2476284092128534e-6,1.2510902029115656e-6,5.521799485791726e-9,4.677685901772419e-9,6.527274147220636e-9 -LookupCoin/4/4/10,1.2427450026656707e-6,1.2407219410327528e-6,1.244694170970827e-6,6.478591779094514e-9,5.774544148817447e-9,7.457783845616137e-9 -LookupCoin/4/4/10,1.2405678380218471e-6,1.239472517052258e-6,1.2419806027735965e-6,4.180190975320986e-9,3.2529654074885624e-9,6.4637540624838414e-9 -LookupCoin/4/4/9,1.2470985656204953e-6,1.2451911356361358e-6,1.2505604396142339e-6,8.64952179853078e-9,5.499440603862215e-9,1.6950749190632643e-8 -LookupCoin/4/4/7,1.2211888003478062e-6,1.2190011158181976e-6,1.2240882033814619e-6,8.080707957074064e-9,6.305138297317099e-9,1.1776649274884938e-8 -LookupCoin/4/4/9,1.246219310561986e-6,1.245437450978012e-6,1.246809450611543e-6,2.412046931433032e-9,1.8927550130235225e-9,3.0625303338979937e-9 -LookupCoin/4/4/10,1.2435562259612564e-6,1.2408279711741978e-6,1.2473329572788982e-6,1.0375907802602415e-8,7.558591085578553e-9,1.6619301178051737e-8 -LookupCoin/4/4/11,1.2566593790245024e-6,1.2547745390633302e-6,1.2580461459342272e-6,5.177468241484571e-9,4.4732163055357475e-9,5.97641360247158e-9 -LookupCoin/4/4/5,1.2222850423977606e-6,1.2198634245527795e-6,1.2245354078111845e-6,7.633968696095189e-9,6.5335072332637135e-9,9.542295348113819e-9 -LookupCoin/4/4/11,1.250724884648928e-6,1.2493655966439506e-6,1.2520092544978692e-6,4.525402933405244e-9,3.2639556504411075e-9,5.800440213532362e-9 -LookupCoin/4/4/10,1.2068371041422458e-6,1.2042905831069772e-6,1.2116967214131046e-6,1.1463478005529737e-8,5.926027070607464e-9,2.003439982144368e-8 -LookupCoin/4/4/11,1.249978109654377e-6,1.2485166300238452e-6,1.25129900312455e-6,4.5522270648791855e-9,3.779068074537687e-9,5.760482059895065e-9 -LookupCoin/4/4/11,1.2475821002420454e-6,1.2463425589908768e-6,1.248865157618701e-6,4.418533688654753e-9,3.831743248913124e-9,5.1355594110117185e-9 -LookupCoin/4/4/11,1.2824686538244592e-6,1.2806454501654126e-6,1.2835954633486922e-6,4.553276855116181e-9,3.2065092593393655e-9,6.510056588005699e-9 -LookupCoin/4/4/11,1.2476285657224824e-6,1.2458184354685831e-6,1.2493532691780388e-6,5.923501300843389e-9,4.982009348860194e-9,6.560467377310131e-9 -LookupCoin/4/4/10,1.255662696176642e-6,1.2545942315210734e-6,1.2570827230105889e-6,4.232617540673662e-9,3.122484000734275e-9,6.004940118545869e-9 -LookupCoin/4/4/11,1.2632371956169925e-6,1.262087452884752e-6,1.2646611536769036e-6,4.214692293096922e-9,3.6497836477963984e-9,4.99841094675237e-9 -LookupCoin/4/4/9,1.2263133139798144e-6,1.2249150844327286e-6,1.2280707543272765e-6,5.217563533857947e-9,4.248988064921147e-9,6.850915601279552e-9 -LookupCoin/4/4/10,1.267580407468345e-6,1.2664251919122808e-6,1.2695814693671906e-6,5.060835604571611e-9,3.2744441882488892e-9,7.801696075872192e-9 -LookupCoin/4/4/10,1.2702550540307273e-6,1.2690361316721864e-6,1.271785886281737e-6,4.709580062307059e-9,3.9172281586586234e-9,5.760859480023366e-9 -LookupCoin/4/4/11,1.2772109439969944e-6,1.2752148793757192e-6,1.2786659829042811e-6,5.310849216638733e-9,3.836083745065901e-9,6.7941489720876594e-9 -LookupCoin/4/4/10,1.2429060453469263e-6,1.241245013919552e-6,1.245271552789436e-6,6.453920574459102e-9,5.463370128053782e-9,8.250494923386193e-9 -LookupCoin/4/4/11,1.2594845920498652e-6,1.258829512116578e-6,1.260081082924469e-6,2.1840304469199286e-9,1.929810006251522e-9,2.5721154106385036e-9 -LookupCoin/4/4/7,1.2449795444125502e-6,1.2438519079844736e-6,1.2460009518989505e-6,3.72631134649154e-9,3.0567838293096365e-9,4.601298942970308e-9 -LookupCoin/4/4/10,1.2587275547920323e-6,1.2580585680492439e-6,1.259294861967665e-6,2.1665285788944064e-9,1.7655283969560557e-9,2.8149181705908985e-9 -LookupCoin/4/4/11,1.2671369502797785e-6,1.266381262906568e-6,1.2682294936447123e-6,3.0391615578004883e-9,2.237439249413991e-9,4.726796071503188e-9 -LookupCoin/4/4/9,1.2460256783078088e-6,1.2448213298091874e-6,1.2474381416771475e-6,4.247057528773148e-9,3.565074908939502e-9,5.109792473606806e-9 -LookupCoin/4/4/11,1.2625785490051976e-6,1.2603402876663008e-6,1.264523471792608e-6,6.7216716870891865e-9,4.822707811606611e-9,9.658444882223709e-9 -LookupCoin/4/4/11,1.2601724350236416e-6,1.2586076567572118e-6,1.2614463262986e-6,4.646575684248816e-9,3.8569144585025716e-9,5.701170676573042e-9 -LookupCoin/4/4/11,1.2594666014956414e-6,1.2569066914216517e-6,1.2620469447074957e-6,8.113755699691054e-9,7.0889147017881055e-9,9.790857188751279e-9 -LookupCoin/4/4/11,1.2483322547313684e-6,1.246922398829055e-6,1.2494618661208718e-6,4.227096626061319e-9,3.2964584498552177e-9,5.176462746379732e-9 -LookupCoin/4/4/10,1.2507030318964978e-6,1.2497114457152014e-6,1.2518263125459921e-6,3.514907595086918e-9,3.0336391285036447e-9,4.049502069340815e-9 -LookupCoin/4/4/11,1.2659144388382993e-6,1.2640341608364966e-6,1.267648709453335e-6,5.736216813757631e-9,5.160343354957749e-9,6.481641342850583e-9 -LookupCoin/4/4/10,1.2400762810239897e-6,1.2391963219245801e-6,1.241097346130724e-6,3.135263351241175e-9,2.7279430658895024e-9,3.748231837374052e-9 -LookupCoin/4/4/11,1.263973766364745e-6,1.2618998592797444e-6,1.266156012888118e-6,6.702539803669301e-9,5.986254231935802e-9,7.679041022313684e-9 -LookupCoin/4/4/11,1.2518657549321e-6,1.249698041364627e-6,1.2543520787819552e-6,8.21492363743867e-9,7.502152116069559e-9,9.032819253550832e-9 -LookupCoin/4/4/11,1.2447452163543908e-6,1.2432615426074351e-6,1.24614768243031e-6,4.508507282143032e-9,3.6427744855388576e-9,5.5518638783273744e-9 -LookupCoin/4/4/10,1.2547778124119448e-6,1.2531725308913239e-6,1.256177821583896e-6,5.004623276948704e-9,4.2643369888211545e-9,6.5759544545108475e-9 -LookupCoin/4/4/11,1.262101773693123e-6,1.260538976123052e-6,1.263577789695053e-6,4.97866214878748e-9,4.164670845113131e-9,6.300658435484918e-9 -LookupCoin/4/4/10,1.2494335719693193e-6,1.2476880983976523e-6,1.2514891224272283e-6,6.418555268694696e-9,5.366391848815581e-9,7.513651464226535e-9 -LookupCoin/4/4/11,1.2387548743791755e-6,1.237845436760153e-6,1.2405509071249566e-6,4.28984778905161e-9,2.9691107844361234e-9,7.046837709689141e-9 -LookupCoin/4/4/11,1.2677106259147114e-6,1.265969981450797e-6,1.2691891201905115e-6,5.163314212047524e-9,4.1805760847750965e-9,6.592570331142436e-9 -LookupCoin/4/4/11,1.2567718001024835e-6,1.2544537416887077e-6,1.2597352116935727e-6,8.85986967326852e-9,7.398492441824828e-9,1.2428211768407896e-8 -LookupCoin/4/4/10,1.2389168105488148e-6,1.2375955513750582e-6,1.2400231775571017e-6,4.008816976653277e-9,3.2399733821715353e-9,4.987886471339023e-9 -LookupCoin/4/4/10,1.2509606088835598e-6,1.249057560262197e-6,1.2533980097055831e-6,7.0078540806729966e-9,5.515720387811593e-9,1.0425137894541599e-8 -LookupCoin/4/4/10,1.2560702825481937e-6,1.254182357902354e-6,1.2578364303624702e-6,6.3074612066411135e-9,5.402658501938011e-9,7.1755182224242935e-9 -LookupCoin/4/4/11,1.261477281509439e-6,1.2598608323447094e-6,1.2645048495194436e-6,7.3215983161567294e-9,5.06978493862556e-9,1.2070413799448123e-8 -LookupCoin/4/4/11,1.2505703363027947e-6,1.2485366337552197e-6,1.2525612822110055e-6,6.7275076765512455e-9,5.656662242601031e-9,8.177635928720666e-9 -LookupCoin/4/4/10,1.252750231643778e-6,1.2519391911460776e-6,1.25370618678725e-6,2.9367119134048805e-9,2.3846107743696134e-9,4.452664454286303e-9 -LookupCoin/4/4/11,1.2651209512343535e-6,1.2640485350872299e-6,1.2665477595295832e-6,4.445028596926021e-9,3.5798373563486984e-9,5.613910810172365e-9 -LookupCoin/4/4/9,1.2380226585104609e-6,1.2362900280118667e-6,1.2394597324025156e-6,5.098746547729719e-9,4.0008517314912585e-9,6.17440360947907e-9 -LookupCoin/4/4/11,1.2703297022532047e-6,1.2682373544251785e-6,1.2725687697034899e-6,7.1697855080640995e-9,6.362672547516085e-9,7.955775896416468e-9 -LookupCoin/4/4/9,1.2512604199844874e-6,1.2492795128279614e-6,1.2524030795580555e-6,4.9877478857470085e-9,2.6403970450768774e-9,7.84666258604664e-9 -LookupCoin/4/4/11,1.25530062493191e-6,1.2538911148269256e-6,1.256762557605688e-6,4.89632318090818e-9,4.121922806649131e-9,5.647847583992622e-9 -LookupCoin/4/4/11,1.244886197896722e-6,1.2442984295041443e-6,1.2455696642306306e-6,2.1744201587193866e-9,1.8222381766251497e-9,2.7778320145962305e-9 -LookupCoin/4/4/9,1.2399591441601689e-6,1.2389190944878488e-6,1.241535033732355e-6,4.328263567193719e-9,3.0591536458771003e-9,7.148980702975058e-9 -LookupCoin/4/4/11,1.2486555145560358e-6,1.246992527911053e-6,1.2499947696601263e-6,5.260233301569391e-9,4.470520683516049e-9,6.335261171113161e-9 -LookupCoin/4/4/11,1.2474333744884636e-6,1.2463055183966161e-6,1.2488613195097239e-6,4.384271706272338e-9,3.3913447781582296e-9,5.620648578678502e-9 -LookupCoin/4/4/8,1.2334567415991134e-6,1.232841971210817e-6,1.2340915474552801e-6,2.0301269087575176e-9,1.6381181131674423e-9,2.574270880546165e-9 -ValueContains/4/1,1.105434543510619e-6,1.104761669698638e-6,1.1063157641412615e-6,2.5006074729243277e-9,1.9669982721380314e-9,3.4335626539358642e-9 -ValueContains/4/0,1.0306397386859852e-6,1.028800477510463e-6,1.0326739767127572e-6,6.616346473915064e-9,6.193309934090764e-9,7.092235734931024e-9 -ValueContains/4/10,1.820720834681636e-6,1.8191253437797686e-6,1.8232358592510541e-6,6.763821102008429e-9,4.673938452762895e-9,1.0315848552337634e-8 -ValueContains/7/0,1.0252209862077256e-6,1.024618617182076e-6,1.0258351403077722e-6,2.1175286634167027e-9,1.8802323738637716e-9,2.3741920511291424e-9 -ValueContains/7/0,1.0280232194067423e-6,1.026147003532159e-6,1.0299502826838859e-6,6.6761800893311246e-9,5.844848366093946e-9,7.621882989357328e-9 -ValueContains/7/100,1.214555391020298e-5,1.2113948799568427e-5,1.2168651147537038e-5,9.779236859850173e-8,7.466824051239605e-8,1.290089244182694e-7 -ValueContains/10/0,1.0285184266132384e-6,1.0270438056630502e-6,1.0297528205450551e-6,4.695725307334156e-9,3.6900650397944465e-9,6.236441473384819e-9 -ValueContains/10/0,1.0263040164773018e-6,1.0248999834722293e-6,1.0281672020073887e-6,5.2621977948493825e-9,3.920032953487552e-9,6.786795094325855e-9 -ValueContains/10/0,1.0223050687143138e-6,1.0214652962394742e-6,1.02428431951749e-6,4.320538557649969e-9,2.1763514970030737e-9,8.183340862647313e-9 -ValueContains/10/1000,1.3293093433683166e-4,1.328007675682534e-4,1.330761492549652e-4,4.6952283865058516e-7,3.797641833707987e-7,5.965668337160833e-7 -ValueContains/5/200,1.6503035639538536e-5,1.6492615656743238e-5,1.652001562155218e-5,4.719531447553505e-8,3.116649329387387e-8,7.663918693214212e-8 -ValueContains/1/0,1.0140103329349797e-6,1.0133749711003663e-6,1.0146722566964554e-6,2.2098469290476243e-9,1.7252381027510976e-9,3.0448743578033727e-9 -ValueContains/4/0,1.0243604560021716e-6,1.0221135174097028e-6,1.0265054031795115e-6,6.995648455944508e-9,5.896134154624651e-9,8.338092410022835e-9 -ValueContains/7/0,1.0306611958595134e-6,1.0282909768284086e-6,1.032360391015259e-6,6.4096520173214514e-9,4.613845016528073e-9,7.985244408860542e-9 -ValueContains/10/0,1.0246081379431291e-6,1.0226349717738905e-6,1.0272466609220711e-6,7.336532498054823e-9,6.2703178287046045e-9,9.543486985491354e-9 -ValueContains/10/646,7.441283070704394e-5,7.43784527236331e-5,7.445334613303153e-5,1.2652896884550386e-7,9.682926240156536e-8,1.6517639740827547e-7 -ValueContains/12/1358,1.6815208792024118e-4,1.6801249062461747e-4,1.683697543385396e-4,5.683078446110742e-7,3.6254491417830065e-7,1.0188119073030313e-6 -ValueContains/12/1165,1.488730510294422e-4,1.4883083320586053e-4,1.4894906949057245e-4,1.7525791994769714e-7,1.2028745351972862e-7,2.904692560082104e-7 -ValueContains/11/1291,1.5744929873441713e-4,1.5733887209082092e-4,1.576521837252153e-4,4.778509795564433e-7,3.2166058589942764e-7,7.738721371331961e-7 -ValueContains/10/998,1.1769401376810234e-4,1.175866182768469e-4,1.1779423082385351e-4,3.644027956706522e-7,3.1439828134125906e-7,4.1708799263704205e-7 -ValueContains/11/977,1.1597171501481696e-4,1.1590377470108519e-4,1.1611919805174089e-4,3.3555975827259076e-7,1.684220641376806e-7,6.274138667382754e-7 -ValueContains/13/370,4.9042983606935425e-5,4.901990115467035e-5,4.9072765036134805e-5,9.315363198270772e-8,6.571454491625358e-8,1.410408886683234e-7 -ValueContains/12/3033,3.954000098741814e-4,3.9505425268160485e-4,3.9600008358255974e-4,1.4748756053438227e-6,8.927150332810167e-7,2.6335053757918597e-6 -ValueContains/13/2884,3.820988400883808e-4,3.820432673545169e-4,3.8216145711987326e-4,2.0065292972365346e-7,1.6677728225330086e-7,2.5293391932034945e-7 -ValueContains/7/61,5.724093459596734e-6,5.712072631283652e-6,5.737850135956423e-6,4.292519299064555e-8,3.583252164197087e-8,5.685966772277251e-8 -ValueContains/12/596,7.276195428181185e-5,7.27292343015308e-5,7.281506484537547e-5,1.3941999073003655e-7,8.516005638835006e-8,2.178771895942148e-7 -ValueContains/12/1042,1.326226108648041e-4,1.3249750443789052e-4,1.330446334034546e-4,6.807757078902529e-7,1.9096025943030226e-7,1.3866327183932838e-6 -ValueContains/7/45,4.531518268866434e-6,4.526054255525554e-6,4.539353846578104e-6,2.2055581276136084e-8,1.9124314926478775e-8,2.641271749763396e-8 -ValueContains/12/843,1.047847990246496e-4,1.0469850850759846e-4,1.0517405993592751e-4,5.163085093891324e-7,1.029915924970202e-7,1.15964961296233e-6 -ValueContains/12/2476,3.206175835857794e-4,3.2054668126016233e-4,3.2072027577290655e-4,2.871260879068344e-7,2.0686047545757418e-7,4.0564344814662266e-7 -ValueContains/10/905,1.060932626401992e-4,1.0603241495905132e-4,1.0625809058707843e-4,3.0425668238843574e-7,1.3872548253346558e-7,5.768341435609618e-7 -ValueContains/13/1853,2.398676338723237e-4,2.3982315100902393e-4,2.3992903068258532e-4,1.6787080994715174e-7,1.272986305753252e-7,2.562178324460746e-7 -ValueContains/9/211,2.3241070684104172e-5,2.3219853813195678e-5,2.3267199165385782e-5,7.916610845106641e-8,5.678895369841774e-8,1.2844030824010097e-7 -ValueContains/12/3149,4.053205885826389e-4,4.052364280370845e-4,4.054533293956877e-4,3.483064322018529e-7,2.386353952377759e-7,5.100052812828452e-7 -ValueContains/11/997,1.1979601908866435e-4,1.1964607048393313e-4,1.2019172120249887e-4,8.007959364807597e-7,4.268431968692829e-7,1.468850226791584e-6 -ValueContains/12/63,8.477595458556624e-6,8.469514037945754e-6,8.48870380587104e-6,3.289714464788442e-8,2.8027260298508268e-8,4.04664755206175e-8 -ValueContains/11/833,1.0019015554687506e-4,1.0011840782240724e-4,1.0032847381252279e-4,3.2048950930382616e-7,1.9607669251094275e-7,5.558785603702673e-7 -ValueContains/12/1396,1.791641752310758e-4,1.790648874977756e-4,1.792906943941706e-4,3.910369867417785e-7,2.9055353677751513e-7,4.943280688124263e-7 -ValueContains/11/999,1.1960282097559351e-4,1.1952034354510336e-4,1.1989610054844092e-4,4.387334699430444e-7,1.75347492797394e-7,9.489745653188127e-7 -ValueContains/12/377,4.9268527063048286e-5,4.92458556144685e-5,4.930304872085852e-5,8.547419940709613e-8,6.144316820489737e-8,1.1435969493440315e-7 -ValueContains/11/375,4.502966455405575e-5,4.4996404789337704e-5,4.5103226489301955e-5,1.543294999693142e-7,7.141805309458704e-8,3.0580115765887084e-7 -ValueContains/13/2268,2.9853066805901585e-4,2.984288596048085e-4,2.987156786493456e-4,4.4334013044019857e-7,3.1213691628991156e-7,6.309871710987987e-7 -ValueContains/8/156,1.6435523637515978e-5,1.642570000016781e-5,1.6444351496447234e-5,3.199701420893554e-8,2.6320257705438826e-8,4.113050725667119e-8 -ValueContains/11/953,1.1254710757347861e-4,1.1251409678969029e-4,1.1259323161640841e-4,1.3247832019796597e-7,1.0481391039741116e-7,1.6317952880011978e-7 -ValueContains/13/531,6.722172127439049e-5,6.7141806531495e-5,6.758557600845466e-5,4.797650396818759e-7,1.052597340557341e-7,1.0706484974322888e-6 -ValueContains/12/2298,2.9534540322019836e-4,2.9476549321575383e-4,2.968912027074983e-4,2.7264220973975565e-6,2.564165051847216e-7,5.425325609838385e-6 -ValueContains/12/390,4.803131363004283e-5,4.7991037693599024e-5,4.814213019798374e-5,1.9784949880825503e-7,9.084699751568076e-8,3.8402545346945097e-7 -ValueContains/11/90,1.0964518538526184e-5,1.0956047380495303e-5,1.0973930920667138e-5,3.0220549623052384e-8,2.5451127869939373e-8,3.689602601711146e-8 -ValueContains/12/1765,2.2191669166752722e-4,2.2171853222201495e-4,2.2242359166528946e-4,1.0196637342158027e-6,4.739033004648279e-7,2.0226821395999575e-6 -ValueContains/8/138,1.4059720594516508e-5,1.4051939255563339e-5,1.4071461179695633e-5,3.0636780375753266e-8,2.090202202749129e-8,4.321581009323182e-8 -ValueContains/12/1818,2.424236552202903e-4,2.4222666660322738e-4,2.4303811894505544e-4,1.0407167560159624e-6,4.000641517049369e-7,2.0672745947498194e-6 -ValueContains/13/3251,4.287348073060723e-4,4.2859131672895294e-4,4.289712803376432e-4,6.296789036808865e-7,4.164747058995414e-7,1.0300660804876753e-6 -ValueContains/9/375,4.2127877178920495e-5,4.208522745503054e-5,4.22177746390498e-5,2.026686870691483e-7,1.0598115655851085e-7,3.998411429342358e-7 -ValueContains/12/415,5.1223984617488054e-5,5.1200368120805436e-5,5.1250291238085066e-5,8.784310981732528e-8,6.264693948228433e-8,1.4712070847594412e-7 -ValueContains/13/1497,1.987664901375959e-4,1.9852875412114182e-4,1.9952989050732664e-4,1.3357046915971355e-6,4.232048833454561e-7,2.690932419150629e-6 -ValueContains/12/588,7.609657701697021e-5,7.60704189672081e-5,7.61302074615819e-5,9.707686719213686e-8,8.193430682587038e-8,1.206116106566066e-7 -ValueContains/12/1079,1.3282491359168218e-4,1.3278256702678074e-4,1.3287295880426772e-4,1.5162208469969725e-7,1.21731971058478e-7,2.0652890452078913e-7 -ValueContains/13/2290,3.0017499838337397e-4,3.0009808624299414e-4,3.002733886994872e-4,2.979611803890221e-7,2.3292533684262637e-7,3.9405349548164203e-7 -ValueContains/10/45,5.887778235971029e-6,5.882112081863332e-6,5.893851931166322e-6,2.01279437294267e-8,1.702777980890875e-8,2.599683733803629e-8 -ValueContains/11/742,9.131898189290163e-5,9.12757401951564e-5,9.136409750554772e-5,1.481028947911416e-7,1.2096382212492334e-7,1.8312611699589294e-7 -ValueContains/10/298,3.533820991336732e-5,3.532230857317866e-5,3.535444863431016e-5,5.286330819841384e-8,4.3823959909992985e-8,6.43855767534137e-8 -ValueContains/12/515,6.738708848391595e-5,6.735189737115322e-5,6.741837286038623e-5,1.0564164187449367e-7,8.916338903006408e-8,1.2330582038591818e-7 -ValueContains/12/489,5.99591026385554e-5,5.992211308955975e-5,6.001279979970592e-5,1.5116792038111816e-7,9.253121526527911e-8,2.265785823242215e-7 -ValueContains/13/2291,3.1149480339926015e-4,3.112743669968882e-4,3.1204881853179686e-4,1.037230082693866e-6,5.18940645889787e-7,1.890466739075077e-6 -ValueContains/12/184,2.3282846136456296e-5,2.3255417267824355e-5,2.331506926535788e-5,1.0091162302207955e-7,8.70753354986584e-8,1.1583240073582862e-7 -ValueContains/11/1622,1.9812267667886877e-4,1.9802036488066814e-4,1.9826799056670618e-4,3.9089080404453247e-7,2.941462537295892e-7,5.616758128592064e-7 -ValueContains/11/1103,1.3043614696358626e-4,1.303836848282631e-4,1.304929533429926e-4,1.8325946113827698e-7,1.4252476107083352e-7,2.464251219431128e-7 -ValueContains/12/833,1.0243524009510309e-4,1.0240408969358041e-4,1.0248056007238512e-4,1.22568392180608e-7,9.352560290740514e-8,1.7106802473446964e-7 -ValueContains/10/166,1.8807292208057004e-5,1.8782664632152158e-5,1.8832642314387125e-5,8.505942756167824e-8,7.390178728552626e-8,9.993723382366903e-8 -ValueContains/12/1270,1.6295986438092945e-4,1.6289830167437184e-4,1.6306011112165262e-4,2.8263817997579223e-7,1.9475736964171977e-7,4.928254794077895e-7 -ValueContains/11/287,3.521145389839651e-5,3.518599530249471e-5,3.5256452151419566e-5,1.166283369349522e-7,7.992628995786976e-8,1.927854012616892e-7 -ValueContains/10/912,1.071642176152517e-4,1.0708505345588232e-4,1.0746464358857595e-4,4.4590841007547816e-7,1.125591676639726e-7,9.227484266041511e-7 -ValueContains/12/1892,2.4434978476151856e-4,2.4430678593079436e-4,2.4440644018393646e-4,1.6783993154812263e-7,1.3583143838326006e-7,2.2285878765144933e-7 -ValueContains/12/1863,2.3608685664246537e-4,2.3603195757177634e-4,2.3617656726364477e-4,2.4081722466297496e-7,1.6857087371863572e-7,3.5876027011889764e-7 -ValueContains/10/577,6.60213853409024e-5,6.59978372496058e-5,6.605862283578572e-5,9.651005007816427e-8,7.026133825107891e-8,1.5485715967503996e-7 -ValueContains/12/1231,1.593963366747364e-4,1.5933680121769334e-4,1.594565359346893e-4,1.9786660178980482e-7,1.5361444979162913e-7,2.650700982126226e-7 -ValueContains/12/2931,3.722377996327141e-4,3.7205561267537505e-4,3.7248410813460887e-4,6.865993893471296e-7,5.373982811138052e-7,9.494962627994329e-7 -ValueContains/13/4382,5.814563169246447e-4,5.813342500148208e-4,5.816325702849465e-4,5.094744549521182e-7,3.8306107926475136e-7,8.167624785920538e-7 -ValueContains/12/1565,1.9923057588953856e-4,1.9917579510814635e-4,1.992989897592509e-4,1.9768045522226999e-7,1.62120079585953e-7,2.959690651991732e-7 -ValueContains/11/56,7.049112065774829e-6,7.041332035193911e-6,7.056127465548296e-6,2.505808622301429e-8,2.0508139111524797e-8,3.193362898655345e-8 -ValueContains/11/372,4.2994661318304265e-5,4.297774695404077e-5,4.3016054077768e-5,6.40259121611655e-8,5.342079873707793e-8,8.193141363157006e-8 -ValueContains/12/1409,1.8298640251247647e-4,1.828956388989965e-4,1.831225937031092e-4,3.6755011456854844e-7,2.419447623751336e-7,6.077541441558001e-7 -ValueContains/12/2411,3.144557275816184e-4,3.1433530606879016e-4,3.146722906304664e-4,5.403181114817953e-7,3.929803869702245e-7,7.897920675234983e-7 -ValueContains/12/2022,2.5625710548620497e-4,2.561676036513246e-4,2.563470391509658e-4,3.0049331661144854e-7,2.567272449637465e-7,3.676583526502356e-7 -ValueContains/8/169,1.7567833586422405e-5,1.7537519109719872e-5,1.7606200569759918e-5,1.1265019366997327e-7,9.717704176025805e-8,1.3195230018012848e-7 -ValueContains/12/2128,2.699247947339283e-4,2.698240077337551e-4,2.701565976749698e-4,4.651855280997162e-7,2.711381101183825e-7,8.77842077493533e-7 -ValueContains/11/984,1.1937167865455437e-4,1.1928473503062602e-4,1.1967742707817802e-4,5.008963833613214e-7,1.4061253764269697e-7,1.0296267731926103e-6 -ValueContains/11/262,3.1544192277398865e-5,3.15095266680693e-5,3.158007062905678e-5,1.1764242238434015e-7,1.0128604715566369e-7,1.3934900641952566e-7 -ValueContains/13/1362,1.7908436398682647e-4,1.7901920469637036e-4,1.792162858046282e-4,2.9150352884122645e-7,1.5708689878298075e-7,5.206287603533956e-7 -ValueContains/13/3396,4.4285323819141055e-4,4.4268075065829717e-4,4.430977340159761e-4,6.896050060773073e-7,4.496001729624406e-7,1.1434657060778898e-6 -ValueContains/12/845,1.1222378575879455e-4,1.1217748665402018e-4,1.1227615614207284e-4,1.604006691837945e-7,1.2727793390926994e-7,2.1030416112254738e-7 -ValueContains/13/3273,4.331549571719631e-4,4.328868162395225e-4,4.334481397429046e-4,9.392917286548258e-7,6.89113913639228e-7,1.403638475432845e-6 -ValueContains/10/503,5.743197405717264e-5,5.7379791535214774e-5,5.7509040694888954e-5,1.978597540887674e-7,1.487696747366074e-7,2.5917502875732304e-7 -ValueContains/11/421,4.9284396577657796e-5,4.924871756163534e-5,4.9324237123028804e-5,1.2514542238741243e-7,1.0366933208028346e-7,1.565381916787151e-7 -ValueContains/11/88,1.0997944692881061e-5,1.0976417633640176e-5,1.102884717031259e-5,8.153902360416276e-8,6.290666182681504e-8,1.0133976895898452e-7 -ValueContains/12/2096,2.695700404524966e-4,2.694899225900187e-4,2.6976295760082583e-4,3.892841130919495e-7,2.135037546528592e-7,6.987062420690264e-7 -ValueContains/12/958,1.2775525674266257e-4,1.277236828615857e-4,1.278013960537453e-4,1.2479726066035998e-7,9.26071656390998e-8,1.9392807499720426e-7 -ValueContains/12/2635,3.4406649791623057e-4,3.4399273206417767e-4,3.44216954510562e-4,3.616196961263488e-7,1.9102208009623364e-7,6.550070593423511e-7 -ValueContains/7/54,5.331028378799725e-6,5.327189332578184e-6,5.334778869443724e-6,1.3495644741628291e-8,1.1246036301715161e-8,1.5989744242932852e-8 -ValueContains/12/3154,4.063129808051071e-4,4.061286928451106e-4,4.066708017503966e-4,8.699231488189299e-7,4.823254059562437e-7,1.6881632390449117e-6 -ValueContains/13/3744,5.016773266714847e-4,5.01589233851217e-4,5.017989967578292e-4,3.530234641028672e-7,2.716653085568384e-7,4.890190946962745e-7 -ValueContains/11/355,4.180919772508725e-5,4.178547778650308e-5,4.1840456224693724e-5,9.000584786498028e-8,7.364125269427776e-8,1.2389877930887057e-7 -ValueContains/11/980,1.2275675690234686e-4,1.2267487588957997e-4,1.2284925514429059e-4,2.9684048482151794e-7,2.3492153821048423e-7,3.825219659316146e-7 -ValueContains/13/3350,4.429107862668096e-4,4.427642322701703e-4,4.431400153255526e-4,6.006361097385757e-7,3.9545434226110795e-7,9.71636201816491e-7 -ValueContains/13/2294,3.0339158169837086e-4,3.033114381472984e-4,3.034836585298028e-4,2.940425264542992e-7,2.3676491577331085e-7,3.8139540522221467e-7 -ValueContains/13/4444,5.962139868447767e-4,5.959720657251243e-4,5.966065129669149e-4,1.055438883627953e-6,7.139647588747463e-7,1.7257747081792733e-6 -ValueContains/12/1882,2.3371214655523747e-4,2.335936618456013e-4,2.3383204858605503e-4,3.768029448605273e-7,3.022341201904928e-7,4.753401461074988e-7 -ValueContains/12/1262,1.642018935406448e-4,1.640671385807914e-4,1.6435845252788618e-4,4.966588324910747e-7,3.819941467699423e-7,8.033481132996157e-7 -ValueContains/11/657,7.792025571447051e-5,7.789441602608649e-5,7.794886611340072e-5,9.17920692696743e-8,7.390091468742131e-8,1.3985276267618588e-7 -ValueContains/12/2180,2.713135309176018e-4,2.711645227193468e-4,2.714849915155506e-4,5.468013004134306e-7,4.0954215109699106e-7,7.382800322293021e-7 -ValueContains/13/728,1.0143838523683126e-4,1.0140438327118037e-4,1.0149493728776178e-4,1.4194640230833648e-7,8.794872412714315e-8,2.100494976780515e-7 -ValueContains/12/1296,1.6374830773475144e-4,1.636295451404291e-4,1.6390825706682273e-4,4.5512986164665656e-7,3.7695923281399107e-7,6.060230167904003e-7 -ValueContains/11/701,8.469772846558616e-5,8.468168710623024e-5,8.472143871798954e-5,6.716883242925578e-8,5.030538318708717e-8,9.885784695058379e-8 -ValueContains/13/2528,3.3662004066964337e-4,3.3647921660858853e-4,3.3701721396276325e-4,7.531951114588133e-7,2.257640172910717e-7,1.5339742876432358e-6 -ValueContains/10/662,7.799822503281861e-5,7.795432920805907e-5,7.804605390057409e-5,1.606065609463777e-7,1.354602544006714e-7,2.0584373791285545e-7 -ValueData/0,8.491889096596671e-7,8.474502971660789e-7,8.506137758572909e-7,5.111329214539667e-9,4.303481093916784e-9,6.103052824928771e-9 -ValueData/10,8.536772612315314e-7,8.530765418662205e-7,8.542350819040113e-7,1.90548352139756e-9,1.5398189665210485e-9,2.4639909342920807e-9 -ValueData/100,8.509232117281916e-7,8.497187371872595e-7,8.517056976917077e-7,3.2050058154741175e-9,2.1397215304619156e-9,5.201039230687773e-9 -ValueData/500,8.535831001721129e-7,8.528371095228981e-7,8.542402261485153e-7,2.404886756201847e-9,2.0544097108108714e-9,2.9019636521671364e-9 -ValueData/1000,8.503620064745987e-7,8.492727336826363e-7,8.510805271844457e-7,2.8523021844990105e-9,1.9000300247769356e-9,4.26410511879433e-9 -ValueData/5000,8.456274218841898e-7,8.434758384943089e-7,8.479169679014288e-7,7.424813273560543e-9,6.40171810297941e-9,8.937594000856933e-9 -ValueData/10000,8.521692129306124e-7,8.513322986331105e-7,8.531729305605561e-7,3.202011936525637e-9,2.735499160701126e-9,3.964043367095772e-9 -ValueData/12,8.524782650799322e-7,8.512324940367628e-7,8.534868930559195e-7,3.739378699190234e-9,2.8622783185580692e-9,5.2189586336573326e-9 -ValueData/132,8.518641219101371e-7,8.507891638164795e-7,8.527095166578669e-7,3.2454116569304947e-9,2.0934930961657703e-9,5.3010300557355035e-9 -ValueData/400,8.54326239312973e-7,8.528276147764191e-7,8.555584486601825e-7,4.622817473100502e-9,3.5885124332449724e-9,5.917490002383504e-9 -ValueData/97532,8.489894926417452e-7,8.474776994716881e-7,8.504797114711922e-7,5.127756013958843e-9,4.224490647801043e-9,6.562485085015828e-9 -ValueData/123234,8.488610377944512e-7,8.47673801911665e-7,8.496679184721956e-7,3.165447605683565e-9,2.4018248420673443e-9,4.097120827889815e-9 -ValueData/132651,8.460488190258313e-7,8.436234137841776e-7,8.48436781383805e-7,8.00695104798979e-9,7.454630075244634e-9,8.720049228981087e-9 -ValueData/79831,8.485348608351178e-7,8.461059410035796e-7,8.506551319448549e-7,7.697358258650205e-9,6.606599734036178e-9,9.00424372423834e-9 -ValueData/2567,8.483417275201465e-7,8.467567740805494e-7,8.502071625127907e-7,5.599541868537745e-9,4.7200368542944335e-9,6.586885642878378e-9 -ValueData/225250,8.532659084334731e-7,8.51873555571226e-7,8.542710206695556e-7,4.036718793141761e-9,3.3330587637839835e-9,5.575281453774376e-9 -ValueData/129168,8.49479175968378e-7,8.479710437711364e-7,8.510627145459614e-7,4.904750554473975e-9,4.183501090301991e-9,5.660288839845393e-9 -ValueData/95589,8.573919525058234e-7,8.569312609324598e-7,8.57810924025367e-7,1.4331309086456993e-9,1.211848017419693e-9,1.7173749291641115e-9 -ValueData/393828,8.529246771173438e-7,8.507038170606696e-7,8.547144273387028e-7,6.695902076329811e-9,5.173610038449872e-9,8.074646533519432e-9 -ValueData/277103,8.559638658317148e-7,8.554274139829204e-7,8.564846690487816e-7,1.7153070255380866e-9,1.4850532000337766e-9,2.0865932283322898e-9 -ValueData/149732,8.568952213150124e-7,8.55779559386523e-7,8.583202337440934e-7,4.058932224433089e-9,2.920609176400781e-9,6.10364063175426e-9 -ValueData/20295,8.592090895241722e-7,8.585468566287558e-7,8.597103679598852e-7,1.9589461127960793e-9,1.5020961846565704e-9,2.53245151603325e-9 -ValueData/274721,8.556310346575752e-7,8.545182575729657e-7,8.570085156588638e-7,4.072983231227863e-9,2.9894065840915132e-9,6.650854252738855e-9 -ValueData/234360,8.495773315849466e-7,8.485095898533361e-7,8.508590560485591e-7,3.945885261239193e-9,3.3307796278669102e-9,4.88263922439458e-9 -ValueData/435575,8.554316016970627e-7,8.538057251650714e-7,8.571822727065235e-7,5.22165775590414e-9,3.822225646271991e-9,7.912659649938424e-9 -ValueData/325,8.575383560860995e-7,8.551456054417133e-7,8.598318890975003e-7,7.301228301796286e-9,5.898989793599207e-9,9.170285573277641e-9 -ValueData/309672,8.455838662678522e-7,8.438929583098089e-7,8.481128496280869e-7,6.693508880581244e-9,4.4891910590555004e-9,1.137117018751179e-8 -ValueData/35730,8.503165857726503e-7,8.481929705257501e-7,8.516384413851961e-7,5.7155624436964685e-9,4.5511453783585685e-9,6.997453715992399e-9 -ValueData/140014,8.497151545708349e-7,8.47665192217661e-7,8.525789066401396e-7,7.826592793711272e-9,5.2974447055560445e-9,1.2683466835836368e-8 -ValueData/204540,8.547612676005635e-7,8.541325977717021e-7,8.554903718929581e-7,2.2527957694464155e-9,1.8667067331724525e-9,2.773592456121547e-9 -ValueData/162450,8.487506984701391e-7,8.465771829739707e-7,8.521365758677206e-7,8.841224778102471e-9,6.6926023509893566e-9,1.3281905024646752e-8 -ValueData/173264,8.562504495480041e-7,8.545357665578781e-7,8.574980439256358e-7,5.189153572955064e-9,3.812114301485482e-9,6.801955327270975e-9 -ValueData/34804,8.488094176189896e-7,8.471112077894535e-7,8.518703990459759e-7,7.368614047478343e-9,4.7738497483993025e-9,1.2861751838021989e-8 -ValueData/101238,8.491653203365375e-7,8.471167463151252e-7,8.513892668592282e-7,7.011704217750554e-9,6.246082809121775e-9,7.85427874561324e-9 -ValueData/10857,8.53340260023185e-7,8.51733021923939e-7,8.577891620108842e-7,8.56880225654526e-9,3.7036805227047417e-9,1.6894879950523497e-8 -ValueData/842,8.518487603033034e-7,8.512686060694756e-7,8.52466383127732e-7,2.045925927265305e-9,1.7231537556893947e-9,2.541823788150579e-9 -ValueData/283434,8.491846975222256e-7,8.473914983974797e-7,8.510037925216556e-7,5.79124519501295e-9,4.8451434866888664e-9,6.80761433065066e-9 -ValueData/148255,8.576744946811667e-7,8.556633506862432e-7,8.589271508500057e-7,5.31799961973457e-9,2.732711973241952e-9,8.2684315303086e-9 -ValueData/15156,8.591817798288072e-7,8.583380706837744e-7,8.600590146665929e-7,3.0807725325311505e-9,2.5585140848634544e-9,4.025859681159594e-9 -ValueData/382000,8.541321699516358e-7,8.527137261554062e-7,8.552649289279874e-7,4.5241113374891385e-9,3.787714480600488e-9,5.5478834939184535e-9 -ValueData/205387,8.59263880232035e-7,8.58394258768979e-7,8.600854353488695e-7,2.719065044164826e-9,2.3486986410915696e-9,3.3109672681863356e-9 -ValueData/126392,8.567038496798349e-7,8.56128655177015e-7,8.572978285568135e-7,1.942320811100465e-9,1.658531814482164e-9,2.307633975208863e-9 -ValueData/33839,8.540435375808689e-7,8.522309860198086e-7,8.554138627735398e-7,5.432763905741997e-9,4.07731200095926e-9,7.373001030160369e-9 -ValueData/93500,8.531396796344981e-7,8.525776732804758e-7,8.539021868313024e-7,2.210481853251166e-9,1.5357810025607828e-9,3.0182731425311144e-9 -ValueData/241072,8.556277272730625e-7,8.545950063697891e-7,8.566615470273197e-7,3.382119487888055e-9,2.4695089147116096e-9,5.137339329802755e-9 -ValueData/100606,8.536011014867612e-7,8.524537273969687e-7,8.54726329722913e-7,4.090430838007471e-9,3.3817103295117896e-9,4.901613057818376e-9 -ValueData/15408,8.459468636671925e-7,8.444682305735465e-7,8.472235741334678e-7,4.657080535366424e-9,4.060014962865163e-9,5.509147432714346e-9 -ValueData/69616,8.566448782136618e-7,8.549481754753083e-7,8.574310290639088e-7,3.769537190659225e-9,1.987277360101976e-9,7.140286693043567e-9 -ValueData/304521,8.525787369865922e-7,8.513599351989442e-7,8.537279119368074e-7,3.753510914131666e-9,3.3120583034234087e-9,4.4210015913725766e-9 -ValueData/263198,8.509502296963885e-7,8.489638139041335e-7,8.524589667958955e-7,5.522654208857717e-9,4.191146928016306e-9,6.377548167908616e-9 -ValueData/22260,8.574593081727456e-7,8.569059330882079e-7,8.579716188604812e-7,1.7699769087714066e-9,1.5248074379518592e-9,2.1119148517269495e-9 -ValueData/100352,8.514725924159434e-7,8.501517235480839e-7,8.523989560528702e-7,3.801156560219798e-9,2.82823135305191e-9,4.828535769309876e-9 -ValueData/1773,8.532731677901347e-7,8.513579922650547e-7,8.549742207857545e-7,6.278170410522051e-9,5.043967589585777e-9,7.673213331197956e-9 -ValueData/15330,8.576833934483828e-7,8.563030828770634e-7,8.587431773518986e-7,4.047518878506176e-9,2.7416772650740688e-9,6.000208471479928e-9 -ValueData/176988,8.499643734628492e-7,8.486570355678265e-7,8.511384191783384e-7,4.15135516176567e-9,3.5169318252247064e-9,5.202750690282858e-9 -ValueData/72385,8.558698154904479e-7,8.548736837103324e-7,8.56983593168842e-7,3.4481228223688745e-9,2.729452831934385e-9,4.476737051064749e-9 -ValueData/235037,8.557381138303279e-7,8.542117800971427e-7,8.570984376997041e-7,4.765293488248609e-9,4.00776827567388e-9,5.50668697363528e-9 -ValueData/95940,8.527513288545138e-7,8.504947634870435e-7,8.542552992416777e-7,6.2197153210891185e-9,4.37624817217445e-9,8.418819112463073e-9 -ValueData/103200,8.479903631242557e-7,8.461970775528324e-7,8.497129989311023e-7,5.9024748365191916e-9,5.123371730822309e-9,6.9017623164474515e-9 -ValueData/123816,8.463906341117494e-7,8.444667455341365e-7,8.487137092173759e-7,7.282933356419484e-9,6.309327218991049e-9,8.807160603512193e-9 -UnValueData/4,9.013950914141455e-7,8.998310604752979e-7,9.030685882488825e-7,5.512364943540312e-9,4.653201611803667e-9,6.47512273336601e-9 -UnValueData/146,2.6949717546797696e-6,2.6929457624387185e-6,2.6969263184348243e-6,6.4963161689037006e-9,5.486385356337939e-9,7.903034149953178e-9 -UnValueData/1424,1.7907472683032777e-5,1.7902658268731024e-5,1.7912900682501594e-5,1.7030564686088553e-8,1.3739405874666239e-8,2.235702394823734e-8 -UnValueData/7104,8.723466638282224e-5,8.716778413126838e-5,8.739787957227999e-5,3.227634726193636e-7,1.7190914159487133e-7,6.403529007213577e-7 -UnValueData/14204,1.7629954435655664e-4,1.762349459970134e-4,1.7637827841013271e-4,2.4073648638990344e-7,1.9359582750372447e-7,3.1784683202462695e-7 -UnValueData/71004,9.946969395157833e-4,9.900353441417433e-4,9.999746858039172e-4,1.6185331467772357e-5,1.2962056012188339e-5,2.083933197891671e-5 -UnValueData/142004,2.397080011982262e-3,2.3874266903145874e-3,2.4054034603446426e-3,3.064690617529184e-5,2.384999626785536e-5,4.1279743653245695e-5 -UnValueData/196,3.0199827263550725e-6,3.017306789987222e-6,3.024693062411046e-6,1.1745346040213685e-8,7.283896149278244e-9,2.022058416407555e-8 -UnValueData/1852,2.29141633470779e-5,2.2901937018727813e-5,2.2926753458055604e-5,4.069431060261231e-8,3.060102035322918e-8,5.5071879810478866e-8 -UnValueData/5444,7.063156263358334e-5,7.057804157123944e-5,7.069859342276232e-5,1.996238140884392e-7,1.542720492926638e-7,2.4926521264495196e-7 -UnValueData/1275828,3.538882524236411e-2,3.478603513038184e-2,3.5932591351741185e-2,1.183941554805216e-3,7.744330568201735e-4,1.6523449296964045e-3 -UnValueData/1612534,4.737926376316742e-2,4.62776779509303e-2,4.8709034001214624e-2,2.4348585639314647e-3,1.5746940731853952e-3,3.9328173667833935e-3 -UnValueData/1734871,5.169557410313174e-2,5.04682756532513e-2,5.2880732401104205e-2,2.4318040000490286e-3,1.6238618054290877e-3,3.525916787897464e-3 -UnValueData/1047683,2.641131128597946e-2,2.5918685360555124e-2,2.6709702790024464e-2,7.695329072491731e-4,4.298971335444454e-4,1.332825756720731e-3 -UnValueData/33579,6.152426455998624e-4,6.148176875504924e-4,6.157060469860077e-4,1.5261796251918345e-6,1.288644080255388e-6,1.796888503460542e-6 -UnValueData/2939066,9.26512901297552e-2,9.023907482566565e-2,9.506057565571902e-2,3.998642818583841e-3,2.783073014538003e-3,6.727900341426262e-3 -UnValueData/1684804,5.1487146112206776e-2,5.0502978309739155e-2,5.2652781690950654e-2,2.091384208180315e-3,1.4675335874434114e-3,3.280664969660972e-3 -UnValueData/1247305,3.459056548895746e-2,3.412487858496163e-2,3.489230387579992e-2,7.677741055204657e-4,4.47621044576403e-4,1.1583840895400715e-3 -UnValueData/5130412,0.16981458419864223,0.16325395088642836,0.17271223401200966,6.016863028255257e-3,1.9548767624741675e-3,9.299252409692128e-3 -UnValueData/3609171,0.11841349425002201,0.11602325454420809,0.12104833646070412,4.081346296375948e-3,2.926312950107069e-3,5.494254156111412e-3 -UnValueData/1950504,6.320052693321689e-2,6.206578748869477e-2,6.439125182122434e-2,2.0702897863452336e-3,1.513519277421885e-3,3.3145439156368577e-3 -UnValueData/271219,5.031523948159418e-3,5.004123806872513e-3,5.052210004663146e-3,7.306414479334599e-5,5.0912722379372435e-5,1.0991753223006613e-4 -UnValueData/3580509,0.11745919117473975,0.11377198422754493,0.12064254725354702,5.25111169031894e-3,3.585995810264577e-3,7.687502014415927e-3 -UnValueData/3057844,9.653946980168776e-2,9.408781219461056e-2,9.780864584846077e-2,2.8770118126227847e-3,1.2885996102524905e-3,4.556584505851217e-3 -UnValueData/5673483,0.19078302505270886,0.18456831483894753,0.19503182816422648,7.061850089992917e-3,3.8511126574441645e-3,1.0086965889737357e-2 -UnValueData/4529,5.625718368900359e-5,5.623774328452426e-5,5.629127231353821e-5,8.678094600698326e-8,5.488153364553722e-8,1.491449287144414e-7 -UnValueData/4034848,0.13457402487041517,0.12930228858853557,0.1367327969776289,5.036560760839139e-3,1.5513411387421015e-3,7.899560240646458e-3 -UnValueData/474022,9.805654390060441e-3,9.753899276753719e-3,9.859140308874604e-3,1.4180011864017576e-4,1.0811060695524623e-4,1.8860835375446178e-4 -UnValueData/1831694,5.4992708895459506e-2,5.3810050151133465e-2,5.6280690193825374e-2,2.341608645119063e-3,1.3074225970835772e-3,3.94235789815771e-3 -UnValueData/2670712,8.26651621592926e-2,8.138630474348449e-2,8.431409838321131e-2,2.576492254751651e-3,1.2573055311387187e-3,4.44932088444523e-3 -UnValueData/2117254,6.863611344774988e-2,6.720114102994305e-2,6.94921848416342e-2,1.9754774895120383e-3,1.1332767466359756e-3,3.1940716312409095e-3 -UnValueData/2261844,7.048193999585929e-2,6.914867769720803e-2,7.146712106398562e-2,2.109635769978593e-3,1.2475559370112653e-3,3.3765680126158683e-3 -UnValueData/455168,1.0449800699444808e-2,1.0400068849978404e-2,1.0491944938338344e-2,1.2202157938707612e-4,8.986403452445767e-5,1.6712388985635403e-4 -UnValueData/1319482,3.950063670287641e-2,3.883719935405675e-2,4.0251589232390854e-2,1.4594368726337176e-3,9.261067520744372e-4,2.3081120539885105e-3 -UnValueData/152989,2.5965329380654386e-3,2.5838396408271727e-3,2.6051057952206714e-3,3.414947791954888e-5,2.5300625886029688e-5,4.76689285949758e-5 -UnValueData/10974,2.2697574332799172e-4,2.2683659999458297e-4,2.272447562959622e-4,6.057397762368306e-7,3.845644747906495e-7,1.0749201209116146e-6 -UnValueData/3691630,0.12319773742180717,0.12001946693663264,0.1260003725185968,4.406698122037507e-3,2.917801104444502e-3,6.276373978235909e-3 -UnValueData/1939259,5.8617135278751016e-2,5.702482455092231e-2,5.933012497948886e-2,1.7921968622351299e-3,7.721450142221724e-4,3.2390124987271168e-3 -UnValueData/202084,3.7703821813843386e-3,3.759376500364373e-3,3.7791312531530014e-3,3.439621073325981e-5,2.746593956654542e-5,4.404686468031192e-5 -UnValueData/4977464,0.16588871036086003,0.16072344034910202,0.17091598903418198,7.476364872295917e-3,4.69137783649583e-3,1.1944210928733824e-2 -UnValueData/2675807,8.77234403006289e-2,8.569994060943524e-2,8.85390866139815e-2,2.1492565120412623e-3,6.053499624658883e-4,3.6332337932161733e-3 -UnValueData/1646652,5.1892095547350296e-2,5.1256377560672535e-2,5.2457293943654074e-2,1.21240508552964e-3,9.395777310174762e-4,1.7311997357392101e-3 -UnValueData/442875,1.0217844956572268e-2,1.01606788886645e-2,1.0273542205872678e-2,1.4970650455225067e-4,1.1806841943842336e-4,1.9486376067482752e-4 -UnValueData/1218804,3.549055977064392e-2,3.5009643010831065e-2,3.595800491653723e-2,9.764448630159033e-4,6.293937019350363e-4,1.5894944475261681e-3 -UnValueData/3143456,0.10080232521111715,9.842218463333748e-2,0.10219765393592325,2.996856871256996e-3,1.4768703771080765e-3,4.710209046701973e-3 -UnValueData/1314338,3.7279427758090386e-2,3.6829950773914516e-2,3.768657982896742e-2,9.112051286569823e-4,6.313747519712489e-4,1.3543938646120163e-3 -UnValueData/201592,4.380088179555611e-3,4.370509130895144e-3,4.389290959128947e-3,3.022455726361525e-5,2.4408953433486835e-5,3.9399788029737926e-5 -UnValueData/910508,2.351005395746229e-2,2.3235037084557975e-2,2.41903310127284e-2,9.062658011207139e-4,3.6989662586122156e-4,1.693000534947892e-3 -UnValueData/3969013,0.1300488320723941,0.1266004712108822,0.1332678787293844,5.135393369043468e-3,3.440452006778816e-3,8.322783973869336e-3 -UnValueData/3429846,0.11217209955793805,0.10898463778236571,0.11529797055603316,4.779718065167384e-3,2.9571761719117337e-3,7.883906432417116e-3 -UnValueData/290104,7.187295906219642e-3,7.154558198153695e-3,7.216326370950873e-3,8.762410918099477e-5,5.972690566620994e-5,1.3214128640280976e-4 -UnValueData/1309284,3.84539475102095e-2,3.781680300899196e-2,3.907831123847283e-2,1.2818704971530644e-3,8.847947267276011e-4,2.040408084729673e-3 -UnValueData/30145,4.0607192508357564e-4,4.058249861764727e-4,4.0638758622843333e-4,9.274747513906685e-7,6.682446858137631e-7,1.3748319482782774e-6 -UnValueData/201814,4.103992603376012e-3,4.088651000708487e-3,4.1128834364904535e-3,3.43360316581495e-5,2.2758963126485183e-5,5.8545732644850565e-5 -UnValueData/2307904,7.358309062585765e-2,7.218055283709032e-2,7.556175181482923e-2,2.972594826418836e-3,1.7564457039264782e-3,5.108224053769436e-3 -UnValueData/942869,2.645375524770737e-2,2.6295833915344537e-2,2.658400715372948e-2,3.0238803368070027e-4,2.0658911742334137e-4,4.554496864733326e-4 -UnValueData/3066633,9.714020909860605e-2,9.408058526837866e-2,9.868559868442883e-2,3.398024340113775e-3,1.5939510685882108e-3,5.088663729577467e-3 -UnValueData/1256080,3.465983354970306e-2,3.419705321044698e-2,3.5023144250937804e-2,9.019721216417195e-4,3.984352477224662e-4,1.4786623858695051e-3 -UnValueData/1348804,3.832256070634588e-2,3.776391157830391e-2,3.876221402943205e-2,1.0372502062233494e-3,6.511066805053482e-4,1.68453125674602e-3 -UnValueData/1612828,5.086401175192149e-2,4.9854595441005824e-2,5.1837199296619715e-2,1.8245221979116828e-3,1.162131919470242e-3,3.944316792234646e-3 +LookupCoin/4/4/1,1.1697108080181536e-6,1.168821234505366e-6,1.1723465191864994e-6,4.716644588356427e-9,2.3430737725273626e-9,9.658139374989224e-9 +LookupCoin/4/4/4,1.197419834351788e-6,1.1964593354794394e-6,1.1984748420210096e-6,3.3117652848729744e-9,2.8278712558256027e-9,3.942910155538903e-9 +LookupCoin/4/4/4,1.2105664883646643e-6,1.209553859148611e-6,1.2126399505542392e-6,4.539669691162183e-9,2.9343689942860255e-9,7.801601946705972e-9 +LookupCoin/4/4/6,1.228502466397917e-6,1.2276388746968598e-6,1.2293794333965936e-6,2.8365950199435727e-9,2.262500664753311e-9,4.102904844614158e-9 +LookupCoin/4/4/7,1.2341113111322185e-6,1.2326368750439452e-6,1.2361132573873327e-6,5.960319238406489e-9,4.358707098436504e-9,9.489169130255943e-9 +LookupCoin/4/4/9,1.2440088713635867e-6,1.2433419266035411e-6,1.244658329909325e-6,2.1777523187182086e-9,1.860809203401042e-9,2.622035845865055e-9 +LookupCoin/4/4/10,1.2590833176442277e-6,1.2579285823586164e-6,1.2606453887490079e-6,4.512979933077232e-9,3.8355934953693816e-9,6.2705096957434704e-9 +LookupCoin/4/4/3,1.198959227785464e-6,1.1982309689794912e-6,1.1997566713400149e-6,2.4994099229192873e-9,1.970592743387721e-9,3.247757078324411e-9 +LookupCoin/4/4/4,1.2130344002024768e-6,1.2116050528680782e-6,1.215676276149374e-6,6.336941424892223e-9,4.221962054110571e-9,1.1948330296178361e-8 +LookupCoin/4/4/5,1.2154981317892604e-6,1.2147401617597355e-6,1.2162053970962376e-6,2.4527550451576626e-9,2.0876776622244234e-9,2.929088576807172e-9 +LookupCoin/4/4/9,1.2371930756906897e-6,1.2360528173169546e-6,1.238913660529153e-6,4.902733185892853e-9,3.367493627264707e-9,8.269646671979606e-9 +LookupCoin/4/4/7,1.2124300594245786e-6,1.211889624968005e-6,1.2131653342965383e-6,2.170575108151274e-9,1.7050649983731382e-9,3.492023301952406e-9 +LookupCoin/4/4/9,1.226662002345339e-6,1.2257016597852336e-6,1.228373308721749e-6,4.1728549275093335e-9,2.7195517177022387e-9,7.060903309380737e-9 +LookupCoin/4/4/10,1.2460493026909793e-6,1.2447491498361454e-6,1.2477591575533104e-6,5.206053260850191e-9,4.148264615282915e-9,7.592482543377857e-9 +LookupCoin/4/4/8,1.2389102130053683e-6,1.2378194632558927e-6,1.241232178786885e-6,5.176843354105181e-9,2.9842499717008512e-9,9.218009042245045e-9 +LookupCoin/4/4/10,1.2470174477108264e-6,1.2458080941685637e-6,1.2482130471838322e-6,3.891687822432955e-9,3.2361650668783053e-9,4.801841225924434e-9 +LookupCoin/4/4/7,1.2096551172922683e-6,1.208048730062437e-6,1.2121052517421568e-6,6.710312854838667e-9,4.5596395422371135e-9,1.1642832038731222e-8 +LookupCoin/4/4/9,1.236088089875015e-6,1.2356619493174214e-6,1.2365271534684044e-6,1.4606048438176316e-9,1.254949516603869e-9,1.7410842616706878e-9 +LookupCoin/4/4/10,1.2582467184677703e-6,1.2564135792681499e-6,1.2616671620690463e-6,8.350474758061344e-9,4.8746207617235825e-9,1.5099000824357255e-8 +LookupCoin/4/4/10,1.2443671739978894e-6,1.2431653781418486e-6,1.2452350901049321e-6,3.346995102535447e-9,2.6244662850680067e-9,4.246006176707587e-9 +LookupCoin/4/4/10,1.2480838330616997e-6,1.2468586484975573e-6,1.2490254341751588e-6,3.61083809679136e-9,2.811963863104157e-9,4.971676237009003e-9 +LookupCoin/4/4/10,1.2455842305106098e-6,1.2450293470286068e-6,1.2464404697509894e-6,2.4324916160862726e-9,1.7674298130870043e-9,3.604905761217919e-9 +LookupCoin/4/4/9,1.2336750447972988e-6,1.2329730266461632e-6,1.2345524554578834e-6,2.5980878406212895e-9,2.010600701971652e-9,3.4227346208864528e-9 +LookupCoin/4/4/9,1.2326117745442434e-6,1.2316765095204855e-6,1.2336787929154839e-6,3.2849729907541525e-9,2.78088220995093e-9,3.8905746716149614e-9 +LookupCoin/4/4/9,1.2275044007346412e-6,1.2266488529157138e-6,1.2284336944587511e-6,2.962480015143421e-9,2.5068032133455e-9,3.5755097027596483e-9 +LookupCoin/4/4/8,1.2054867622577074e-6,1.204849948479908e-6,1.2062940626968763e-6,2.4259660965053903e-9,1.962629823802868e-9,3.025364954394713e-9 +LookupCoin/4/4/9,1.2355470937925595e-6,1.234801606108345e-6,1.2363149425209876e-6,2.5550301814812555e-9,2.163791915494604e-9,3.1802911065348715e-9 +LookupCoin/4/4/10,1.2766231486887846e-6,1.275884621174173e-6,1.2775433697071452e-6,2.7960218131543466e-9,2.1879321862849126e-9,3.505044689733272e-9 +LookupCoin/4/4/9,1.2313661584515245e-6,1.230523141927911e-6,1.2322304263996558e-6,2.915335061489737e-9,2.4234331978601106e-9,3.6350030783107438e-9 +LookupCoin/4/4/10,1.2365756598592769e-6,1.2356729019594153e-6,1.237413039220989e-6,2.9566536194265075e-9,2.5715073349933658e-9,3.681315432795484e-9 +LookupCoin/4/4/9,1.2333385652739018e-6,1.2326864987254998e-6,1.2341175262648882e-6,2.4048495116109993e-9,2.0195697593236277e-9,3.1803510321311427e-9 +LookupCoin/4/4/9,1.2384272951897245e-6,1.2374780134185973e-6,1.239375549062892e-6,3.0895929218850177e-9,2.7234106587975402e-9,3.4750689105056344e-9 +LookupCoin/4/4/9,1.240727212227516e-6,1.2388891560274423e-6,1.242693379524857e-6,6.429789891380752e-9,5.354277221909358e-9,7.981475797589119e-9 +LookupCoin/4/4/10,1.2600657530886329e-6,1.2591698492355715e-6,1.261147283381832e-6,3.437236263983271e-9,2.685926477223312e-9,5.293458492061048e-9 +LookupCoin/4/4/9,1.2470483195550015e-6,1.245703816949775e-6,1.2484975870170002e-6,4.604055933463116e-9,3.954013159591928e-9,5.381316662175224e-9 +LookupCoin/4/4/9,1.2356925487515664e-6,1.2348631572484635e-6,1.2367025713511272e-6,2.9913551563855585e-9,2.455503001161769e-9,4.1096871964953925e-9 +LookupCoin/4/4/10,1.2505038628122508e-6,1.2491061781900452e-6,1.25221860449456e-6,4.990642977733982e-9,4.1122452415633e-9,6.9505541949505345e-9 +LookupCoin/4/4/10,1.238165634861657e-6,1.2372232741945494e-6,1.23948532278423e-6,3.741105341248167e-9,2.6926962270792455e-9,5.75599116827575e-9 +LookupCoin/4/4/9,1.2348944676374662e-6,1.2337942245019898e-6,1.2364811072370116e-6,4.3933969072335646e-9,3.0154798524116637e-9,6.8944014397537114e-9 +LookupCoin/4/4/10,1.2447074708786151e-6,1.2437973780112442e-6,1.2459488406958364e-6,3.4649795911358565e-9,2.6801488196731307e-9,4.923331930005279e-9 +LookupCoin/4/4/10,1.2541685625213916e-6,1.253100520038605e-6,1.2553129227782672e-6,3.738745409198097e-9,3.1997152522735096e-9,4.4161695861133365e-9 +LookupCoin/4/4/10,1.2591054603885218e-6,1.2580504255889407e-6,1.2601694642077592e-6,3.662744739333211e-9,2.874063175440071e-9,4.8943341115891516e-9 +LookupCoin/4/4/10,1.2489830357419668e-6,1.2482451485576008e-6,1.2498090497944244e-6,2.6279704006468314e-9,2.183989588290957e-9,3.3083910876775962e-9 +LookupCoin/4/4/9,1.2170709234086026e-6,1.2155312451471089e-6,1.2188307378015095e-6,5.4107613597875365e-9,4.678383271442085e-9,6.339558744660862e-9 +LookupCoin/4/4/9,1.2443110197038305e-6,1.2436242834987645e-6,1.2449759593896452e-6,2.2418551799354828e-9,1.8334805913612716e-9,2.8205362074179004e-9 +LookupCoin/4/4/8,1.2220487469051031e-6,1.2206043239846844e-6,1.2235486479029413e-6,4.857007077661286e-9,3.937238707550021e-9,6.3794967588104164e-9 +LookupCoin/4/4/10,1.2501843489649957e-6,1.249470806208686e-6,1.251102651202567e-6,2.7590971806803523e-9,2.1810635770403194e-9,4.268761434945777e-9 +LookupCoin/4/4/10,1.2546132304707667e-6,1.2531681032373974e-6,1.2559266255115694e-6,4.9008859131854355e-9,4.0186626048466616e-9,5.722904223279788e-9 +LookupCoin/4/4/10,1.2472987859641628e-6,1.246333937583404e-6,1.2483136607786524e-6,3.4374272189810063e-9,3.0233649739257452e-9,4.078677289183089e-9 +LookupCoin/4/4/10,1.257289885780312e-6,1.2561471192857335e-6,1.259297142010002e-6,5.074798533301969e-9,3.027873306485155e-9,9.073321296739781e-9 +LookupCoin/4/4/8,1.234695354115067e-6,1.2339195591355863e-6,1.2356300144036983e-6,2.8693457928519677e-9,2.455616085767567e-9,3.41607913710769e-9 +LookupCoin/4/4/10,1.2275155278974081e-6,1.2265562999905127e-6,1.2284216653260961e-6,3.08170575762874e-9,2.469050749370086e-9,4.214707515381152e-9 +LookupCoin/4/4/10,1.243759540846969e-6,1.2427112891244496e-6,1.2446295098759129e-6,3.2820727744803495e-9,2.7235693761359966e-9,4.031208364718703e-9 +LookupCoin/4/4/9,1.238406082251816e-6,1.237106448647996e-6,1.2406559941302227e-6,5.76845557608286e-9,4.05178877302676e-9,9.689312944660408e-9 +LookupCoin/4/4/9,1.2218834628022707e-6,1.2213592919711338e-6,1.2225690734722582e-6,2.024619758461744e-9,1.5563259112744294e-9,2.654070902739526e-9 +LookupCoin/4/4/10,1.2418481002043983e-6,1.2399465204345789e-6,1.2435985718336768e-6,6.162696996211367e-9,5.1970223197992535e-9,8.437095796444955e-9 +LookupCoin/4/4/9,1.2398190674747734e-6,1.2389724712087143e-6,1.2407423545036635e-6,3.045916161641388e-9,2.6657936643164306e-9,3.525916473617155e-9 +LookupCoin/4/4/10,1.2491882204795904e-6,1.2477194689440369e-6,1.2522824847646825e-6,7.0084623185113996e-9,4.2218375736244884e-9,1.2275689509756614e-8 +LookupCoin/4/4/9,1.2303599582164441e-6,1.2291325332241363e-6,1.231631471345098e-6,4.2604425190916745e-9,3.7369239520941644e-9,4.860825873220661e-9 +LookupCoin/4/4/9,1.2170010461551755e-6,1.2161901915511362e-6,1.2184735167018027e-6,3.5591364075263227e-9,2.5328357341557557e-9,5.621338545229777e-9 +LookupCoin/4/4/7,1.2275614073937704e-6,1.2271113713628585e-6,1.228036328608289e-6,1.6209009354226949e-9,1.3999552859327015e-9,1.936823761754443e-9 +LookupCoin/4/4/9,1.239971093009026e-6,1.2383863407346815e-6,1.2422869038793659e-6,6.4074024247550565e-9,4.674873449824546e-9,9.912575035089932e-9 +LookupCoin/4/4/10,1.250820535442252e-6,1.2501562470763576e-6,1.2515907622044527e-6,2.4921767290726847e-9,2.1219922264910897e-9,3.0667358206508303e-9 +LookupCoin/4/4/11,1.2553790127566416e-6,1.2536654709929194e-6,1.2570533268466282e-6,5.874590655037513e-9,4.4196211196080054e-9,8.832518248705935e-9 +LookupCoin/4/4/5,1.2090038007880602e-6,1.2082173835783592e-6,1.2098685952643613e-6,2.7571723765254015e-9,2.3441224671825372e-9,3.4910247602378946e-9 +LookupCoin/4/4/11,1.241247646410852e-6,1.240203406405301e-6,1.2422464946610046e-6,3.51898737663362e-9,2.7856128076197317e-9,4.450480501387243e-9 +LookupCoin/4/4/11,1.2432590560230394e-6,1.2426341286504644e-6,1.2440747263302385e-6,2.3703018621244413e-9,1.969873453164278e-9,2.834442463023093e-9 +LookupCoin/4/4/10,1.2407289043497012e-6,1.2401264702434196e-6,1.2413085891271877e-6,2.1239501908308195e-9,1.7774357357623027e-9,2.589168276635471e-9 +LookupCoin/4/4/11,1.2607689016384522e-6,1.2598948673065236e-6,1.261794361330354e-6,3.1837881471991466e-9,2.7310493092383404e-9,3.859152913577096e-9 +LookupCoin/4/4/11,1.2531763577934863e-6,1.2525909597580015e-6,1.2538618408537237e-6,2.1504257889874135e-9,1.7223077547321009e-9,2.9536508375238324e-9 +LookupCoin/4/4/10,1.2415088801259666e-6,1.2406731891795948e-6,1.242768450222254e-6,3.3004465209926063e-9,2.3143646430055366e-9,5.382862905391514e-9 +LookupCoin/4/4/10,1.2283892105026046e-6,1.2276322366509122e-6,1.2291058786881733e-6,2.466111193160826e-9,2.0479052873948924e-9,3.3152384692834025e-9 +LookupCoin/4/4/11,1.2606460620131015e-6,1.2596844021242669e-6,1.2614917141387166e-6,3.0711786241202447e-9,2.51488827115015e-9,3.732538395688686e-9 +LookupCoin/4/4/10,1.2466318813747555e-6,1.2457862977559392e-6,1.2476820423926504e-6,3.095582691697399e-9,2.396694183605456e-9,4.502591621080734e-9 +LookupCoin/4/4/10,1.231413901153807e-6,1.2304520647599062e-6,1.2324110815971323e-6,3.2351925593841e-9,2.7590601041904865e-9,3.899992602135909e-9 +LookupCoin/4/4/7,1.2137917497642551e-6,1.2124411192741975e-6,1.2153746657852204e-6,4.911332451763905e-9,4.221503960723082e-9,5.947493309738063e-9 +LookupCoin/4/4/10,1.2452017444780016e-6,1.2444824516627773e-6,1.2461536806456646e-6,2.9094097462798016e-9,2.2168132928185632e-9,4.353940334978015e-9 +LookupCoin/4/4/11,1.2503867919247944e-6,1.2499776611057803e-6,1.2508142608501873e-6,1.4599290593439317e-9,1.1821198529398551e-9,2.0732476683226483e-9 +LookupCoin/4/4/11,1.2462058372245407e-6,1.2446230232954647e-6,1.2478785689502995e-6,5.540038998826273e-9,4.760308125773058e-9,7.058773314267196e-9 +LookupCoin/4/4/11,1.2501607210736947e-6,1.2494535700255925e-6,1.2508888986644752e-6,2.4306720608256043e-9,2.053884852747493e-9,2.8851034909946726e-9 +LookupCoin/4/4/10,1.246577391161309e-6,1.2449604720948604e-6,1.2509783127977872e-6,8.285927128876795e-9,3.6909965107403938e-9,1.6693827271579106e-8 +LookupCoin/4/4/11,1.2481858056389869e-6,1.2471686486094632e-6,1.2493252283758214e-6,3.588924882476405e-9,3.102633624789598e-9,4.261285291561462e-9 +LookupCoin/4/4/10,1.234749550240397e-6,1.233985630609682e-6,1.2357151178632057e-6,2.9669600831980922e-9,2.3960468564700926e-9,3.655961104113488e-9 +LookupCoin/4/4/10,1.2505733600432316e-6,1.249367236780861e-6,1.2518550616087952e-6,4.133093607804304e-9,3.5307185498390227e-9,4.791553481960602e-9 +LookupCoin/4/4/11,1.271413823037886e-6,1.2706037979897562e-6,1.2723474488196948e-6,3.0004134332150523e-9,2.454400730898568e-9,3.6301136674397515e-9 +LookupCoin/4/4/8,1.2246226846788342e-6,1.224085632840035e-6,1.2252985793031374e-6,1.8584275127759694e-9,1.53002719390583e-9,2.352020526710014e-9 +LookupCoin/4/4/11,1.2530228033613433e-6,1.251778970422524e-6,1.254130066290737e-6,3.941390823812702e-9,3.421217382841052e-9,4.601361468134656e-9 +LookupCoin/4/4/11,1.2405261172273201e-6,1.2395424195671817e-6,1.2416469916218492e-6,3.5128107059062576e-9,2.8425554092513393e-9,4.658670793044547e-9 +LookupCoin/4/4/11,1.2439791741796996e-6,1.2431126853770436e-6,1.2448051623120779e-6,2.869721380370578e-9,2.3800129341779e-9,3.4684232618964124e-9 +LookupCoin/4/4/10,1.2355780177512313e-6,1.2346334745913936e-6,1.2364896113626468e-6,3.143105042657989e-9,2.5170880843175777e-9,3.816081188375383e-9 +LookupCoin/4/4/11,1.2489337516546245e-6,1.247992742500274e-6,1.25002337078884e-6,3.2972816307148326e-9,2.735403317989366e-9,4.086005086639011e-9 +LookupCoin/4/4/11,1.2472521676974043e-6,1.246180205210337e-6,1.2497194648510362e-6,5.511282756179962e-9,2.808086451268632e-9,1.0265829216106953e-8 +LookupCoin/4/4/11,1.25549982903908e-6,1.254747750956376e-6,1.2562746515110732e-6,2.7631464926295974e-9,2.268592557777647e-9,3.3883340154562313e-9 +LookupCoin/4/4/10,1.2484200600125675e-6,1.2476538527823768e-6,1.2495855888076212e-6,3.0458181928574898e-9,2.221872073028509e-9,4.977667739841173e-9 +LookupCoin/4/4/9,1.2423571945504644e-6,1.241468699797019e-6,1.2431479480664121e-6,2.7321654595347156e-9,2.18177352956854e-9,3.608946696086819e-9 +LookupCoin/4/4/9,1.2328201741155857e-6,1.2318932840633818e-6,1.2349631880358485e-6,4.413992896509118e-9,2.166446332180485e-9,9.030145918148484e-9 +LookupCoin/4/4/11,1.2525846105478666e-6,1.2517607017175452e-6,1.2535274269295089e-6,3.049524371683899e-9,2.5421012696286185e-9,3.684012056332699e-9 +LookupCoin/4/4/10,1.2385197803764863e-6,1.2366907322169736e-6,1.2442703700223826e-6,1.0069817040337275e-8,3.126061858487965e-9,2.0640387016604502e-8 +LookupCoin/4/4/11,1.2473682855382386e-6,1.2468018147041009e-6,1.247995865828385e-6,1.9039650938788714e-9,1.5612110741290985e-9,2.441237425453308e-9 +LookupCoin/4/4/9,1.2431526284615897e-6,1.2422396471978106e-6,1.2441222016984172e-6,3.224740997121396e-9,2.8183422885165273e-9,3.684654671500225e-9 +LookupCoin/4/4/11,1.2518025352090638e-6,1.2511100753683388e-6,1.252553120149778e-6,2.5463026907993414e-9,2.0966264210870694e-9,3.3244598497977186e-9 +LookupCoin/4/4/10,1.2483963139963221e-6,1.2478187223975245e-6,1.2490960726615228e-6,2.0996425165094807e-9,1.7155560837419597e-9,2.679551513104474e-9 +LookupCoin/4/4/11,1.2539289852528264e-6,1.2530206278508644e-6,1.254806749061674e-6,2.997299189856659e-9,2.462129257480767e-9,3.6815065315816898e-9 +LookupCoin/4/4/10,1.2346304769270814e-6,1.2338747000514088e-6,1.2352572514709445e-6,2.42682523178336e-9,2.037491593885004e-9,2.9870837501823817e-9 +LookupCoin/4/4/9,1.2173304766905813e-6,1.216117192909887e-6,1.218537414346466e-6,4.342165762094043e-9,3.666448814253374e-9,5.957131435523091e-9 +LookupCoin/4/4/11,1.2504647560317849e-6,1.2497158072235584e-6,1.2510916146311196e-6,2.2955741584687246e-9,1.9295299507298546e-9,2.8046258914238046e-9 +LookupCoin/4/4/11,1.2403991391228998e-6,1.2395136414832954e-6,1.2422277769658595e-6,4.273786617406553e-9,2.694203170906102e-9,7.371739601590599e-9 +LookupCoin/4/4/10,1.2512444909289105e-6,1.250332008699582e-6,1.2522675671591145e-6,3.2707648251178727e-9,2.742327329330054e-9,3.990693989462503e-9 +LookupCoin/4/4/10,1.2449072269635028e-6,1.2438148675689987e-6,1.246051201472081e-6,3.6554621997918077e-9,3.177226369301188e-9,4.343751446718684e-9 +LookupCoin/4/4/11,1.2556087870842488e-6,1.2545236774137204e-6,1.2565833267592558e-6,3.5330486977479267e-9,2.888185687109178e-9,4.759609627903453e-9 +LookupCoin/4/4/11,1.252033139325492e-6,1.2505950903976188e-6,1.2532261016951873e-6,4.416422507567805e-9,3.9471532467031755e-9,5.176768287496665e-9 +LookupCoin/4/4/10,1.2602014077338466e-6,1.2593051707223002e-6,1.2610755552279167e-6,2.831058490203997e-9,2.3019147615026436e-9,3.3604753286911443e-9 +LookupCoin/4/4/11,1.2550047148527483e-6,1.2537844598819335e-6,1.2566923108108786e-6,4.520053035535084e-9,3.3258317413988896e-9,6.519372179183177e-9 +LookupCoin/4/4/10,1.2328530924937776e-6,1.2320919952831327e-6,1.233771126842418e-6,2.9135592409011884e-9,2.420175107221782e-9,3.5975760184578205e-9 +LookupCoin/4/4/11,1.2512075442031918e-6,1.2499242296952986e-6,1.2532084852697252e-6,5.276265366943044e-9,3.37632483063052e-9,9.62620033497846e-9 +ValueContains/4/1,1.117652550269312e-6,1.1165043108953805e-6,1.1189434830832812e-6,3.866084734197916e-9,3.3384089652484082e-9,4.784233616330343e-9 +ValueContains/4/0,1.0243332057293326e-6,1.0231254113762293e-6,1.0284935525111438e-6,6.682898460450429e-9,2.6613607769526014e-9,1.2998659514901811e-8 +ValueContains/4/10,1.7827826389965773e-6,1.7804768380919621e-6,1.7844995681150503e-6,6.817301293629099e-9,5.775770532482603e-9,7.968887836401614e-9 +ValueContains/7/0,1.0227777692231634e-6,1.0218685350409536e-6,1.0246742534825295e-6,4.158519549068223e-9,2.5376860134628787e-9,7.296650358142231e-9 +ValueContains/7/0,1.019673477226688e-6,1.019203529217371e-6,1.0200682441592737e-6,1.4862747242183329e-9,1.1831075810886551e-9,2.2242470093486322e-9 +ValueContains/7/100,1.102190629726943e-5,1.1003746246407482e-5,1.106949563475277e-5,8.92685178724376e-8,3.9010702031807095e-8,1.73173578293233e-7 +ValueContains/10/0,1.0247331328158465e-6,1.0238117709598077e-6,1.0254897170050632e-6,2.809260721460524e-9,2.404190682468274e-9,3.3950833242276077e-9 +ValueContains/10/0,1.0275740352771401e-6,1.026790280958967e-6,1.0293987993301002e-6,3.843940026977366e-9,2.184204018929444e-9,6.951548633903871e-9 +ValueContains/10/0,1.0248908323401232e-6,1.0243476908385546e-6,1.0254312189162081e-6,1.9396356590851645e-9,1.5957151380730652e-9,2.4395699807397894e-9 +ValueContains/10/1000,1.3953983426742036e-4,1.3936078373464348e-4,1.398197434694726e-4,7.36887808621925e-7,4.606420549980772e-7,1.2353941023274986e-6 +ValueContains/5/200,1.7462839677828407e-5,1.7447395042352337e-5,1.747841891658741e-5,5.25024519912565e-8,4.350794016901038e-8,6.436013495299469e-8 +ValueContains/1/0,1.0214480293033692e-6,1.020884108154564e-6,1.0220149697973383e-6,1.859394211560464e-9,1.495305144756765e-9,2.3326227392858035e-9 +ValueContains/4/0,1.0216329614398732e-6,1.0209982267609106e-6,1.022221194615472e-6,2.141378298749644e-9,1.8689075351432286e-9,2.5290113656981776e-9 +ValueContains/7/0,1.0191317714210964e-6,1.0184577896745084e-6,1.0201632194645358e-6,2.838121955815522e-9,2.3462539810319014e-9,3.629269799879261e-9 +ValueContains/10/0,1.02452230515218e-6,1.0233715896691429e-6,1.0255781258659012e-6,3.858553115242746e-9,2.947159426985744e-9,5.451744008249845e-9 +ValueContains/8/159,1.5892775694571584e-5,1.5877585613046744e-5,1.591672956167701e-5,6.399555598346714e-8,3.5799362380816734e-8,1.0063803913115515e-7 +ValueContains/10/185,2.137361531127552e-5,2.135467909613083e-5,2.1403687606970723e-5,7.518542065753727e-8,5.137648713268796e-8,1.3073286785031817e-7 +ValueContains/10/91,1.1151935403255879e-5,1.1144430681406825e-5,1.1158844684891731e-5,2.5157456103509433e-8,2.201732529884528e-8,3.006538780012987e-8 +ValueContains/11/1085,1.2988651788975613e-4,1.2981462572788751e-4,1.3003749264320144e-4,3.286283739083712e-7,2.0371002633971985e-7,5.95689052825723e-7 +ValueContains/13/1072,1.3857093340223907e-4,1.3850067808942533e-4,1.386885347964117e-4,3.0051632190937816e-7,2.020327920226665e-7,5.226126121011985e-7 +ValueContains/11/393,4.669665501148989e-5,4.6657424035191804e-5,4.673308125035785e-5,1.255123873170387e-7,1.0759907143982432e-7,1.449603310507858e-7 +ValueContains/13/3733,4.91824389116872e-4,4.916859734586856e-4,4.920202641052555e-4,5.531184362329819e-7,4.0074793327061237e-7,8.30692520985997e-7 +ValueContains/12/2748,3.5668921823068064e-4,3.5655666314544666e-4,3.5693133444759093e-4,5.754388401594542e-7,2.938311926033285e-7,1.0016375907863331e-6 +ValueContains/12/2414,3.108827615804156e-4,3.1082034086075445e-4,3.1096742279927464e-4,2.5262460651262034e-7,1.7477838021292088e-7,4.1177004713548684e-7 +ValueContains/12/1781,2.2581980177882268e-4,2.2577122442829294e-4,2.2588655818004224e-4,1.892281197896396e-7,1.358993243966893e-7,2.650609708491327e-7 +ValueContains/8/238,2.442828447076103e-5,2.4411280744226393e-5,2.4460624925778175e-5,7.913978125338524e-8,5.18405733567112e-8,1.214069698411936e-7 +ValueContains/12/2016,2.593077789498717e-4,2.59235204390236e-4,2.5942251113860766e-4,3.1139133463330415e-7,1.940641055630178e-7,4.958901229901456e-7 +ValueContains/7/44,4.513335955691902e-6,4.508747294551952e-6,4.519329756631066e-6,1.7187814196601805e-8,1.3754853071992287e-8,2.2694812916444914e-8 +ValueContains/10/531,6.100925365118557e-5,6.098108208270612e-5,6.103847704264381e-5,1.00492706271806e-7,8.388878468319219e-8,1.2661612265026414e-7 +ValueContains/11/342,3.9373184811320196e-5,3.935242335973419e-5,3.939829164444051e-5,7.23758438184884e-8,6.019239936021163e-8,8.824575366744494e-8 +ValueContains/10/413,4.8828516715627704e-5,4.8809944406598585e-5,4.885183149995888e-5,6.651011378397961e-8,4.919509217384549e-8,9.039985380246872e-8 +ValueContains/13/1579,2.0726687179975042e-4,2.0722079521846439e-4,2.0731673360402906e-4,1.5741636240492153e-7,1.2140917159290169e-7,2.4385877728819637e-7 +ValueContains/12/1671,2.125708285717146e-4,2.1250767163367025e-4,2.1261317816318216e-4,1.6921897489477105e-7,1.1360520742288753e-7,2.505643620223788e-7 +ValueContains/12/1201,1.5481775147491159e-4,1.5477798414544e-4,1.548791438337921e-4,1.6370436776527397e-7,1.1296250875992578e-7,2.568862769884447e-7 +ValueContains/12/634,7.972304786589202e-5,7.969293026643762e-5,7.975363254395675e-5,9.892278045488739e-8,7.694830110225972e-8,1.2566807490171998e-7 +ValueContains/12/1941,2.4644349151789583e-4,2.4636160574254603e-4,2.465391302972076e-4,2.9320565766746306e-7,2.2110235275023913e-7,3.9670443819445495e-7 +ValueContains/12/1377,1.718083853104113e-4,1.717287590399222e-4,1.7189297806419093e-4,2.732523593950103e-7,2.290611042272379e-7,3.6433264842634313e-7 +ValueContains/12/251,3.1873911831919294e-5,3.186125925261989e-5,3.188482660977345e-5,3.884409834326675e-8,3.196651593526515e-8,4.840326638959013e-8 +ValueContains/12/2519,3.200804583971724e-4,3.1999832783489817e-4,3.20176365925878e-4,2.889335387854318e-7,2.4696689902982606e-7,3.436750217113881e-7 +ValueContains/7/4,1.3506984366698212e-6,1.3498778023741704e-6,1.3515613292390913e-6,2.80073791791712e-9,2.3898329399903386e-9,3.540368797712468e-9 +ValueContains/12/1792,2.261303314806663e-4,2.259551149644636e-4,2.2647062955030841e-4,7.617112614838907e-7,3.670353549129821e-7,1.2514698137428327e-6 +ValueContains/12/2272,2.9018833512851677e-4,2.901014434967882e-4,2.9027951329889455e-4,3.070430597381297e-7,2.4633921423168805e-7,3.98539655716381e-7 +ValueContains/13/3620,4.8387833223194e-4,4.835103629969011e-4,4.8476440619562374e-4,1.767256866401608e-6,7.149361951679961e-7,3.0070131106676433e-6 +ValueContains/12/2767,3.67677896993866e-4,3.67631985764689e-4,3.677538005716184e-4,1.9783893743232698e-7,1.328742319815987e-7,3.1167649536324535e-7 +ValueContains/10/140,1.5496320513223518e-5,1.5480990424216037e-5,1.5508521962132426e-5,4.6506382743084325e-8,3.890399087018622e-8,5.6696472075404526e-8 +ValueContains/12/2926,3.745283246807314e-4,3.744598505573216e-4,3.746112910323646e-4,2.6124203338772244e-7,2.0436907296200443e-7,3.387585057722259e-7 +ValueContains/12/100,1.3193242879778705e-5,1.318751680306371e-5,1.3205385022086972e-5,2.850488361423009e-8,1.482744578503142e-8,5.098964225250428e-8 +ValueContains/12/1921,2.449231365328489e-4,2.4484904310574564e-4,2.4509946334593945e-4,3.664781550277607e-7,2.014381920404878e-7,6.626129308147575e-7 +ValueContains/12/505,6.412295219295507e-5,6.407813508768598e-5,6.422471925516424e-5,2.1200761633209257e-7,1.0067448202855474e-7,4.0189930444131616e-7 +ValueContains/12/2641,3.4048139358443805e-4,3.40415873113124e-4,3.4059078905207107e-4,2.764256166810487e-7,1.955577261571182e-7,3.981570453265424e-7 +ValueContains/12/96,1.2950904338555236e-5,1.2943934797503662e-5,1.2959162778221524e-5,2.5732847526731743e-8,2.1685337454682816e-8,3.135335219198683e-8 +ValueContains/11/446,5.4206134113358184e-5,5.41878659432474e-5,5.4225834288343756e-5,6.82290951488681e-8,5.626634260023341e-8,9.066945108895847e-8 +ValueContains/7/82,7.499871657801869e-6,7.493950253969675e-6,7.507906579624651e-6,2.221401450247578e-8,1.7597694206787737e-8,3.4102264163260685e-8 +ValueContains/13/2322,3.0462623383337205e-4,3.045607186764467e-4,3.047386110886567e-4,2.7995426638892024e-7,1.7706053882372683e-7,4.714642362722683e-7 +ValueContains/11/351,4.138231341566371e-5,4.136578666406264e-5,4.1417405716124915e-5,7.744913203109477e-8,3.365957189279625e-8,1.5327733395398808e-7 +ValueContains/13/1098,1.4308110839482874e-4,1.4303881062037823e-4,1.4316145955084634e-4,1.9307396493534571e-7,1.0995428991022478e-7,3.271758060029778e-7 +ValueContains/11/277,3.314403902361394e-5,3.312943133977003e-5,3.318426024269169e-5,7.486656805416154e-8,4.1396480331147454e-8,1.3847769378042172e-7 +ValueContains/11/773,9.378287549199199e-5,9.373640751810906e-5,9.385524809713384e-5,1.9353113985447817e-7,1.2444238721370948e-7,3.0575571518084373e-7 +ValueContains/13/1794,2.417982854712688e-4,2.4169719924279904e-4,2.4200830348282184e-4,4.5311332542338445e-7,2.483720920519228e-7,7.83025049776069e-7 +ValueContains/12/343,4.230301864573629e-5,4.2290519131894546e-5,4.231802156049992e-5,4.783110774458239e-8,3.773216558094521e-8,6.292841038164774e-8 +ValueContains/7/2,1.1844695710434288e-6,1.183325847614445e-6,1.1862455518902968e-6,4.511248207497589e-9,3.671598272775817e-9,5.7495340602792185e-9 +ValueContains/12/583,6.990142345342221e-5,6.987409559114698e-5,6.992731461931123e-5,9.246286529679772e-8,7.873501813230902e-8,1.1278977138368469e-7 +ValueContains/9/273,2.9750288226899495e-5,2.972554203702476e-5,2.9782076456048907e-5,9.305414438976443e-8,7.023790694832678e-8,1.1965560569516208e-7 +ValueContains/11/1214,1.497982911495322e-4,1.4972203021561262e-4,1.5002103938581201e-4,4.394466651057161e-7,8.597156967058264e-8,8.295889034329942e-7 +ValueContains/12/2076,2.634394270205321e-4,2.633395981967894e-4,2.636375667232603e-4,4.2929592508367976e-7,2.490726812398374e-7,7.988105981376706e-7 +ValueContains/12/140,1.7290295811352744e-5,1.7280092909625215e-5,1.73017797192196e-5,3.584105653872089e-8,2.8928175357300496e-8,5.426809709898994e-8 +ValueContains/12/133,1.766605540602769e-5,1.765595009008035e-5,1.7683901811145586e-5,4.60166112845941e-8,2.7385552265002808e-8,7.569133852187323e-8 +ValueContains/7/74,6.980877302151948e-6,6.975112018018608e-6,6.9863149695818285e-6,1.938247733692031e-8,1.727453448399157e-8,2.281122231443279e-8 +ValueContains/12/997,1.2724533882234058e-4,1.270590209293919e-4,1.2794584544714664e-4,9.963356548040342e-7,4.3946302186355464e-7,2.069075575532036e-6 +ValueContains/12/1977,2.481432042933153e-4,2.4801663654874806e-4,2.4826725994497927e-4,4.336618028454559e-7,3.4004084581708346e-7,5.688034535592003e-7 +ValueContains/12/537,7.063933755829352e-5,7.060860591107332e-5,7.074115883285634e-5,1.4865148961984137e-7,6.213491867106832e-8,3.328776217635917e-7 +ValueContains/13/3356,4.430452282336113e-4,4.4292632151623877e-4,4.4316498476476237e-4,4.1197200567346226e-7,3.3558701297573e-7,5.143568644769447e-7 +ValueContains/12/2268,2.858808793294172e-4,2.857192496745244e-4,2.8620752686500986e-4,7.380580383611614e-7,4.0137638991986903e-7,1.3895567595098996e-6 +ValueContains/10/528,5.964122788727593e-5,5.961513882163397e-5,5.966939957325345e-5,9.141284574020593e-8,8.112416171249595e-8,1.029407591017846e-7 +ValueContains/13/105,1.4031246562269162e-5,1.400866514587525e-5,1.4069178147841297e-5,9.714513815092244e-8,6.073367656984795e-8,1.812794734468918e-7 +ValueContains/12/676,8.505155664235578e-5,8.500310139698682e-5,8.509900380985492e-5,1.6810211068199886e-7,1.4596082806925588e-7,1.976215136897861e-7 +ValueContains/12/2328,2.9854311744574005e-4,2.9842888316399874e-4,2.9889319844234334e-4,6.209611414573777e-7,2.0617436636801655e-7,1.348757349335276e-6 +ValueContains/12/1092,1.3612422612650391e-4,1.36093476011573e-4,1.3617823673165775e-4,1.4155208486020096e-7,7.983759980008221e-8,2.3449890937893345e-7 +ValueContains/9/50,5.672801645816502e-6,5.6682741177157975e-6,5.679581933920019e-6,1.8774156546820317e-8,1.4143094985411332e-8,3.0109775926256164e-8 +ValueContains/13/3703,4.8524429434496487e-4,4.850912960838038e-4,4.8536120706704804e-4,4.6077158118373524e-7,2.925150965479825e-7,7.111386230750456e-7 +ValueContains/12/830,1.0367317657869579e-4,1.0362302935720768e-4,1.0374102452140129e-4,1.9864350320410719e-7,1.0979656921844266e-7,3.672131407624006e-7 +ValueContains/11/801,9.708814939971309e-5,9.706146789940075e-5,9.7123195797267e-5,1.0176074916108242e-7,8.006326132194934e-8,1.4757267907833082e-7 +ValueContains/12/3255,4.209523250487745e-4,4.2071863309525064e-4,4.212060672432006e-4,7.937318132261511e-7,5.186245377446395e-7,1.184892070490809e-6 +ValueContains/13/2881,3.804446422686174e-4,3.803644244726478e-4,3.8052289221913495e-4,2.6467595199811566e-7,2.1423040651816354e-7,3.28111223781533e-7 +ValueContains/12/1851,2.3166803796986323e-4,2.3157177406631676e-4,2.320120786090039e-4,5.480484600704621e-7,2.1401356528940427e-7,1.0674459617773102e-6 +ValueContains/10/300,3.427135937742027e-5,3.425525346657818e-5,3.430477403804241e-5,7.376726434604575e-8,4.594948069157006e-8,1.254656056239515e-7 +ValueContains/6/15,1.9673707634139657e-6,1.9658051539892416e-6,1.9687728900773386e-6,5.092698901132448e-9,4.394467257629831e-9,6.194528667856454e-9 +ValueContains/12/1488,1.8555607212043693e-4,1.8549756530316977e-4,1.8563239010901088e-4,2.151009512928942e-7,1.769206705188598e-7,2.8405782926484203e-7 +ValueContains/11/566,6.875001544018517e-5,6.871499807609513e-5,6.877902059204304e-5,1.1378877346907602e-7,8.71184634345072e-8,1.681774092879163e-7 +ValueContains/12/648,8.01158796565461e-5,8.009440934736991e-5,8.015760253068128e-5,9.480422542669123e-8,6.29385872996164e-8,1.661190534128933e-7 +ValueContains/11/1339,1.6279036309018897e-4,1.6271737416881867e-4,1.630355893581192e-4,4.021572503880551e-7,1.2593372122030916e-7,8.091123510443709e-7 +ValueContains/12/104,1.3862945296886261e-5,1.385566311455628e-5,1.3870449882700787e-5,2.418916175343945e-8,1.983993390085188e-8,3.186756020778998e-8 +ValueContains/10/389,4.353518160586402e-5,4.351111440535118e-5,4.3594770241704784e-5,1.1884022923606531e-7,5.227908651591945e-8,2.120260245942795e-7 +ValueContains/9/194,2.0605685664495366e-5,2.0597979218940725e-5,2.0612863523244333e-5,2.4178073267751346e-8,2.0623027333395742e-8,2.950618287737528e-8 +ValueContains/12/2166,2.839476116926073e-4,2.8384942060249605e-4,2.840476990372169e-4,3.200849559887564e-7,2.2085059900661048e-7,4.5249570004422134e-7 +ValueContains/12/826,1.0291972752476672e-4,1.0290622647799034e-4,1.0293832099030254e-4,5.3843479700628356e-8,4.136983761007242e-8,7.575936893506993e-8 +ValueContains/12/2062,2.6275680036602677e-4,2.626643365754972e-4,2.630939722373389e-4,4.987384941349451e-7,2.044566245968875e-7,1.0565493554120336e-6 +ValueContains/11/1298,1.5816518555177684e-4,1.5810274833115147e-4,1.5827058942474985e-4,2.610257995044986e-7,1.75612865747802e-7,4.0085374276342557e-7 +ValueContains/8/34,3.794064738555039e-6,3.7905687911235624e-6,3.7977198576196703e-6,1.2109253674844755e-8,1.0372661254205007e-8,1.4880875550464317e-8 +ValueContains/12/609,7.860466767546641e-5,7.857672523324214e-5,7.864340555710777e-5,1.1832546404977498e-7,8.961776865817092e-8,1.7291316182594115e-7 +ValueContains/12/1727,2.1439243046804043e-4,2.142927702108739e-4,2.1478127666131743e-4,5.655333557812445e-7,1.8551282671783354e-7,1.1494143053163487e-6 +ValueContains/10/506,5.8137844413488266e-5,5.810370022013693e-5,5.826154726540427e-5,1.8160283705985924e-7,7.18144729472629e-8,4.055097141695691e-7 +ValueContains/11/1473,1.8153166240891892e-4,1.8139372458733131e-4,1.81823969995465e-4,6.590248199879426e-7,3.2576282992561835e-7,1.22097626898255e-6 +ValueContains/13/2126,2.7331859396513835e-4,2.7324305935906264e-4,2.7340902939903004e-4,2.884884774575182e-7,2.2419699113299884e-7,4.0842883312352495e-7 +ValueContains/11/689,8.239050370208903e-5,8.232006023152852e-5,8.256629349109647e-5,3.4543080502202307e-7,1.634865263814583e-7,6.516745647442046e-7 +ValueContains/13/4197,5.502806471788047e-4,5.500604012729804e-4,5.505580149482997e-4,8.471742861868089e-7,7.170851417814597e-7,1.1404789482084809e-6 +ValueContains/12/1133,1.3959924949511369e-4,1.3949983817469004e-4,1.398059775160836e-4,4.5402512018825686e-7,2.373855360928698e-7,7.428315700145905e-7 +ValueContains/11/434,5.1257436408181545e-5,5.12259118784171e-5,5.129300094394052e-5,1.1523062373191474e-7,9.541888639357979e-8,1.483216225020858e-7 +ValueContains/10/326,3.762261697891163e-5,3.7601902485654975e-5,3.7649436777688194e-5,7.920679117432433e-8,5.676849225639675e-8,1.0616551578760696e-7 +ValueContains/11/777,9.381081266365895e-5,9.37832061434814e-5,9.38521389836732e-5,1.1671865692645083e-7,8.044094653735345e-8,1.6730516767134855e-7 +ValueContains/13/2294,2.969049648468808e-4,2.967759956914527e-4,2.974357886227835e-4,7.488432083158731e-7,2.4823802516892874e-7,1.5144144922125704e-6 +ValueContains/12/1337,1.6715472990647796e-4,1.6712755771230948e-4,1.6718864510724058e-4,1.0396673909961183e-7,8.381767987414707e-8,1.3886616647157168e-7 +ValueContains/12/2392,3.099221611844788e-4,3.0972161488671565e-4,3.1026024232492556e-4,8.377928389988515e-7,5.047248844643975e-7,1.4104299842810961e-6 +ValueContains/13/2706,3.5759067054318903e-4,3.5748827158919855e-4,3.577258345587112e-4,3.8622708325294097e-7,2.7162147123131547e-7,5.974005435081299e-7 +ValueContains/12/1533,1.9156475043136803e-4,1.9148005720111638e-4,1.9177907547072892e-4,4.168133171708497e-7,2.2480554317666833e-7,7.757516391772386e-7 +ValueData/0,8.259375279998844e-7,8.252153289694753e-7,8.267435757851359e-7,2.5087705150514537e-9,2.117341878281717e-9,2.9850655959576934e-9 +ValueData/10,8.221146711312163e-7,8.211735000060185e-7,8.228624974519468e-7,2.861350690629261e-9,2.1899982467470096e-9,4.110447495546439e-9 +ValueData/100,8.212224366115354e-7,8.204905637428957e-7,8.219787693881847e-7,2.436625822300213e-9,2.0221123644803654e-9,3.009515028623728e-9 +ValueData/500,8.248429906764184e-7,8.239639274683871e-7,8.261206270212216e-7,3.2963783055617143e-9,2.328798700742226e-9,5.281050375500905e-9 +ValueData/1000,8.266715364291172e-7,8.259256854847058e-7,8.273024867888763e-7,2.3627020454205105e-9,2.076315554478266e-9,2.667842403662652e-9 +ValueData/5000,8.269838196178779e-7,8.261944361375068e-7,8.280347106212685e-7,2.981523644754545e-9,2.225378400537329e-9,4.7192096485766726e-9 +ValueData/10000,8.250900248844933e-7,8.242269683856638e-7,8.25915926475446e-7,2.8848855941251203e-9,2.496786947682346e-9,3.353350229428064e-9 +ValueData/12,8.278939657425042e-7,8.270791800408652e-7,8.292225226548215e-7,3.462633447617647e-9,2.3024244758466204e-9,5.988582760096897e-9 +ValueData/132,8.262928362197708e-7,8.25567802657832e-7,8.269099504347259e-7,2.174867756612828e-9,1.8246969727089798e-9,2.654464948948167e-9 +ValueData/400,8.238256311066887e-7,8.229858410869695e-7,8.247524144983101e-7,2.810862264100594e-9,2.243319106898002e-9,3.7244731528022417e-9 +ValueData/27066,8.25083601618178e-7,8.245349000496211e-7,8.259067059349859e-7,2.235829421761038e-9,1.7136892591676215e-9,3.3933410502468457e-9 +ValueData/5358,8.255531931512631e-7,8.248900202279681e-7,8.27382601367956e-7,3.155133204754369e-9,1.820661096828026e-9,6.005980951002198e-9 +ValueData/34510,8.262905911013016e-7,8.25201894215541e-7,8.276468481425179e-7,4.051451967280871e-9,2.887843868830607e-9,6.660953180418949e-9 +ValueData/57816,8.26866916187003e-7,8.257918752246246e-7,8.278082184290757e-7,3.3989729322532647e-9,2.7384983891847164e-9,4.157570916175028e-9 +ValueData/6946,8.242690528556214e-7,8.236882269297737e-7,8.254414480207965e-7,2.5884054352735257e-9,1.51662640317413e-9,4.8398561971024826e-9 +ValueData/267444,8.346256717138532e-7,8.335033219674349e-7,8.358014604927717e-7,3.8521849121486144e-9,3.161142843810333e-9,4.780660843505411e-9 +ValueData/1620,8.303504891246882e-7,8.296270464937316e-7,8.31023934280632e-7,2.3312169221054436e-9,1.9146381836215283e-9,2.915868591621596e-9 +ValueData/49404,8.245363727986023e-7,8.239473679852392e-7,8.251173947849452e-7,2.0314389914259746e-9,1.705168157946653e-9,2.6848337027539e-9 +ValueData/388385,8.244094522374476e-7,8.232054418438292e-7,8.254818473106365e-7,3.6994404145640697e-9,2.9451746653959487e-9,4.6504933216466155e-9 +ValueData/311344,8.228681299096737e-7,8.219090595395827e-7,8.24328829260724e-7,4.0373488037749086e-9,2.7590940723392936e-9,6.13659361503511e-9 +ValueData/260442,8.239771387687647e-7,8.233895395621375e-7,8.246118107582908e-7,1.9619303537023055e-9,1.5973584121689779e-9,2.368725321950424e-9 +ValueData/198648,8.258208970048934e-7,8.25151624890348e-7,8.271188118407746e-7,2.983500587615112e-9,1.6807559430556488e-9,5.4378190731736525e-9 +ValueData/184512,8.272003105859325e-7,8.265128572099665e-7,8.278039946192013e-7,2.1902162617535296e-9,1.8309180325841673e-9,2.7018175580523304e-9 +ValueData/99822,8.271312311286199e-7,8.260362915248513e-7,8.284973785612256e-7,4.121380522315001e-9,3.2772618432261308e-9,5.972824980138077e-9 +ValueData/84744,8.28322794026114e-7,8.278732878388506e-7,8.288705998976038e-7,1.644207113160797e-9,1.360036887491121e-9,2.214355178194003e-9 +ValueData/2828,8.30525441273806e-7,8.29756113406469e-7,8.313208957860836e-7,2.59427342233359e-9,2.2226274150548094e-9,3.2570012019546085e-9 +ValueData/56800,8.260878808754813e-7,8.253288322733565e-7,8.268930431229305e-7,2.4877402436300583e-9,2.1204235754740468e-9,3.01806502274434e-9 +ValueData/20874,8.259417460668029e-7,8.249060710721996e-7,8.273769490395069e-7,4.097591447043488e-9,3.0382324849589755e-9,6.482262327359846e-9 +ValueData/81396,8.222632786779464e-7,8.216811450375727e-7,8.229221894734487e-7,2.16996535363592e-9,1.863349599023836e-9,2.5843777140456974e-9 +ValueData/7776,8.260966798515111e-7,8.251160439338485e-7,8.276475951133831e-7,4.183367402401495e-9,2.8268974388120115e-9,6.626203890787823e-9 +ValueData/82000,8.261022088670282e-7,8.248680096006831e-7,8.274194413132213e-7,4.055233051038916e-9,3.475651731036169e-9,4.843581682355438e-9 +ValueData/2514,8.297633130644205e-7,8.293003490612942e-7,8.303221148861796e-7,1.6697469065332867e-9,1.4186878657320109e-9,2.0676014797707226e-9 +ValueData/63883,8.272410708284946e-7,8.262742005455105e-7,8.281903914374403e-7,3.207568523041863e-9,2.682833126233864e-9,4.0398447806312014e-9 +ValueData/29920,8.250593633522062e-7,8.243468808038325e-7,8.262786193787849e-7,3.1576886434701445e-9,2.2689297120984097e-9,4.381467176415186e-9 +ValueData/207740,8.291129293345739e-7,8.283768530879131e-7,8.300543983205882e-7,2.806418467257282e-9,2.335327522017162e-9,3.344876911837507e-9 +ValueData/120500,8.258771552969031e-7,8.248307782757096e-7,8.283364646654e-7,4.942766353269775e-9,2.4111098659658596e-9,1.1005898272172465e-8 +ValueData/10386,8.281762527413857e-7,8.266949821437386e-7,8.295558876222537e-7,4.8719821732488705e-9,4.3062638075069556e-9,5.544445955864192e-9 +ValueData/62216,8.258394172009131e-7,8.24334999280891e-7,8.273215381077913e-7,4.712712971771237e-9,4.163952069006148e-9,5.391943818976089e-9 +ValueData/110826,8.273367368255515e-7,8.267841916633614e-7,8.278711098423912e-7,1.8789325074363535e-9,1.5911381195753375e-9,2.3150036020113412e-9 +ValueData/41817,8.291714200812619e-7,8.281383831142686e-7,8.31577813854755e-7,4.820051101605578e-9,2.5544320842279827e-9,8.874051951930856e-9 +ValueData/69934,8.285374340044779e-7,8.277409169365587e-7,8.294005559488315e-7,2.6870328679906937e-9,2.257269794603768e-9,3.2874678253488317e-9 +ValueData/195776,8.274415299400283e-7,8.264169380116746e-7,8.289378612762599e-7,4.136920390650902e-9,2.6528928104323973e-9,6.945285474691269e-9 +ValueData/413556,8.275534122235766e-7,8.270140063759432e-7,8.280492286911896e-7,1.7856044752167336e-9,1.4732678731286447e-9,2.1659365436004765e-9 +ValueData/22695,8.271775662968697e-7,8.260523673856607e-7,8.291440390302232e-7,4.83281736420234e-9,3.0907329142161405e-9,8.403059269520945e-9 +ValueData/54526,8.290747835819978e-7,8.28521918085665e-7,8.296757048421197e-7,2.0509969892782474e-9,1.846939289601749e-9,2.32290462624725e-9 +ValueData/9512,8.262546302976572e-7,8.251343121766955e-7,8.299968615834592e-7,6.3972105984306e-9,2.1457075596486475e-9,1.2881978718084955e-8 +ValueData/39990,8.272493830940491e-7,8.265560311468243e-7,8.280835912920267e-7,2.580492760735123e-9,2.26777072444934e-9,3.0420223583682754e-9 +ValueData/225646,8.249524841929177e-7,8.242317948674715e-7,8.266867888585946e-7,3.5219967224749615e-9,1.8500328713956601e-9,6.662142380992675e-9 +ValueData/54540,8.255774637395604e-7,8.250643183517212e-7,8.261743508251389e-7,1.7291047802572835e-9,1.4132309970140771e-9,2.1134377345405637e-9 +ValueData/336072,8.260860447475383e-7,8.253420627217906e-7,8.271284296440245e-7,3.0451206220405075e-9,1.900829978153231e-9,5.568419513484841e-9 +ValueData/17955,8.300496044418231e-7,8.294572996009988e-7,8.307365979378417e-7,2.1523466579080415e-9,1.8162890673831022e-9,2.5497445421369792e-9 +ValueData/166144,8.26906675392406e-7,8.264604470081705e-7,8.27379446376845e-7,1.6006064445308071e-9,1.3372404690061647e-9,2.0096898449589813e-9 +ValueData/279876,8.28985795470153e-7,8.285414777372236e-7,8.294584037367623e-7,1.5085279774484512e-9,1.2621145878156026e-9,1.8111175917751756e-9 +ValueData/35364,8.277404706769311e-7,8.272715161967813e-7,8.282863492832091e-7,1.7251475843450939e-9,1.4449632483925262e-9,2.1375735575904186e-9 +ValueData/64527,8.286341412971453e-7,8.278020651802567e-7,8.295777340956106e-7,2.851678762400587e-9,2.4136648947556414e-9,3.5163219492272073e-9 +ValueData/100182,8.286903709070453e-7,8.282554521101623e-7,8.292472468329749e-7,1.6438909643656652e-9,1.3235981702048535e-9,2.0367351130009526e-9 +ValueData/18408,8.311576693891226e-7,8.300375931544523e-7,8.322524851394231e-7,3.541582023700388e-9,3.1045597296098848e-9,4.3255013820169976e-9 +ValueData/181685,8.295345621976337e-7,8.287839933288239e-7,8.302901281708805e-7,2.595595227154869e-9,2.2433699762362337e-9,3.082451952306541e-9 +ValueData/113526,8.281846642492015e-7,8.273848320790801e-7,8.290264475092894e-7,2.916501112066787e-9,2.3464624240461492e-9,3.5718770138241056e-9 +ValueData/53988,8.299184290613442e-7,8.283799719784051e-7,8.314833572667615e-7,5.1777187544619055e-9,4.517922756978937e-9,5.974526373361333e-9 +UnValueData/4,8.835680836498377e-7,8.821008747506569e-7,8.850917047245195e-7,4.899544994034088e-9,4.296616318762323e-9,5.574382537952672e-9 +UnValueData/146,2.7863990400473593e-6,2.7821974335365375e-6,2.790409692595142e-6,1.3239669496119918e-8,1.1852740190735835e-8,1.551331534659293e-8 +UnValueData/1424,1.8478503563433924e-5,1.8459203068869175e-5,1.8499169343622076e-5,6.605037275727506e-8,5.277809418442778e-8,9.269222969153358e-8 +UnValueData/7104,8.994379859002063e-5,8.988085879500752e-5,9.006193951085749e-5,2.622870869933662e-7,1.812730108499912e-7,4.2823165542337013e-7 +UnValueData/14204,1.8279326234183993e-4,1.8259398173796644e-4,1.8299602591983756e-4,6.986930275073668e-7,6.281398041465083e-7,8.121073186666243e-7 +UnValueData/71004,1.032483942633388e-3,1.0276617030566344e-3,1.0367105390833985e-3,1.568771652132178e-5,1.1909649698973034e-5,2.0734468512154628e-5 +UnValueData/142004,2.468920144391297e-3,2.4590062402060314e-3,2.4798825125268704e-3,3.4152431190953874e-5,2.740337116584026e-5,4.431975197616275e-5 +UnValueData/196,3.1849441144986897e-6,3.181153146932377e-6,3.1887073691549533e-6,1.2680053956947538e-8,1.0848741716993316e-8,1.4641596172017785e-8 +UnValueData/1852,2.4213034882501317e-5,2.4193403446031334e-5,2.4236032177135e-5,7.027599648785188e-8,5.313848331011267e-8,1.0437005322575838e-7 +UnValueData/5444,7.363337236077213e-5,7.357233615795939e-5,7.372445375707624e-5,2.571028465912988e-7,1.7186499312593706e-7,4.0094940737665106e-7 +UnValueData/356026,7.512898078043502e-3,7.4830968635702854e-3,7.543254426846885e-3,8.501571276113754e-5,6.644133015688417e-5,1.147160633971311e-4 +UnValueData/70222,1.4077375874541774e-3,1.401913702684408e-3,1.413240968796658e-3,2.0452036179115896e-5,1.5142510601107924e-5,2.656393589688059e-5 +UnValueData/449474,1.1794154220525979e-2,1.1710000862021428e-2,1.200667530235313e-2,3.480266121230809e-4,1.663259829762643e-4,6.453780307830345e-4 +UnValueData/761248,1.761836913202244e-2,1.7354841414820635e-2,1.7822459851491577e-2,5.673587382836573e-4,3.354731556503015e-4,9.945073920221942e-4 +UnValueData/92114,1.745665847360822e-3,1.7393742682095211e-3,1.7519721326725718e-3,2.0838620778171688e-5,1.7327642086152675e-5,2.5985056084919643e-5 +UnValueData/3486712,0.12232599157349407,0.12000591489777435,0.12532255539762055,4.168880595756439e-3,2.672448580743459e-3,6.676303276606794e-3 +UnValueData/21280,3.682597278870657e-4,3.6794703812317864e-4,3.685850146430806e-4,1.1626796880614985e-6,9.7288084937758e-7,1.3764775229619527e-6 +UnValueData/643912,1.6615853417736474e-2,1.6432528281390305e-2,1.6799985030561123e-2,4.490480427021394e-4,2.117155595267092e-4,7.570468003968353e-4 +UnValueData/5059389,0.18172550208659635,0.17381364352380235,0.18589389039100043,7.255540644276801e-3,2.8996347290392932e-3,1.0112684236372642e-2 +UnValueData/4059188,0.1427900107887884,0.1382630933963117,0.14539130381530238,4.7967744005390925e-3,1.9462882443792564e-3,7.1880604987698314e-3 +UnValueData/3394018,0.11998753921985293,0.11639342138022628,0.12240306079897674,4.477202726289051e-3,2.5095213777627584e-3,6.9935808057352816e-3 +UnValueData/2588836,9.069903282394445e-2,8.884892758602897e-2,9.231190363871594e-2,2.976751874966214e-3,1.912332998493141e-3,5.1051210308385745e-3 +UnValueData/2404612,8.406764467875104e-2,8.249424194569685e-2,8.638918947169764e-2,3.239517219620891e-3,2.1344292035203544e-3,4.717589686080588e-3 +UnValueData/1302406,3.928079960975326e-2,3.856630462894527e-2,4.0151175236643084e-2,1.5633000154927855e-3,1.0777084744972082e-3,2.4387164033466474e-3 +UnValueData/1104844,3.171325183346789e-2,3.1273619961013736e-2,3.211334598453468e-2,9.209170406590446e-4,6.94432589699387e-4,1.2627805732313407e-3 +UnValueData/36936,7.262882443380538e-4,7.257986204570035e-4,7.26876116294966e-4,1.6928347204863874e-6,1.4581954436170541e-6,1.984927987975492e-6 +UnValueData/740324,1.9843216766148173e-2,1.9610488228152662e-2,2.011189483243265e-2,6.229062241225948e-4,4.09137262691574e-4,9.282102599040224e-4 +UnValueData/283294,5.13410384300042e-3,5.114190634073477e-3,5.155231375096413e-3,6.195492773719875e-5,4.163739006209691e-5,9.996927841982114e-5 +UnValueData/1061008,3.0808573769223586e-2,3.0378270170636247e-2,3.1827057958966294e-2,1.3592543796541508e-3,5.46711239945081e-4,2.3640711894901056e-3 +UnValueData/112756,1.9103260941979612e-3,1.903408245566379e-3,1.916145706498395e-3,2.2015436763870684e-5,1.6566300286232204e-5,2.957442517524344e-5 +UnValueData/1068404,3.148452288807444e-2,3.1032800725751188e-2,3.229842965915843e-2,1.2114410729678296e-3,6.182015635173954e-4,2.185704108290375e-3 +UnValueData/37714,4.935526954067097e-4,4.93192751298099e-4,4.939097467266982e-4,1.218182864236061e-6,9.971034626337653e-7,1.652525242337308e-6 +UnValueData/834455,2.110420367211012e-2,2.0818306534419382e-2,2.1269491231185968e-2,4.7560117951338064e-4,2.822069847031158e-4,8.404329530257744e-4 +UnValueData/399524,7.946863537235265e-3,7.909494547575542e-3,7.979421373306999e-3,1.0144696559674803e-4,8.06381542273022e-5,1.4051700649133893e-4 +UnValueData/2705928,9.730700290551643e-2,9.470541283021791e-2,9.940508027795893e-2,3.8717374225748515e-3,2.4981413539574425e-3,5.8304123545070375e-3 +UnValueData/1572288,4.9960083316046844e-2,4.921107540052187e-2,5.0708015504342625e-2,1.450536110245453e-3,1.0165158874141393e-3,2.0555501760789285e-3 +UnValueData/141946,2.460609820471755e-3,2.4506989114876127e-3,2.4684096946986454e-3,3.08747410809671e-5,2.3150602049093322e-5,4.158896198123118e-5 +UnValueData/818508,1.895015110998868e-2,1.874412593984232e-2,1.908207502350236e-2,4.0951510223757366e-4,2.384979212493314e-4,6.577822282692453e-4 +UnValueData/1444126,4.649182713237036e-2,4.596650244968709e-2,4.7160717035441016e-2,1.1524449686703474e-3,7.249542417638462e-4,1.8727522550872392e-3 +UnValueData/553093,1.2045063189785219e-2,1.197071839982743e-2,1.2132085076381086e-2,2.1202171386635287e-4,1.63402796959337e-4,2.8407276277787424e-4 +UnValueData/920642,2.2899782303193162e-2,2.251928142514345e-2,2.3629731335017844e-2,1.1554777013896768e-3,6.545064448667906e-4,1.941275389329934e-3 +UnValueData/2555580,8.716069243083309e-2,8.557809631883477e-2,8.833630486956931e-2,2.3135718984961693e-3,1.2403792256509949e-3,4.0525319437013044e-3 +UnValueData/5387800,0.19215508130016842,0.18566061636536488,0.19696732387981483,7.873635626777477e-3,4.815282836398895e-3,1.2127153724338098e-2 +UnValueData/295651,7.531843969087549e-3,7.503089541366385e-3,7.560909121188496e-3,8.112488137456363e-5,6.415137922978193e-5,1.0543744241191568e-4 +UnValueData/713618,1.7541463065843577e-2,1.7276633286149378e-2,1.810408729290783e-2,9.12376773449063e-4,4.507690750845055e-4,1.5068952509599462e-3 +UnValueData/124152,2.916987366372547e-3,2.9091734021958796e-3,2.9230849874677463e-3,2.174847211559988e-5,1.578230167789592e-5,3.1488792081301096e-5 +UnValueData/527614,1.1345538708850654e-2,1.1247166254819248e-2,1.1440643774327457e-2,2.7013714525086976e-4,1.6990371359934498e-4,4.176259904770178e-4 +UnValueData/2939570,0.1037927473940011,0.10039873882254333,0.10512694199039802,3.5463090100688694e-3,6.658321217664263e-4,5.6895991282306935e-3 +UnValueData/719932,1.6556323163951666e-2,1.6277707271500293e-2,1.6714099077960384e-2,5.0198150918265e-4,2.6115306979283115e-4,9.319304598393031e-4 +UnValueData/4378972,0.15701045863311358,0.15083434020302125,0.159470377589709,5.5422440681979525e-3,1.0495642464235164e-3,7.922497502884816e-3 +UnValueData/235687,5.048006611934687e-3,5.029593475145545e-3,5.060741830465507e-3,4.6044708844476356e-5,3.3021312887585965e-5,6.490356422457591e-5 +UnValueData/2167664,7.366252842079285e-2,7.143738986885806e-2,7.46436465872602e-2,2.4079876799893585e-3,1.0160435018232202e-3,3.980840638718813e-3 +UnValueData/3645136,0.13117595511374974,0.12717934568007921,0.13336424299147134,4.488203809813884e-3,2.2734343718311912e-3,7.002266659136294e-3 +UnValueData/464788,1.0145085835126464e-2,1.0095077942666023e-2,1.0201426795703647e-2,1.4568356974487839e-4,1.0919325031797931e-4,2.219934598293472e-4 +UnValueData/840499,2.406794475520991e-2,2.383805307922955e-2,2.4529467660739764e-2,6.952229126114989e-4,3.4200223020673404e-4,1.2053827877354449e-3 +UnValueData/1309162,3.874095447684746e-2,3.8267170288157924e-2,3.907439312712836e-2,8.360306265540415e-4,4.316039882644803e-4,1.4219633350870575e-3 +UnValueData/243556,4.944059401941106e-3,4.925888626062511e-3,4.960424600000067e-3,5.441960331902805e-5,4.282901822637958e-5,6.952968524756884e-5 +UnValueData/2372649,8.007962980873085e-2,7.849782424923477e-2,8.176850379001172e-2,2.763560645363069e-3,1.8005278382191869e-3,4.066712892469676e-3 +UnValueData/1479514,4.769281767907638e-2,4.718665239766185e-2,4.8264427716201125e-2,1.0643947840050763e-3,7.610122765517957e-4,1.5677161335164475e-3 +UnValueData/703432,1.8827785758564447e-2,1.873784910998197e-2,1.893703626851274e-2,2.2962044934602378e-4,1.6731049277402885e-4,3.5443334332768326e-4 diff --git a/plutus-core/cost-model/data/builtinCostModelA.json b/plutus-core/cost-model/data/builtinCostModelA.json index fbe4c0a3218..2266ce44650 100644 --- a/plutus-core/cost-model/data/builtinCostModelA.json +++ b/plutus-core/cost-model/data/builtinCostModelA.json @@ -1209,8 +1209,8 @@ "lookupCoin": { "cpu": { "arguments": { - "intercept": 209937, - "slope": 7181 + "intercept": 203599, + "slope": 7256 }, "type": "linear_in_z" }, @@ -1223,7 +1223,7 @@ "cpu": { "arguments": { "intercept": 1000, - "slope": 131959 + "slope": 130720 }, "type": "linear_in_y" }, @@ -1234,7 +1234,7 @@ }, "valueData": { "cpu": { - "arguments": 182815, + "arguments": 156990, "type": "constant_cost" }, "memory": { @@ -1246,7 +1246,7 @@ "cpu": { "arguments": { "intercept": 1000, - "slope": 33361 + "slope": 36194 }, "type": "linear_in_x" }, diff --git a/plutus-core/cost-model/data/builtinCostModelB.json b/plutus-core/cost-model/data/builtinCostModelB.json index 43080c3de3d..5adaf9d9253 100644 --- a/plutus-core/cost-model/data/builtinCostModelB.json +++ b/plutus-core/cost-model/data/builtinCostModelB.json @@ -1209,8 +1209,8 @@ "lookupCoin": { "cpu": { "arguments": { - "intercept": 209937, - "slope": 7181 + "intercept": 203599, + "slope": 7256 }, "type": "linear_in_z" }, @@ -1223,7 +1223,7 @@ "cpu": { "arguments": { "intercept": 1000, - "slope": 131959 + "slope": 130720 }, "type": "linear_in_y" }, @@ -1234,7 +1234,7 @@ }, "valueData": { "cpu": { - "arguments": 182815, + "arguments": 156990, "type": "constant_cost" }, "memory": { @@ -1246,7 +1246,7 @@ "cpu": { "arguments": { "intercept": 1000, - "slope": 33361 + "slope": 36194 }, "type": "linear_in_x" }, diff --git a/plutus-core/cost-model/data/builtinCostModelC.json b/plutus-core/cost-model/data/builtinCostModelC.json index dabd53de9f9..29504a4f236 100644 --- a/plutus-core/cost-model/data/builtinCostModelC.json +++ b/plutus-core/cost-model/data/builtinCostModelC.json @@ -1227,8 +1227,8 @@ "lookupCoin": { "cpu": { "arguments": { - "intercept": 209937, - "slope": 7181 + "intercept": 203599, + "slope": 7256 }, "type": "linear_in_z" }, @@ -1241,7 +1241,7 @@ "cpu": { "arguments": { "intercept": 1000, - "slope": 131959 + "slope": 130720 }, "type": "linear_in_y" }, @@ -1252,7 +1252,7 @@ }, "valueData": { "cpu": { - "arguments": 182815, + "arguments": 156990, "type": "constant_cost" }, "memory": { @@ -1264,7 +1264,7 @@ "cpu": { "arguments": { "intercept": 1000, - "slope": 33361 + "slope": 36194 }, "type": "linear_in_x" }, From d42b9636151bd90f626815b1e90eb9d87e3b00c8 Mon Sep 17 00:00:00 2001 From: Ana Pantilie Date: Tue, 16 Sep 2025 18:40:30 +0300 Subject: [PATCH 16/17] Add insertCoin and unionValue costing skeleton --- .../create-cost-model/BuiltinMemoryModels.hs | 2 + .../CreateBuiltinCostModel.hs | 12 + .../cost-model/data/builtinCostModelA.json | 2353 +++++++++-------- .../cost-model/data/builtinCostModelB.json | 20 + .../cost-model/data/builtinCostModelC.json | 20 + .../src/PlutusCore/Default/Builtins.hs | 4 +- .../Evaluation/Machine/BuiltinCostModel.hs | 2 + .../Evaluation/Machine/ExBudgetingDefaults.hs | 5 + 8 files changed, 1247 insertions(+), 1171 deletions(-) diff --git a/plutus-core/cost-model/create-cost-model/BuiltinMemoryModels.hs b/plutus-core/cost-model/create-cost-model/BuiltinMemoryModels.hs index a138a9bbf1b..cb664c87936 100644 --- a/plutus-core/cost-model/create-cost-model/BuiltinMemoryModels.hs +++ b/plutus-core/cost-model/create-cost-model/BuiltinMemoryModels.hs @@ -181,5 +181,7 @@ builtinMemoryModels = BuiltinCostModelBase , paramValueContains = Id $ ModelTwoArgumentsConstantCost 1 , paramValueData = Id $ ModelOneArgumentConstantCost 1 , paramUnValueData = Id $ ModelOneArgumentConstantCost 1 + , paramInsertCoin = Id $ ModelFourArgumentsConstantCost 1 + , paramUnionValue = Id $ ModelTwoArgumentsConstantCost 1 } where identityFunction = OneVariableLinearFunction 0 1 diff --git a/plutus-core/cost-model/create-cost-model/CreateBuiltinCostModel.hs b/plutus-core/cost-model/create-cost-model/CreateBuiltinCostModel.hs index 9d138865dde..fff87c349a5 100644 --- a/plutus-core/cost-model/create-cost-model/CreateBuiltinCostModel.hs +++ b/plutus-core/cost-model/create-cost-model/CreateBuiltinCostModel.hs @@ -136,6 +136,8 @@ builtinCostModelNames = BuiltinCostModelBase , paramValueContains = "valueContainsModel" , paramValueData = "valueDataModel" , paramUnValueData = "unValueDataModel" + , paramInsertCoin = "insertCoinModel" + , paramUnionValue = "unionValueModel" } @@ -289,6 +291,9 @@ createBuiltinCostModel bmfile rfile = do paramValueContains <- getParams readCF2 paramValueContains paramValueData <- getParams readCF1 paramValueData paramUnValueData <- getParams readCF1 paramUnValueData + -- Values + paramInsertCoin <- getParams readCF4 paramInsertCoin + paramUnionValue <- getParams readCF2 paramUnionValue pure $ BuiltinCostModelBase {..} @@ -452,6 +457,13 @@ readCF3 e = do "exp_mod_cost" -> ModelThreeArgumentsExpModCost <$> readExpModCostingFunction "y_mem" "z_mem" e _ -> error $ "Unknown three-variable model type: " ++ ty +readCF4 :: MonadR m => SomeSEXP (Region m) -> m ModelFourArguments +readCF4 e = do + ty <- getType e + case ty of + "constant_cost" -> ModelFourArgumentsConstantCost <$> getConstant e + _ -> error $ "Unknown four-variable model type: " ++ ty + readCF6 :: MonadR m => SomeSEXP (Region m) -> m ModelSixArguments readCF6 e = do ty <- getType e diff --git a/plutus-core/cost-model/data/builtinCostModelA.json b/plutus-core/cost-model/data/builtinCostModelA.json index 2266ce44650..66c908673b8 100644 --- a/plutus-core/cost-model/data/builtinCostModelA.json +++ b/plutus-core/cost-model/data/builtinCostModelA.json @@ -1,1205 +1,423 @@ { - "addInteger": { - "cpu": { - "arguments": { - "intercept": 205665, - "slope": 812 - }, - "type": "max_size" - }, - "memory": { - "arguments": { - "intercept": 1, - "slope": 1 - }, - "type": "max_size" - } - }, - "appendByteString": { - "cpu": { - "arguments": { - "intercept": 1000, - "slope": 571 - }, - "type": "added_sizes" - }, - "memory": { - "arguments": { - "intercept": 0, - "slope": 1 - }, - "type": "added_sizes" - } - }, - "appendString": { - "cpu": { - "arguments": { - "intercept": 1000, - "slope": 24177 - }, - "type": "added_sizes" - }, - "memory": { - "arguments": { - "intercept": 4, - "slope": 1 - }, - "type": "added_sizes" - } - }, - "bData": { - "cpu": { - "arguments": 1000, - "type": "constant_cost" - }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } - }, - "blake2b_224": { - "cpu": { - "arguments": { - "intercept": 207616, - "slope": 8310 - }, - "type": "linear_in_x" - }, - "memory": { - "arguments": 4, - "type": "constant_cost" - } - }, - "blake2b_256": { - "cpu": { - "arguments": { - "intercept": 117366, - "slope": 10475 - }, - "type": "linear_in_x" - }, - "memory": { - "arguments": 4, - "type": "constant_cost" - } - }, - "bls12_381_G1_add": { - "cpu": { - "arguments": 962335, - "type": "constant_cost" - }, - "memory": { - "arguments": 18, - "type": "constant_cost" - } - }, - "bls12_381_G1_compress": { - "cpu": { - "arguments": 2780678, - "type": "constant_cost" - }, - "memory": { - "arguments": 6, - "type": "constant_cost" - } - }, - "bls12_381_G1_equal": { - "cpu": { - "arguments": 442008, - "type": "constant_cost" - }, - "memory": { - "arguments": 1, - "type": "constant_cost" - } - }, - "bls12_381_G1_hashToGroup": { - "cpu": { - "arguments": { - "intercept": 52538055, - "slope": 3756 - }, - "type": "linear_in_x" - }, - "memory": { - "arguments": 18, - "type": "constant_cost" - } - }, - "bls12_381_G1_neg": { - "cpu": { - "arguments": 267929, - "type": "constant_cost" - }, - "memory": { - "arguments": 18, - "type": "constant_cost" - } - }, - "bls12_381_G1_scalarMul": { - "cpu": { - "arguments": { - "intercept": 76433006, - "slope": 8868 - }, - "type": "linear_in_x" - }, - "memory": { - "arguments": 18, - "type": "constant_cost" - } - }, - "bls12_381_G1_multiScalarMul": { - "cpu": { - "arguments": { - "intercept": 321837444, - "slope": 25087669 - }, - "type": "linear_in_x" - }, - "memory": { - "arguments": 18, - "type": "constant_cost" - } - }, - "bls12_381_G1_uncompress": { - "cpu": { - "arguments": 52948122, - "type": "constant_cost" - }, - "memory": { - "arguments": 18, - "type": "constant_cost" - } - }, - "bls12_381_G2_add": { - "cpu": { - "arguments": 1995836, - "type": "constant_cost" - }, - "memory": { - "arguments": 36, - "type": "constant_cost" - } - }, - "bls12_381_G2_compress": { - "cpu": { - "arguments": 3227919, - "type": "constant_cost" - }, - "memory": { - "arguments": 12, - "type": "constant_cost" - } - }, - "bls12_381_G2_equal": { - "cpu": { - "arguments": 901022, - "type": "constant_cost" - }, - "memory": { - "arguments": 1, - "type": "constant_cost" - } - }, - "bls12_381_G2_hashToGroup": { - "cpu": { - "arguments": { - "intercept": 166917843, - "slope": 4307 - }, - "type": "linear_in_x" - }, - "memory": { - "arguments": 36, - "type": "constant_cost" - } - }, - "bls12_381_G2_neg": { - "cpu": { - "arguments": 284546, - "type": "constant_cost" - }, - "memory": { - "arguments": 36, - "type": "constant_cost" - } - }, - "bls12_381_G2_scalarMul": { - "cpu": { - "arguments": { - "intercept": 158221314, - "slope": 26549 - }, - "type": "linear_in_x" - }, - "memory": { - "arguments": 36, - "type": "constant_cost" - } - }, - "bls12_381_G2_multiScalarMul": { - "cpu": { - "arguments": { - "intercept": 617887431, - "slope": 67302824 - }, - "type": "linear_in_x" - }, - "memory": { - "arguments": 36, - "type": "constant_cost" - } - }, - "bls12_381_G2_uncompress": { - "cpu": { - "arguments": 74698472, - "type": "constant_cost" - }, - "memory": { - "arguments": 36, - "type": "constant_cost" - } - }, - "bls12_381_finalVerify": { - "cpu": { - "arguments": 333849714, - "type": "constant_cost" - }, - "memory": { - "arguments": 1, - "type": "constant_cost" - } - }, - "bls12_381_millerLoop": { - "cpu": { - "arguments": 254006273, - "type": "constant_cost" - }, - "memory": { - "arguments": 72, - "type": "constant_cost" - } - }, - "bls12_381_mulMlResult": { - "cpu": { - "arguments": 2174038, - "type": "constant_cost" - }, - "memory": { - "arguments": 72, - "type": "constant_cost" - } - }, - "byteStringToInteger": { - "cpu": { - "arguments": { - "c0": 1006041, - "c1": 43623, - "c2": 251 - }, - "type": "quadratic_in_y" - }, - "memory": { - "arguments": { - "intercept": 0, - "slope": 1 - }, - "type": "linear_in_y" - } - }, - "chooseData": { - "cpu": { - "arguments": 19537, - "type": "constant_cost" - }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } - }, - "chooseList": { - "cpu": { - "arguments": 175354, - "type": "constant_cost" - }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } - }, - "chooseUnit": { - "cpu": { - "arguments": 46417, - "type": "constant_cost" - }, - "memory": { - "arguments": 4, - "type": "constant_cost" - } - }, - "consByteString": { - "cpu": { - "arguments": { - "intercept": 221973, - "slope": 511 - }, - "type": "linear_in_y" - }, - "memory": { - "arguments": { - "intercept": 0, - "slope": 1 - }, - "type": "added_sizes" - } - }, - "constrData": { - "cpu": { - "arguments": 89141, - "type": "constant_cost" - }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } - }, - "decodeUtf8": { - "cpu": { - "arguments": { - "intercept": 497525, - "slope": 14068 - }, - "type": "linear_in_x" - }, - "memory": { - "arguments": { - "intercept": 4, - "slope": 2 - }, - "type": "linear_in_x" - } - }, - "divideInteger": { - "cpu": { - "arguments": { - "constant": 196500, - "model": { - "arguments": { - "intercept": 453240, - "slope": 220 - }, - "type": "multiplied_sizes" - } - }, - "type": "const_above_diagonal" - }, - "memory": { - "arguments": { - "intercept": 0, - "minimum": 1, - "slope": 1 - }, - "type": "subtracted_sizes" - } - }, - "encodeUtf8": { - "cpu": { - "arguments": { - "intercept": 1000, - "slope": 28662 - }, - "type": "linear_in_x" - }, - "memory": { - "arguments": { - "intercept": 4, - "slope": 2 - }, - "type": "linear_in_x" - } - }, - "equalsByteString": { - "cpu": { - "arguments": { - "constant": 245000, - "intercept": 216773, - "slope": 62 - }, - "type": "linear_on_diagonal" - }, - "memory": { - "arguments": 1, - "type": "constant_cost" - } - }, - "equalsData": { - "cpu": { - "arguments": { - "intercept": 1060367, - "slope": 12586 - }, - "type": "min_size" - }, - "memory": { - "arguments": 1, - "type": "constant_cost" - } - }, - "equalsInteger": { - "cpu": { - "arguments": { - "intercept": 208512, - "slope": 421 - }, - "type": "min_size" - }, - "memory": { - "arguments": 1, - "type": "constant_cost" - } - }, - "equalsString": { - "cpu": { - "arguments": { - "constant": 187000, - "intercept": 1000, - "slope": 52998 - }, - "type": "linear_on_diagonal" - }, - "memory": { - "arguments": 1, - "type": "constant_cost" - } - }, - "fstPair": { - "cpu": { - "arguments": 80436, - "type": "constant_cost" - }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } - }, - "headList": { - "cpu": { - "arguments": 43249, - "type": "constant_cost" - }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } - }, - "iData": { - "cpu": { - "arguments": 1000, - "type": "constant_cost" - }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } - }, - "ifThenElse": { - "cpu": { - "arguments": 80556, - "type": "constant_cost" - }, - "memory": { - "arguments": 1, - "type": "constant_cost" - } - }, - "indexByteString": { - "cpu": { - "arguments": 57667, - "type": "constant_cost" - }, - "memory": { - "arguments": 4, - "type": "constant_cost" - } - }, - "integerToByteString": { - "cpu": { - "arguments": { - "c0": 1293828, - "c1": 28716, - "c2": 63 - }, - "type": "quadratic_in_z" - }, - "memory": { - "arguments": { - "intercept": 0, - "slope": 1 - }, - "type": "literal_in_y_or_linear_in_z" - } - }, - "keccak_256": { - "cpu": { - "arguments": { - "intercept": 2261318, - "slope": 64571 - }, - "type": "linear_in_x" - }, - "memory": { - "arguments": 4, - "type": "constant_cost" - } - }, - "lengthOfByteString": { - "cpu": { - "arguments": 1000, - "type": "constant_cost" - }, - "memory": { - "arguments": 10, - "type": "constant_cost" - } - }, - "lessThanByteString": { - "cpu": { - "arguments": { - "intercept": 197145, - "slope": 156 - }, - "type": "min_size" - }, - "memory": { - "arguments": 1, - "type": "constant_cost" - } - }, - "lessThanEqualsByteString": { - "cpu": { - "arguments": { - "intercept": 197145, - "slope": 156 - }, - "type": "min_size" - }, - "memory": { - "arguments": 1, - "type": "constant_cost" - } - }, - "lessThanEqualsInteger": { - "cpu": { - "arguments": { - "intercept": 204924, - "slope": 473 - }, - "type": "min_size" - }, - "memory": { - "arguments": 1, - "type": "constant_cost" - } - }, - "lessThanInteger": { - "cpu": { - "arguments": { - "intercept": 208896, - "slope": 511 - }, - "type": "min_size" - }, - "memory": { - "arguments": 1, - "type": "constant_cost" - } - }, - "listData": { - "cpu": { - "arguments": 52467, - "type": "constant_cost" - }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } - }, - "mapData": { - "cpu": { - "arguments": 64832, - "type": "constant_cost" - }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } - }, - "mkCons": { - "cpu": { - "arguments": 65493, - "type": "constant_cost" - }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } - }, - "mkNilData": { - "cpu": { - "arguments": 22558, - "type": "constant_cost" - }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } - }, - "mkNilPairData": { - "cpu": { - "arguments": 16563, - "type": "constant_cost" - }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } - }, - "mkPairData": { - "cpu": { - "arguments": 76511, - "type": "constant_cost" - }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } - }, - "modInteger": { - "cpu": { - "arguments": { - "constant": 196500, - "model": { - "arguments": { - "intercept": 453240, - "slope": 220 - }, - "type": "multiplied_sizes" + "addInteger": { + "cpu": { + "arguments": { + "intercept": 205665, + "slope": 812 + }, + "type": "max_size" + }, + "memory": { + "arguments": { + "intercept": 1, + "slope": 1 + }, + "type": "max_size" } - }, - "type": "const_above_diagonal" - }, - "memory": { - "arguments": { - "intercept": 0, - "minimum": 1, - "slope": 1 - }, - "type": "subtracted_sizes" - } - }, - "multiplyInteger": { - "cpu": { - "arguments": { - "intercept": 69522, - "slope": 11687 - }, - "type": "added_sizes" - }, - "memory": { - "arguments": { - "intercept": 0, - "slope": 1 - }, - "type": "added_sizes" - } - }, - "nullList": { - "cpu": { - "arguments": 60091, - "type": "constant_cost" - }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } - }, - "indexArray": { - "cpu": { - "arguments": 194922, - "type": "constant_cost" - }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } - }, - "lengthOfArray": { - "cpu": { - "arguments": 198994, - "type": "constant_cost" }, - "memory": { - "arguments": 10, - "type": "constant_cost" - } - }, - "listToArray": { - "cpu": { - "arguments": { - "intercept": 307802, - "slope": 8496 - }, - "type": "linear_in_x" + "appendByteString": { + "cpu": { + "arguments": { + "intercept": 1000, + "slope": 571 + }, + "type": "added_sizes" + }, + "memory": { + "arguments": { + "intercept": 0, + "slope": 1 + }, + "type": "added_sizes" + } }, - "memory": { - "arguments": { - "intercept": 7, - "slope": 1 - }, - "type": "linear_in_x" - } - }, - "quotientInteger": { - "cpu": { - "arguments": { - "constant": 196500, - "model": { - "arguments": { - "intercept": 453240, - "slope": 220 - }, - "type": "multiplied_sizes" + "appendString": { + "cpu": { + "arguments": { + "intercept": 1000, + "slope": 24177 + }, + "type": "added_sizes" + }, + "memory": { + "arguments": { + "intercept": 4, + "slope": 1 + }, + "type": "added_sizes" } - }, - "type": "const_above_diagonal" }, - "memory": { - "arguments": { - "intercept": 0, - "minimum": 1, - "slope": 1 - }, - "type": "subtracted_sizes" - } - }, - "remainderInteger": { - "cpu": { - "arguments": { - "constant": 196500, - "model": { - "arguments": { - "intercept": 453240, - "slope": 220 - }, - "type": "multiplied_sizes" + "bData": { + "cpu": { + "arguments": 1000, + "type": "constant_cost" + }, + "memory": { + "arguments": 32, + "type": "constant_cost" } - }, - "type": "const_above_diagonal" }, - "memory": { - "arguments": { - "intercept": 0, - "minimum": 1, - "slope": 1 - }, - "type": "subtracted_sizes" - } - }, - "serialiseData": { - "cpu": { - "arguments": { - "intercept": 1159724, - "slope": 392670 - }, - "type": "linear_in_x" + "blake2b_224": { + "cpu": { + "arguments": { + "intercept": 207616, + "slope": 8310 + }, + "type": "linear_in_x" + }, + "memory": { + "arguments": 4, + "type": "constant_cost" + } }, - "memory": { - "arguments": { - "intercept": 0, - "slope": 2 - }, - "type": "linear_in_x" - } - }, - "sha2_256": { - "cpu": { - "arguments": { - "intercept": 806990, - "slope": 30482 - }, - "type": "linear_in_x" + "blake2b_256": { + "cpu": { + "arguments": { + "intercept": 117366, + "slope": 10475 + }, + "type": "linear_in_x" + }, + "memory": { + "arguments": 4, + "type": "constant_cost" + } }, - "memory": { - "arguments": 4, - "type": "constant_cost" - } - }, - "sha3_256": { - "cpu": { - "arguments": { - "intercept": 1927926, - "slope": 82523 - }, - "type": "linear_in_x" + "bls12_381_G1_add": { + "cpu": { + "arguments": 962335, + "type": "constant_cost" + }, + "memory": { + "arguments": 18, + "type": "constant_cost" + } }, - "memory": { - "arguments": 4, - "type": "constant_cost" - } - }, - "sliceByteString": { - "cpu": { - "arguments": { - "intercept": 265318, - "slope": 0 - }, - "type": "linear_in_z" + "bls12_381_G1_compress": { + "cpu": { + "arguments": 2780678, + "type": "constant_cost" + }, + "memory": { + "arguments": 6, + "type": "constant_cost" + } }, - "memory": { - "arguments": { - "intercept": 4, - "slope": 0 - }, - "type": "linear_in_z" - } - }, - "sndPair": { - "cpu": { - "arguments": 85931, - "type": "constant_cost" + "bls12_381_G1_equal": { + "cpu": { + "arguments": 442008, + "type": "constant_cost" + }, + "memory": { + "arguments": 1, + "type": "constant_cost" + } }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } - }, - "subtractInteger": { - "cpu": { - "arguments": { - "intercept": 205665, - "slope": 812 - }, - "type": "max_size" + "bls12_381_G1_hashToGroup": { + "cpu": { + "arguments": { + "intercept": 52538055, + "slope": 3756 + }, + "type": "linear_in_x" + }, + "memory": { + "arguments": 18, + "type": "constant_cost" + } }, - "memory": { - "arguments": { - "intercept": 1, - "slope": 1 - }, - "type": "max_size" - } - }, - "tailList": { - "cpu": { - "arguments": 41182, - "type": "constant_cost" + "bls12_381_G1_neg": { + "cpu": { + "arguments": 267929, + "type": "constant_cost" + }, + "memory": { + "arguments": 18, + "type": "constant_cost" + } }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } - }, - "trace": { - "cpu": { - "arguments": 212342, - "type": "constant_cost" + "bls12_381_G1_scalarMul": { + "cpu": { + "arguments": { + "intercept": 76433006, + "slope": 8868 + }, + "type": "linear_in_x" + }, + "memory": { + "arguments": 18, + "type": "constant_cost" + } }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } - }, - "unBData": { - "cpu": { - "arguments": 31220, - "type": "constant_cost" + "bls12_381_G1_multiScalarMul": { + "cpu": { + "arguments": { + "intercept": 321837444, + "slope": 25087669 + }, + "type": "linear_in_x" + }, + "memory": { + "arguments": 18, + "type": "constant_cost" + } }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } - }, - "unConstrData": { - "cpu": { - "arguments": 32696, - "type": "constant_cost" + "bls12_381_G1_uncompress": { + "cpu": { + "arguments": 52948122, + "type": "constant_cost" + }, + "memory": { + "arguments": 18, + "type": "constant_cost" + } }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } - }, - "unIData": { - "cpu": { - "arguments": 43357, - "type": "constant_cost" + "bls12_381_G2_add": { + "cpu": { + "arguments": 1995836, + "type": "constant_cost" + }, + "memory": { + "arguments": 36, + "type": "constant_cost" + } }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } - }, - "unListData": { - "cpu": { - "arguments": 32247, - "type": "constant_cost" + "bls12_381_G2_compress": { + "cpu": { + "arguments": 3227919, + "type": "constant_cost" + }, + "memory": { + "arguments": 12, + "type": "constant_cost" + } }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } - }, - "unMapData": { - "cpu": { - "arguments": 38314, - "type": "constant_cost" + "bls12_381_G2_equal": { + "cpu": { + "arguments": 901022, + "type": "constant_cost" + }, + "memory": { + "arguments": 1, + "type": "constant_cost" + } }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } - }, - "verifyEcdsaSecp256k1Signature": { - "cpu": { - "arguments": 35190005, - "type": "constant_cost" + "bls12_381_G2_hashToGroup": { + "cpu": { + "arguments": { + "intercept": 166917843, + "slope": 4307 + }, + "type": "linear_in_x" + }, + "memory": { + "arguments": 36, + "type": "constant_cost" + } }, - "memory": { - "arguments": 10, - "type": "constant_cost" - } - }, - "verifyEd25519Signature": { - "cpu": { - "arguments": { - "intercept": 57996947, - "slope": 18975 - }, - "type": "linear_in_z" + "bls12_381_G2_neg": { + "cpu": { + "arguments": 284546, + "type": "constant_cost" + }, + "memory": { + "arguments": 36, + "type": "constant_cost" + } }, - "memory": { - "arguments": 10, - "type": "constant_cost" - } - }, - "verifySchnorrSecp256k1Signature": { - "cpu": { - "arguments": { - "intercept": 39121781, - "slope": 32260 - }, - "type": "linear_in_y" + "bls12_381_G2_scalarMul": { + "cpu": { + "arguments": { + "intercept": 158221314, + "slope": 26549 + }, + "type": "linear_in_x" + }, + "memory": { + "arguments": 36, + "type": "constant_cost" + } }, - "memory": { - "arguments": 10, - "type": "constant_cost" - } - }, - "andByteString": { - "cpu": { - "arguments": { - "intercept": 100181, - "slope1": 726, - "slope2": 719 - }, - "type": "linear_in_y_and_z" + "bls12_381_G2_multiScalarMul": { + "cpu": { + "arguments": { + "intercept": 617887431, + "slope": 67302824 + }, + "type": "linear_in_x" + }, + "memory": { + "arguments": 36, + "type": "constant_cost" + } }, - "memory": { - "arguments": { - "intercept": 0, - "slope": 1 - }, - "type": "linear_in_max_yz" - } - }, - "orByteString": { - "cpu": { - "arguments": { - "intercept": 100181, - "slope1": 726, - "slope2": 719 - }, - "type": "linear_in_y_and_z" + "bls12_381_G2_uncompress": { + "cpu": { + "arguments": 74698472, + "type": "constant_cost" + }, + "memory": { + "arguments": 36, + "type": "constant_cost" + } }, - "memory": { - "arguments": { - "intercept": 0, - "slope": 1 - }, - "type": "linear_in_max_yz" - } - }, - "xorByteString": { - "cpu": { - "arguments": { - "intercept": 100181, - "slope1": 726, - "slope2": 719 - }, - "type": "linear_in_y_and_z" + "bls12_381_finalVerify": { + "cpu": { + "arguments": 333849714, + "type": "constant_cost" + }, + "memory": { + "arguments": 1, + "type": "constant_cost" + } }, - "memory": { - "arguments": { - "intercept": 0, - "slope": 1 - }, - "type": "linear_in_max_yz" - } - }, - "complementByteString": { - "cpu": { - "arguments": { - "intercept": 107878, - "slope": 680 - }, - "type": "linear_in_x" + "bls12_381_millerLoop": { + "cpu": { + "arguments": 254006273, + "type": "constant_cost" + }, + "memory": { + "arguments": 72, + "type": "constant_cost" + } }, - "memory": { - "arguments": { - "intercept": 0, - "slope": 1 - }, - "type": "linear_in_x" - } - }, - "readBit": { - "cpu": { - "arguments": 95336, - "type": "constant_cost" + "bls12_381_mulMlResult": { + "cpu": { + "arguments": 2174038, + "type": "constant_cost" + }, + "memory": { + "arguments": 72, + "type": "constant_cost" + } }, - "memory": { - "arguments": 1, - "type": "constant_cost" - } - }, - "writeBits": { - "cpu": { - "arguments": { - "intercept": 281145, - "slope": 18848 - }, - "type": "linear_in_y" + "byteStringToInteger": { + "cpu": { + "arguments": { + "c0": 1006041, + "c1": 43623, + "c2": 251 + }, + "type": "quadratic_in_y" + }, + "memory": { + "arguments": { + "intercept": 0, + "slope": 1 + }, + "type": "linear_in_y" + } }, - "memory": { - "arguments": { - "intercept": 0, - "slope": 1 - }, - "type": "linear_in_x" - } - }, - "replicateByte": { - "cpu": { - "arguments": { - "intercept": 180194, - "slope": 159 - }, - "type": "linear_in_x" + "chooseData": { + "cpu": { + "arguments": 19537, + "type": "constant_cost" + }, + "memory": { + "arguments": 32, + "type": "constant_cost" + } }, - "memory": { - "arguments": { - "intercept": 1, - "slope": 1 - }, - "type": "linear_in_x" - } - }, - "shiftByteString": { - "cpu": { - "arguments": { - "intercept": 158519, - "slope": 8942 - }, - "type": "linear_in_x" + "chooseList": { + "cpu": { + "arguments": 175354, + "type": "constant_cost" + }, + "memory": { + "arguments": 32, + "type": "constant_cost" + } }, - "memory": { - "arguments": { - "intercept": 0, - "slope": 1 - }, - "type": "linear_in_x" - } - }, - "rotateByteString": { - "cpu": { - "arguments": { - "intercept": 159378, - "slope": 8813 - }, - "type": "linear_in_x" + "chooseUnit": { + "cpu": { + "arguments": 46417, + "type": "constant_cost" + }, + "memory": { + "arguments": 4, + "type": "constant_cost" + } }, - "memory": { - "arguments": { - "intercept": 0, - "slope": 1 - }, - "type": "linear_in_x" - } - }, - "countSetBits": { - "cpu": { - "arguments": { - "intercept": 107490, - "slope": 3298 - }, - "type": "linear_in_x" + "consByteString": { + "cpu": { + "arguments": { + "intercept": 221973, + "slope": 511 + }, + "type": "linear_in_y" + }, + "memory": { + "arguments": { + "intercept": 0, + "slope": 1 + }, + "type": "added_sizes" + } }, - "memory": { - "arguments": 1, - "type": "constant_cost" - } - }, - "findFirstSetBit": { - "cpu": { - "arguments": { - "intercept": 106057, - "slope": 655 - }, - "type": "linear_in_x" + "constrData": { + "cpu": { + "arguments": 89141, + "type": "constant_cost" + }, + "memory": { + "arguments": 32, + "type": "constant_cost" + } }, - "memory": { - "arguments": 1, - "type": "constant_cost" - } - }, - "ripemd_160": { - "cpu": { - "arguments": { - "intercept": 1964219, - "slope": 24520 - }, - "type": "linear_in_x" + "decodeUtf8": { + "cpu": { + "arguments": { + "intercept": 497525, + "slope": 14068 + }, + "type": "linear_in_x" + }, + "memory": { + "arguments": { + "intercept": 4, + "slope": 2 + }, + "type": "linear_in_x" + } }, - "memory": { - "arguments": 3, - "type": "constant_cost" - } - }, - "expModInteger": { - "cpu": { - "arguments": { - "coefficient00": 607153, - "coefficient11": 231697, - "coefficient12": 53144 - }, - "type": "exp_mod_cost" + "divideInteger": { + "cpu": { + "arguments": { + "constant": 196500, + "model": { + "arguments": { + "intercept": 453240, + "slope": 220 + }, + "type": "multiplied_sizes" + } + }, + "type": "const_above_diagonal" + }, + "memory": { + "arguments": { + "intercept": 0, + "minimum": 1, + "slope": 1 + }, + "type": "subtracted_sizes" + } }, - "memory": { - "arguments": { - "intercept": 0, - "slope": 1 - }, - "type": "linear_in_z" - } - }, - "dropList": { - "cpu": { - "arguments": { - "intercept": 116711, - "slope": 1957 - }, - "type": "linear_in_x" + "encodeUtf8": { + "cpu": { + "arguments": { + "intercept": 1000, + "slope": 28662 + }, + "type": "linear_in_x" + }, + "memory": { + "arguments": { + "intercept": 4, + "slope": 2 + }, + "type": "linear_in_x" + } }, "memory": { "arguments": 4, @@ -1250,9 +468,806 @@ }, "type": "linear_in_x" }, - "memory": { - "arguments": 1, - "type": "constant_cost" + "fstPair": { + "cpu": { + "arguments": 80436, + "type": "constant_cost" + }, + "memory": { + "arguments": 32, + "type": "constant_cost" + } + }, + "headList": { + "cpu": { + "arguments": 43249, + "type": "constant_cost" + }, + "memory": { + "arguments": 32, + "type": "constant_cost" + } + }, + "iData": { + "cpu": { + "arguments": 1000, + "type": "constant_cost" + }, + "memory": { + "arguments": 32, + "type": "constant_cost" + } + }, + "ifThenElse": { + "cpu": { + "arguments": 80556, + "type": "constant_cost" + }, + "memory": { + "arguments": 1, + "type": "constant_cost" + } + }, + "indexByteString": { + "cpu": { + "arguments": 57667, + "type": "constant_cost" + }, + "memory": { + "arguments": 4, + "type": "constant_cost" + } + }, + "integerToByteString": { + "cpu": { + "arguments": { + "c0": 1293828, + "c1": 28716, + "c2": 63 + }, + "type": "quadratic_in_z" + }, + "memory": { + "arguments": { + "intercept": 0, + "slope": 1 + }, + "type": "literal_in_y_or_linear_in_z" + } + }, + "keccak_256": { + "cpu": { + "arguments": { + "intercept": 2261318, + "slope": 64571 + }, + "type": "linear_in_x" + }, + "memory": { + "arguments": 4, + "type": "constant_cost" + } + }, + "lengthOfByteString": { + "cpu": { + "arguments": 1000, + "type": "constant_cost" + }, + "memory": { + "arguments": 10, + "type": "constant_cost" + } + }, + "lessThanByteString": { + "cpu": { + "arguments": { + "intercept": 197145, + "slope": 156 + }, + "type": "min_size" + }, + "memory": { + "arguments": 1, + "type": "constant_cost" + } + }, + "lessThanEqualsByteString": { + "cpu": { + "arguments": { + "intercept": 197145, + "slope": 156 + }, + "type": "min_size" + }, + "memory": { + "arguments": 1, + "type": "constant_cost" + } + }, + "lessThanEqualsInteger": { + "cpu": { + "arguments": { + "intercept": 204924, + "slope": 473 + }, + "type": "min_size" + }, + "memory": { + "arguments": 1, + "type": "constant_cost" + } + }, + "lessThanInteger": { + "cpu": { + "arguments": { + "intercept": 208896, + "slope": 511 + }, + "type": "min_size" + }, + "memory": { + "arguments": 1, + "type": "constant_cost" + } + }, + "listData": { + "cpu": { + "arguments": 52467, + "type": "constant_cost" + }, + "memory": { + "arguments": 32, + "type": "constant_cost" + } + }, + "mapData": { + "cpu": { + "arguments": 64832, + "type": "constant_cost" + }, + "memory": { + "arguments": 32, + "type": "constant_cost" + } + }, + "mkCons": { + "cpu": { + "arguments": 65493, + "type": "constant_cost" + }, + "memory": { + "arguments": 32, + "type": "constant_cost" + } + }, + "mkNilData": { + "cpu": { + "arguments": 22558, + "type": "constant_cost" + }, + "memory": { + "arguments": 32, + "type": "constant_cost" + } + }, + "mkNilPairData": { + "cpu": { + "arguments": 16563, + "type": "constant_cost" + }, + "memory": { + "arguments": 32, + "type": "constant_cost" + } + }, + "mkPairData": { + "cpu": { + "arguments": 76511, + "type": "constant_cost" + }, + "memory": { + "arguments": 32, + "type": "constant_cost" + } + }, + "modInteger": { + "cpu": { + "arguments": { + "constant": 196500, + "model": { + "arguments": { + "intercept": 453240, + "slope": 220 + }, + "type": "multiplied_sizes" + } + }, + "type": "const_above_diagonal" + }, + "memory": { + "arguments": { + "intercept": 0, + "minimum": 1, + "slope": 1 + }, + "type": "subtracted_sizes" + } + }, + "multiplyInteger": { + "cpu": { + "arguments": { + "intercept": 69522, + "slope": 11687 + }, + "type": "added_sizes" + }, + "memory": { + "arguments": { + "intercept": 0, + "slope": 1 + }, + "type": "added_sizes" + } + }, + "nullList": { + "cpu": { + "arguments": 60091, + "type": "constant_cost" + }, + "memory": { + "arguments": 32, + "type": "constant_cost" + } + }, + "indexArray": { + "cpu": { + "arguments": 194922, + "type": "constant_cost" + }, + "memory": { + "arguments": 32, + "type": "constant_cost" + } + }, + "lengthOfArray": { + "cpu": { + "arguments": 198994, + "type": "constant_cost" + }, + "memory": { + "arguments": 10, + "type": "constant_cost" + } + }, + "listToArray": { + "cpu": { + "arguments": { + "intercept": 307802, + "slope": 8496 + }, + "type": "linear_in_x" + }, + "memory": { + "arguments": { + "intercept": 7, + "slope": 1 + }, + "type": "linear_in_x" + } + }, + "quotientInteger": { + "cpu": { + "arguments": { + "constant": 196500, + "model": { + "arguments": { + "intercept": 453240, + "slope": 220 + }, + "type": "multiplied_sizes" + } + }, + "type": "const_above_diagonal" + }, + "memory": { + "arguments": { + "intercept": 0, + "minimum": 1, + "slope": 1 + }, + "type": "subtracted_sizes" + } + }, + "remainderInteger": { + "cpu": { + "arguments": { + "constant": 196500, + "model": { + "arguments": { + "intercept": 453240, + "slope": 220 + }, + "type": "multiplied_sizes" + } + }, + "type": "const_above_diagonal" + }, + "memory": { + "arguments": { + "intercept": 0, + "minimum": 1, + "slope": 1 + }, + "type": "subtracted_sizes" + } + }, + "serialiseData": { + "cpu": { + "arguments": { + "intercept": 1159724, + "slope": 392670 + }, + "type": "linear_in_x" + }, + "memory": { + "arguments": { + "intercept": 0, + "slope": 2 + }, + "type": "linear_in_x" + } + }, + "sha2_256": { + "cpu": { + "arguments": { + "intercept": 806990, + "slope": 30482 + }, + "type": "linear_in_x" + }, + "memory": { + "arguments": 4, + "type": "constant_cost" + } + }, + "sha3_256": { + "cpu": { + "arguments": { + "intercept": 1927926, + "slope": 82523 + }, + "type": "linear_in_x" + }, + "memory": { + "arguments": 4, + "type": "constant_cost" + } + }, + "sliceByteString": { + "cpu": { + "arguments": { + "intercept": 265318, + "slope": 0 + }, + "type": "linear_in_z" + }, + "memory": { + "arguments": { + "intercept": 4, + "slope": 0 + }, + "type": "linear_in_z" + } + }, + "sndPair": { + "cpu": { + "arguments": 85931, + "type": "constant_cost" + }, + "memory": { + "arguments": 32, + "type": "constant_cost" + } + }, + "subtractInteger": { + "cpu": { + "arguments": { + "intercept": 205665, + "slope": 812 + }, + "type": "max_size" + }, + "memory": { + "arguments": { + "intercept": 1, + "slope": 1 + }, + "type": "max_size" + } + }, + "tailList": { + "cpu": { + "arguments": 41182, + "type": "constant_cost" + }, + "memory": { + "arguments": 32, + "type": "constant_cost" + } + }, + "trace": { + "cpu": { + "arguments": 212342, + "type": "constant_cost" + }, + "memory": { + "arguments": 32, + "type": "constant_cost" + } + }, + "unBData": { + "cpu": { + "arguments": 31220, + "type": "constant_cost" + }, + "memory": { + "arguments": 32, + "type": "constant_cost" + } + }, + "unConstrData": { + "cpu": { + "arguments": 32696, + "type": "constant_cost" + }, + "memory": { + "arguments": 32, + "type": "constant_cost" + } + }, + "unIData": { + "cpu": { + "arguments": 43357, + "type": "constant_cost" + }, + "memory": { + "arguments": 32, + "type": "constant_cost" + } + }, + "unListData": { + "cpu": { + "arguments": 32247, + "type": "constant_cost" + }, + "memory": { + "arguments": 32, + "type": "constant_cost" + } + }, + "unMapData": { + "cpu": { + "arguments": 38314, + "type": "constant_cost" + }, + "memory": { + "arguments": 32, + "type": "constant_cost" + } + }, + "verifyEcdsaSecp256k1Signature": { + "cpu": { + "arguments": 35190005, + "type": "constant_cost" + }, + "memory": { + "arguments": 10, + "type": "constant_cost" + } + }, + "verifyEd25519Signature": { + "cpu": { + "arguments": { + "intercept": 57996947, + "slope": 18975 + }, + "type": "linear_in_z" + }, + "memory": { + "arguments": 10, + "type": "constant_cost" + } + }, + "verifySchnorrSecp256k1Signature": { + "cpu": { + "arguments": { + "intercept": 39121781, + "slope": 32260 + }, + "type": "linear_in_y" + }, + "memory": { + "arguments": 10, + "type": "constant_cost" + } + }, + "andByteString": { + "cpu": { + "arguments": { + "intercept": 100181, + "slope1": 726, + "slope2": 719 + }, + "type": "linear_in_y_and_z" + }, + "memory": { + "arguments": { + "intercept": 0, + "slope": 1 + }, + "type": "linear_in_max_yz" + } + }, + "orByteString": { + "cpu": { + "arguments": { + "intercept": 100181, + "slope1": 726, + "slope2": 719 + }, + "type": "linear_in_y_and_z" + }, + "memory": { + "arguments": { + "intercept": 0, + "slope": 1 + }, + "type": "linear_in_max_yz" + } + }, + "xorByteString": { + "cpu": { + "arguments": { + "intercept": 100181, + "slope1": 726, + "slope2": 719 + }, + "type": "linear_in_y_and_z" + }, + "memory": { + "arguments": { + "intercept": 0, + "slope": 1 + }, + "type": "linear_in_max_yz" + } + }, + "complementByteString": { + "cpu": { + "arguments": { + "intercept": 107878, + "slope": 680 + }, + "type": "linear_in_x" + }, + "memory": { + "arguments": { + "intercept": 0, + "slope": 1 + }, + "type": "linear_in_x" + } + }, + "readBit": { + "cpu": { + "arguments": 95336, + "type": "constant_cost" + }, + "memory": { + "arguments": 1, + "type": "constant_cost" + } + }, + "writeBits": { + "cpu": { + "arguments": { + "intercept": 281145, + "slope": 18848 + }, + "type": "linear_in_y" + }, + "memory": { + "arguments": { + "intercept": 0, + "slope": 1 + }, + "type": "linear_in_x" + } + }, + "replicateByte": { + "cpu": { + "arguments": { + "intercept": 180194, + "slope": 159 + }, + "type": "linear_in_x" + }, + "memory": { + "arguments": { + "intercept": 1, + "slope": 1 + }, + "type": "linear_in_x" + } + }, + "shiftByteString": { + "cpu": { + "arguments": { + "intercept": 158519, + "slope": 8942 + }, + "type": "linear_in_x" + }, + "memory": { + "arguments": { + "intercept": 0, + "slope": 1 + }, + "type": "linear_in_x" + } + }, + "rotateByteString": { + "cpu": { + "arguments": { + "intercept": 159378, + "slope": 8813 + }, + "type": "linear_in_x" + }, + "memory": { + "arguments": { + "intercept": 0, + "slope": 1 + }, + "type": "linear_in_x" + } + }, + "countSetBits": { + "cpu": { + "arguments": { + "intercept": 107490, + "slope": 3298 + }, + "type": "linear_in_x" + }, + "memory": { + "arguments": 1, + "type": "constant_cost" + } + }, + "findFirstSetBit": { + "cpu": { + "arguments": { + "intercept": 106057, + "slope": 655 + }, + "type": "linear_in_x" + }, + "memory": { + "arguments": 1, + "type": "constant_cost" + } + }, + "ripemd_160": { + "cpu": { + "arguments": { + "intercept": 1964219, + "slope": 24520 + }, + "type": "linear_in_x" + }, + "memory": { + "arguments": 3, + "type": "constant_cost" + } + }, + "expModInteger": { + "cpu": { + "arguments": { + "coefficient00": 607153, + "coefficient11": 231697, + "coefficient12": 53144 + }, + "type": "exp_mod_cost" + }, + "memory": { + "arguments": { + "intercept": 0, + "slope": 1 + }, + "type": "linear_in_z" + } + }, + "dropList": { + "cpu": { + "arguments": { + "intercept": 116711, + "slope": 1957 + }, + "type": "linear_in_x" + }, + "memory": { + "arguments": 4, + "type": "constant_cost" + } + }, + "lookupCoin": { + "cpu": { + "arguments": { + "intercept": 272043, + "slope": 16 + }, + "type": "linear_in_z" + }, + "memory": { + "arguments": 1, + "type": "constant_cost" + } + }, + "valueContains": { + "cpu": { + "arguments": { + "intercept": 6684283, + "slope": 1000 + }, + "type": "added_sizes" + }, + "memory": { + "arguments": 1, + "type": "constant_cost" + } + }, + "valueData": { + "cpu": { + "arguments": 167190, + "type": "constant_cost" + }, + "memory": { + "arguments": 1, + "type": "constant_cost" + } + }, + "unValueData": { + "cpu": { + "arguments": { + "intercept": 1000, + "slope": 19835 + }, + "type": "linear_in_x" + }, + "memory": { + "arguments": 1, + "type": "constant_cost" + } + } + , "insertCoin": { + "cpu": { + "arguments": 1000, + "type": "constant_cost" + }, + "memory": { + "arguments": 10, + "type": "constant_cost" + } + } + , "unionValue": { + "cpu": { + "arguments": 1000, + "type": "constant_cost" + }, + "memory": { + "arguments": 10, + "type": "constant_cost" + } } - } } diff --git a/plutus-core/cost-model/data/builtinCostModelB.json b/plutus-core/cost-model/data/builtinCostModelB.json index 5adaf9d9253..c96288929fb 100644 --- a/plutus-core/cost-model/data/builtinCostModelB.json +++ b/plutus-core/cost-model/data/builtinCostModelB.json @@ -1254,5 +1254,25 @@ "arguments": 1, "type": "constant_cost" } + }, + "insertCoin": { + "cpu": { + "arguments": 1000, + "type": "constant_cost" + }, + "memory": { + "arguments": 10, + "type": "constant_cost" + } + }, + "unionValue": { + "cpu": { + "arguments": 1000, + "type": "constant_cost" + }, + "memory": { + "arguments": 10, + "type": "constant_cost" + } } } diff --git a/plutus-core/cost-model/data/builtinCostModelC.json b/plutus-core/cost-model/data/builtinCostModelC.json index 29504a4f236..b6e9991e2b1 100644 --- a/plutus-core/cost-model/data/builtinCostModelC.json +++ b/plutus-core/cost-model/data/builtinCostModelC.json @@ -1272,5 +1272,25 @@ "arguments": 1, "type": "constant_cost" } + }, + "insertCoin": { + "cpu": { + "arguments": 1000, + "type": "constant_cost" + }, + "memory": { + "arguments": 10, + "type": "constant_cost" + } + }, + "unionValue": { + "cpu": { + "arguments": 1000, + "type": "constant_cost" + }, + "memory": { + "arguments": 10, + "type": "constant_cost" + } } } diff --git a/plutus-core/plutus-core/src/PlutusCore/Default/Builtins.hs b/plutus-core/plutus-core/src/PlutusCore/Default/Builtins.hs index 26a3416762f..e08a8714d6f 100644 --- a/plutus-core/plutus-core/src/PlutusCore/Default/Builtins.hs +++ b/plutus-core/plutus-core/src/PlutusCore/Default/Builtins.hs @@ -2053,7 +2053,7 @@ instance uni ~ DefaultUni => ToBuiltinMeaning uni DefaultFun where {-# INLINE insertCoinDenotation #-} in makeBuiltinMeaning insertCoinDenotation - (runCostingFunFourArguments . unimplementedCostingFun) + (runCostingFunFourArguments . paramInsertCoin) toBuiltinMeaning _semvar LookupCoin = let lookupCoinDenotation :: ByteString -> ByteString -> LogValueOuterOrMaxInner -> Integer @@ -2069,7 +2069,7 @@ instance uni ~ DefaultUni => ToBuiltinMeaning uni DefaultFun where {-# INLINE unionValueDenotation #-} in makeBuiltinMeaning unionValueDenotation - (runCostingFunTwoArguments . unimplementedCostingFun) + (runCostingFunTwoArguments . paramUnionValue) toBuiltinMeaning _semvar ValueContains = let valueContainsDenotation :: LogValueOuterOrMaxInner -> ValueTotalSize -> BuiltinResult Bool diff --git a/plutus-core/plutus-core/src/PlutusCore/Evaluation/Machine/BuiltinCostModel.hs b/plutus-core/plutus-core/src/PlutusCore/Evaluation/Machine/BuiltinCostModel.hs index 35ff0ee0e74..87cd1809d53 100644 --- a/plutus-core/plutus-core/src/PlutusCore/Evaluation/Machine/BuiltinCostModel.hs +++ b/plutus-core/plutus-core/src/PlutusCore/Evaluation/Machine/BuiltinCostModel.hs @@ -198,6 +198,8 @@ data BuiltinCostModelBase f = , paramValueContains :: f ModelTwoArguments , paramValueData :: f ModelOneArgument , paramUnValueData :: f ModelOneArgument + , paramInsertCoin :: f ModelFourArguments + , paramUnionValue :: f ModelTwoArguments } deriving stock (Generic) deriving anyclass (FunctorB, TraversableB, ConstraintsB) diff --git a/plutus-core/plutus-core/src/PlutusCore/Evaluation/Machine/ExBudgetingDefaults.hs b/plutus-core/plutus-core/src/PlutusCore/Evaluation/Machine/ExBudgetingDefaults.hs index a5a1a2e97c9..626457c2b40 100644 --- a/plutus-core/plutus-core/src/PlutusCore/Evaluation/Machine/ExBudgetingDefaults.hs +++ b/plutus-core/plutus-core/src/PlutusCore/Evaluation/Machine/ExBudgetingDefaults.hs @@ -238,6 +238,9 @@ unitCostTwoArguments = CostingFun (ModelTwoArgumentsConstantCost 1) (ModelTwo unitCostThreeArguments :: CostingFun ModelThreeArguments unitCostThreeArguments = CostingFun (ModelThreeArgumentsConstantCost 1) (ModelThreeArgumentsConstantCost 0) +unitCostFourArguments :: CostingFun ModelFourArguments +unitCostFourArguments = CostingFun (ModelFourArgumentsConstantCost 1) (ModelFourArgumentsConstantCost 0) + unitCostSixArguments :: CostingFun ModelSixArguments unitCostSixArguments = CostingFun (ModelSixArgumentsConstantCost 1) (ModelSixArgumentsConstantCost 0) @@ -360,6 +363,8 @@ unitCostBuiltinCostModel = BuiltinCostModelBase , paramValueContains = unitCostTwoArguments , paramValueData = unitCostOneArgument , paramUnValueData = unitCostOneArgument + , paramInsertCoin = unitCostFourArguments + , paramUnionValue = unitCostTwoArguments } unitCekParameters :: Typeable ann => MachineParameters CekMachineCosts DefaultFun (CekValue DefaultUni DefaultFun ann) From a018fc2af8c870e26df6b1615895e9521a6b5f2e Mon Sep 17 00:00:00 2001 From: Ana Pantilie Date: Thu, 9 Oct 2025 19:07:10 +0300 Subject: [PATCH 17/17] WIP: add benchmarking for insertCoin --- .../budgeting-bench/Benchmarks/Values.hs | 70 +- .../cost-model/budgeting-bench/Common.hs | 33 + .../cost-model/data/builtinCostModelA.json | 2367 +++++++++-------- 3 files changed, 1280 insertions(+), 1190 deletions(-) diff --git a/plutus-core/cost-model/budgeting-bench/Benchmarks/Values.hs b/plutus-core/cost-model/budgeting-bench/Benchmarks/Values.hs index 3abd3a2548f..d77e058bcfa 100644 --- a/plutus-core/cost-model/budgeting-bench/Benchmarks/Values.hs +++ b/plutus-core/cost-model/budgeting-bench/Benchmarks/Values.hs @@ -10,9 +10,9 @@ import Common import Control.Monad (replicateM) import Criterion.Main (Benchmark) import Data.ByteString (ByteString) -import PlutusCore (DefaultFun (LookupCoin, UnValueData, ValueContains, ValueData)) +import PlutusCore (DefaultFun (InsertCoin, LookupCoin, UnValueData, ValueContains, ValueData)) import PlutusCore.Evaluation.Machine.ExMemoryUsage (LogValueOuterOrMaxInner (..), - ValueTotalSize (..)) + ValueOuterOrMaxInner (..), ValueTotalSize (..)) import PlutusCore.Value (K, Value) import PlutusCore.Value qualified as Value import System.Random.Stateful (StatefulGen, StdGen, runStateGen_, uniformByteStringM, uniformRM) @@ -205,6 +205,58 @@ unValueDataBenchmark :: StdGen -> Benchmark unValueDataBenchmark gen = createOneTermBuiltinBench UnValueData [] (Value.valueData <$> generateTestValues gen) +-- insertCoin :: ByteString -> ByteString -> Integer -> Value -> Value +---------------------------------------------------------------------------------------------------- +-- InsertCoin -------------------------------------------------------------------------------------- + +insertCoinBenchmark :: StdGen -> Benchmark +insertCoinBenchmark gen = + createFourTermBuiltinBenchElementwiseWithWrappers + (id, id, id, ValueOuterOrMaxInner) -- Wrap Value argument to report outer/max inner size + InsertCoin -- the builtin fun + [] -- no type arguments needed (monomorphic builtin) + (insertCoinArgs gen) -- the argument combos to generate benchmarks for + +insertCoinArgs :: StdGen -> [(ByteString, ByteString, Integer, Value)] +insertCoinArgs gen = runStateGen_ gen $ \(g :: g) -> do + -- Add search keys to common test values + let testValues = generateTestValues gen + commonWithKeys <- mapM (withSearchKeys g . pure) testValues + + -- Additional tests specific to insertCoin + let valueSizes = [(100, 10), (500, 20), (1_000, 50), (2_000, 100)] + additionalTests <- + sequence $ + concat + [ -- Value size tests (number of policies × tokens per policy) + [ generateInsertTest g numPolicies tokensPerPolicy + | (numPolicies, tokensPerPolicy) <- valueSizes + ] + , -- Budget-constrained tests (at 30KB limit) + [generateBudgetTest g 30_000] + , -- Additional random tests for parameter spread + replicate 50 (generateRandomInsertTest g) + ] + + pure $ commonWithKeys ++ additionalTests + +-- | Generate insert test with specified parameters +generateInsertTest + :: (StatefulGen g m) + => g + -> Int -- Number of policies + -> Int -- Tokens per policy + -> m (ByteString, ByteString, Value) +generateInsertTest g numPolicies tokensPerPolicy = + withSearchKeys g (generateConstrainedValue numPolicies tokensPerPolicy g) + +-- | Generate random insert test with varied parameters for better spread +generateRandomInsertTest :: (StatefulGen g m) => g -> m (ByteString, ByteString, Value) +generateRandomInsertTest g = do + numPolicies <- uniformRM (1, 2_000) g + tokensPerPolicy <- uniformRM (1, 1_000) g + withSearchKeys g (generateConstrainedValue numPolicies tokensPerPolicy g) + ---------------------------------------------------------------------------------------------------- -- Value Generators -------------------------------------------------------------------------------- @@ -244,15 +296,10 @@ generateConstrainedValue numPolicies tokensPerPolicy g = do policyIds <- replicateM numPolicies (generateKey g) tokenNames <- replicateM tokensPerPolicy (generateKey g) - -- Generate positive quantities (1 to 1000000) - let quantity :: Int -> Int -> Integer - quantity policyIndex tokenIndex = - fromIntegral (1 + (policyIndex * 1_000 + tokenIndex) `mod` 1_000_000) - - nestedMap :: [(K, [(K, Integer)])] + let nestedMap :: [(K, [(K, Integer)])] nestedMap = [ ( policyId - , [ (tokenName, quantity policyIndex tokenIndex) + , [ (tokenName, genQuantity policyIndex tokenIndex) | (tokenIndex, tokenName) <- zip [0 ..] tokenNames ] ) @@ -295,3 +342,8 @@ generateKey g = do -- | Generate random key as ByteString (for lookup arguments) generateKeyBS :: (StatefulGen g m) => g -> m ByteString generateKeyBS = uniformByteStringM Value.maxKeyLen + +-- | Generate positive quantities (1 to 1000000) +genQuantity :: Int -> Int -> Integer +genQuantity policyIndex tokenIndex = + fromIntegral (1 + (policyIndex * 1_000 + tokenIndex) `mod` 1_000_000) diff --git a/plutus-core/cost-model/budgeting-bench/Common.hs b/plutus-core/cost-model/budgeting-bench/Common.hs index 1812fe78731..92766abff5d 100644 --- a/plutus-core/cost-model/budgeting-bench/Common.hs +++ b/plutus-core/cost-model/budgeting-bench/Common.hs @@ -431,3 +431,36 @@ createThreeTermBuiltinBenchWithWrappers (wrapX, wrapY, wrapZ) fun tys xs ys zs = [mkBM x y z | z <- zs] | y <- ys] | x <- xs] where mkBM x y z = benchDefault (showMemoryUsage (wrapZ z)) $ mkApp3 fun tys x y z +{- See Note [Adjusting the memory usage of arguments of costing benchmarks]. -} +createFourTermBuiltinBenchElementwiseWithWrappers + :: ( fun ~ DefaultFun + , uni ~ DefaultUni + , uni `HasTermLevel` a + , uni `HasTermLevel` b + , uni `HasTermLevel` c + , uni `HasTermLevel` d + , ExMemoryUsage a' + , ExMemoryUsage b' + , ExMemoryUsage c' + , ExMemoryUsage d' + , NFData a + , NFData b + , NFData c + , NFData d + ) + => (a -> a', b -> b', c -> c', d -> d') + -> fun + -> [Type tyname uni ()] + -> [(a,b,c,d)] + -> Benchmark +createFourTermBuiltinBenchElementwiseWithWrappers (wrapW, wrapX, wrapY, wrapZ) fun tys inputs = + bgroup (show fun) $ + fmap + (\(w, x, y, z) -> + bgroup (showMemoryUsage $ wrapW w) + [bgroup (showMemoryUsage $ wrapX x) + [bgroup (showMemoryUsage $ wrapY y) [mkBM w x y z]] + ] + ) + inputs + where mkBM w x y z = benchDefault (showMemoryUsage $ wrapZ z) $ mkApp4 fun tys w x y z diff --git a/plutus-core/cost-model/data/builtinCostModelA.json b/plutus-core/cost-model/data/builtinCostModelA.json index 66c908673b8..3f7d19752b1 100644 --- a/plutus-core/cost-model/data/builtinCostModelA.json +++ b/plutus-core/cost-model/data/builtinCostModelA.json @@ -1,423 +1,1205 @@ { - "addInteger": { - "cpu": { - "arguments": { - "intercept": 205665, - "slope": 812 - }, - "type": "max_size" - }, - "memory": { - "arguments": { - "intercept": 1, - "slope": 1 - }, - "type": "max_size" + "addInteger": { + "cpu": { + "arguments": { + "intercept": 205665, + "slope": 812 + }, + "type": "max_size" + }, + "memory": { + "arguments": { + "intercept": 1, + "slope": 1 + }, + "type": "max_size" + } + }, + "appendByteString": { + "cpu": { + "arguments": { + "intercept": 1000, + "slope": 571 + }, + "type": "added_sizes" + }, + "memory": { + "arguments": { + "intercept": 0, + "slope": 1 + }, + "type": "added_sizes" + } + }, + "appendString": { + "cpu": { + "arguments": { + "intercept": 1000, + "slope": 24177 + }, + "type": "added_sizes" + }, + "memory": { + "arguments": { + "intercept": 4, + "slope": 1 + }, + "type": "added_sizes" + } + }, + "bData": { + "cpu": { + "arguments": 1000, + "type": "constant_cost" + }, + "memory": { + "arguments": 32, + "type": "constant_cost" + } + }, + "blake2b_224": { + "cpu": { + "arguments": { + "intercept": 207616, + "slope": 8310 + }, + "type": "linear_in_x" + }, + "memory": { + "arguments": 4, + "type": "constant_cost" + } + }, + "blake2b_256": { + "cpu": { + "arguments": { + "intercept": 117366, + "slope": 10475 + }, + "type": "linear_in_x" + }, + "memory": { + "arguments": 4, + "type": "constant_cost" + } + }, + "bls12_381_G1_add": { + "cpu": { + "arguments": 962335, + "type": "constant_cost" + }, + "memory": { + "arguments": 18, + "type": "constant_cost" + } + }, + "bls12_381_G1_compress": { + "cpu": { + "arguments": 2780678, + "type": "constant_cost" + }, + "memory": { + "arguments": 6, + "type": "constant_cost" + } + }, + "bls12_381_G1_equal": { + "cpu": { + "arguments": 442008, + "type": "constant_cost" + }, + "memory": { + "arguments": 1, + "type": "constant_cost" + } + }, + "bls12_381_G1_hashToGroup": { + "cpu": { + "arguments": { + "intercept": 52538055, + "slope": 3756 + }, + "type": "linear_in_x" + }, + "memory": { + "arguments": 18, + "type": "constant_cost" + } + }, + "bls12_381_G1_neg": { + "cpu": { + "arguments": 267929, + "type": "constant_cost" + }, + "memory": { + "arguments": 18, + "type": "constant_cost" + } + }, + "bls12_381_G1_scalarMul": { + "cpu": { + "arguments": { + "intercept": 76433006, + "slope": 8868 + }, + "type": "linear_in_x" + }, + "memory": { + "arguments": 18, + "type": "constant_cost" + } + }, + "bls12_381_G1_multiScalarMul": { + "cpu": { + "arguments": { + "intercept": 321837444, + "slope": 25087669 + }, + "type": "linear_in_x" + }, + "memory": { + "arguments": 18, + "type": "constant_cost" + } + }, + "bls12_381_G1_uncompress": { + "cpu": { + "arguments": 52948122, + "type": "constant_cost" + }, + "memory": { + "arguments": 18, + "type": "constant_cost" + } + }, + "bls12_381_G2_add": { + "cpu": { + "arguments": 1995836, + "type": "constant_cost" + }, + "memory": { + "arguments": 36, + "type": "constant_cost" + } + }, + "bls12_381_G2_compress": { + "cpu": { + "arguments": 3227919, + "type": "constant_cost" + }, + "memory": { + "arguments": 12, + "type": "constant_cost" + } + }, + "bls12_381_G2_equal": { + "cpu": { + "arguments": 901022, + "type": "constant_cost" + }, + "memory": { + "arguments": 1, + "type": "constant_cost" + } + }, + "bls12_381_G2_hashToGroup": { + "cpu": { + "arguments": { + "intercept": 166917843, + "slope": 4307 + }, + "type": "linear_in_x" + }, + "memory": { + "arguments": 36, + "type": "constant_cost" + } + }, + "bls12_381_G2_neg": { + "cpu": { + "arguments": 284546, + "type": "constant_cost" + }, + "memory": { + "arguments": 36, + "type": "constant_cost" + } + }, + "bls12_381_G2_scalarMul": { + "cpu": { + "arguments": { + "intercept": 158221314, + "slope": 26549 + }, + "type": "linear_in_x" + }, + "memory": { + "arguments": 36, + "type": "constant_cost" + } + }, + "bls12_381_G2_multiScalarMul": { + "cpu": { + "arguments": { + "intercept": 617887431, + "slope": 67302824 + }, + "type": "linear_in_x" + }, + "memory": { + "arguments": 36, + "type": "constant_cost" + } + }, + "bls12_381_G2_uncompress": { + "cpu": { + "arguments": 74698472, + "type": "constant_cost" + }, + "memory": { + "arguments": 36, + "type": "constant_cost" + } + }, + "bls12_381_finalVerify": { + "cpu": { + "arguments": 333849714, + "type": "constant_cost" + }, + "memory": { + "arguments": 1, + "type": "constant_cost" + } + }, + "bls12_381_millerLoop": { + "cpu": { + "arguments": 254006273, + "type": "constant_cost" + }, + "memory": { + "arguments": 72, + "type": "constant_cost" + } + }, + "bls12_381_mulMlResult": { + "cpu": { + "arguments": 2174038, + "type": "constant_cost" + }, + "memory": { + "arguments": 72, + "type": "constant_cost" + } + }, + "byteStringToInteger": { + "cpu": { + "arguments": { + "c0": 1006041, + "c1": 43623, + "c2": 251 + }, + "type": "quadratic_in_y" + }, + "memory": { + "arguments": { + "intercept": 0, + "slope": 1 + }, + "type": "linear_in_y" + } + }, + "chooseData": { + "cpu": { + "arguments": 19537, + "type": "constant_cost" + }, + "memory": { + "arguments": 32, + "type": "constant_cost" + } + }, + "chooseList": { + "cpu": { + "arguments": 175354, + "type": "constant_cost" + }, + "memory": { + "arguments": 32, + "type": "constant_cost" + } + }, + "chooseUnit": { + "cpu": { + "arguments": 46417, + "type": "constant_cost" + }, + "memory": { + "arguments": 4, + "type": "constant_cost" + } + }, + "consByteString": { + "cpu": { + "arguments": { + "intercept": 221973, + "slope": 511 + }, + "type": "linear_in_y" + }, + "memory": { + "arguments": { + "intercept": 0, + "slope": 1 + }, + "type": "added_sizes" + } + }, + "constrData": { + "cpu": { + "arguments": 89141, + "type": "constant_cost" + }, + "memory": { + "arguments": 32, + "type": "constant_cost" + } + }, + "decodeUtf8": { + "cpu": { + "arguments": { + "intercept": 497525, + "slope": 14068 + }, + "type": "linear_in_x" + }, + "memory": { + "arguments": { + "intercept": 4, + "slope": 2 + }, + "type": "linear_in_x" + } + }, + "divideInteger": { + "cpu": { + "arguments": { + "constant": 196500, + "model": { + "arguments": { + "intercept": 453240, + "slope": 220 + }, + "type": "multiplied_sizes" } + }, + "type": "const_above_diagonal" + }, + "memory": { + "arguments": { + "intercept": 0, + "minimum": 1, + "slope": 1 + }, + "type": "subtracted_sizes" + } + }, + "encodeUtf8": { + "cpu": { + "arguments": { + "intercept": 1000, + "slope": 28662 + }, + "type": "linear_in_x" + }, + "memory": { + "arguments": { + "intercept": 4, + "slope": 2 + }, + "type": "linear_in_x" + } + }, + "equalsByteString": { + "cpu": { + "arguments": { + "constant": 245000, + "intercept": 216773, + "slope": 62 + }, + "type": "linear_on_diagonal" + }, + "memory": { + "arguments": 1, + "type": "constant_cost" + } + }, + "equalsData": { + "cpu": { + "arguments": { + "intercept": 1060367, + "slope": 12586 + }, + "type": "min_size" + }, + "memory": { + "arguments": 1, + "type": "constant_cost" + } + }, + "equalsInteger": { + "cpu": { + "arguments": { + "intercept": 208512, + "slope": 421 + }, + "type": "min_size" + }, + "memory": { + "arguments": 1, + "type": "constant_cost" + } + }, + "equalsString": { + "cpu": { + "arguments": { + "constant": 187000, + "intercept": 1000, + "slope": 52998 + }, + "type": "linear_on_diagonal" + }, + "memory": { + "arguments": 1, + "type": "constant_cost" + } + }, + "fstPair": { + "cpu": { + "arguments": 80436, + "type": "constant_cost" + }, + "memory": { + "arguments": 32, + "type": "constant_cost" + } + }, + "headList": { + "cpu": { + "arguments": 43249, + "type": "constant_cost" + }, + "memory": { + "arguments": 32, + "type": "constant_cost" + } + }, + "iData": { + "cpu": { + "arguments": 1000, + "type": "constant_cost" + }, + "memory": { + "arguments": 32, + "type": "constant_cost" + } + }, + "ifThenElse": { + "cpu": { + "arguments": 80556, + "type": "constant_cost" + }, + "memory": { + "arguments": 1, + "type": "constant_cost" + } + }, + "indexByteString": { + "cpu": { + "arguments": 57667, + "type": "constant_cost" + }, + "memory": { + "arguments": 4, + "type": "constant_cost" + } + }, + "integerToByteString": { + "cpu": { + "arguments": { + "c0": 1293828, + "c1": 28716, + "c2": 63 + }, + "type": "quadratic_in_z" + }, + "memory": { + "arguments": { + "intercept": 0, + "slope": 1 + }, + "type": "literal_in_y_or_linear_in_z" + } + }, + "keccak_256": { + "cpu": { + "arguments": { + "intercept": 2261318, + "slope": 64571 + }, + "type": "linear_in_x" + }, + "memory": { + "arguments": 4, + "type": "constant_cost" + } + }, + "lengthOfByteString": { + "cpu": { + "arguments": 1000, + "type": "constant_cost" + }, + "memory": { + "arguments": 10, + "type": "constant_cost" + } + }, + "lessThanByteString": { + "cpu": { + "arguments": { + "intercept": 197145, + "slope": 156 + }, + "type": "min_size" + }, + "memory": { + "arguments": 1, + "type": "constant_cost" + } + }, + "lessThanEqualsByteString": { + "cpu": { + "arguments": { + "intercept": 197145, + "slope": 156 + }, + "type": "min_size" + }, + "memory": { + "arguments": 1, + "type": "constant_cost" + } + }, + "lessThanEqualsInteger": { + "cpu": { + "arguments": { + "intercept": 204924, + "slope": 473 + }, + "type": "min_size" + }, + "memory": { + "arguments": 1, + "type": "constant_cost" + } + }, + "lessThanInteger": { + "cpu": { + "arguments": { + "intercept": 208896, + "slope": 511 + }, + "type": "min_size" + }, + "memory": { + "arguments": 1, + "type": "constant_cost" + } + }, + "listData": { + "cpu": { + "arguments": 52467, + "type": "constant_cost" }, - "appendByteString": { - "cpu": { - "arguments": { - "intercept": 1000, - "slope": 571 - }, - "type": "added_sizes" - }, - "memory": { - "arguments": { - "intercept": 0, - "slope": 1 - }, - "type": "added_sizes" - } + "memory": { + "arguments": 32, + "type": "constant_cost" + } + }, + "mapData": { + "cpu": { + "arguments": 64832, + "type": "constant_cost" }, - "appendString": { - "cpu": { - "arguments": { - "intercept": 1000, - "slope": 24177 - }, - "type": "added_sizes" - }, - "memory": { - "arguments": { - "intercept": 4, - "slope": 1 - }, - "type": "added_sizes" - } + "memory": { + "arguments": 32, + "type": "constant_cost" + } + }, + "mkCons": { + "cpu": { + "arguments": 65493, + "type": "constant_cost" }, - "bData": { - "cpu": { - "arguments": 1000, - "type": "constant_cost" - }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } + "memory": { + "arguments": 32, + "type": "constant_cost" + } + }, + "mkNilData": { + "cpu": { + "arguments": 22558, + "type": "constant_cost" }, - "blake2b_224": { - "cpu": { - "arguments": { - "intercept": 207616, - "slope": 8310 - }, - "type": "linear_in_x" - }, - "memory": { - "arguments": 4, - "type": "constant_cost" - } + "memory": { + "arguments": 32, + "type": "constant_cost" + } + }, + "mkNilPairData": { + "cpu": { + "arguments": 16563, + "type": "constant_cost" }, - "blake2b_256": { - "cpu": { - "arguments": { - "intercept": 117366, - "slope": 10475 - }, - "type": "linear_in_x" - }, - "memory": { - "arguments": 4, - "type": "constant_cost" - } + "memory": { + "arguments": 32, + "type": "constant_cost" + } + }, + "mkPairData": { + "cpu": { + "arguments": 76511, + "type": "constant_cost" }, - "bls12_381_G1_add": { - "cpu": { - "arguments": 962335, - "type": "constant_cost" - }, - "memory": { - "arguments": 18, - "type": "constant_cost" + "memory": { + "arguments": 32, + "type": "constant_cost" + } + }, + "modInteger": { + "cpu": { + "arguments": { + "constant": 196500, + "model": { + "arguments": { + "intercept": 453240, + "slope": 220 + }, + "type": "multiplied_sizes" } + }, + "type": "const_above_diagonal" }, - "bls12_381_G1_compress": { - "cpu": { - "arguments": 2780678, - "type": "constant_cost" - }, - "memory": { - "arguments": 6, - "type": "constant_cost" - } + "memory": { + "arguments": { + "intercept": 0, + "minimum": 1, + "slope": 1 + }, + "type": "subtracted_sizes" + } + }, + "multiplyInteger": { + "cpu": { + "arguments": { + "intercept": 69522, + "slope": 11687 + }, + "type": "added_sizes" }, - "bls12_381_G1_equal": { - "cpu": { - "arguments": 442008, - "type": "constant_cost" - }, - "memory": { - "arguments": 1, - "type": "constant_cost" - } + "memory": { + "arguments": { + "intercept": 0, + "slope": 1 + }, + "type": "added_sizes" + } + }, + "nullList": { + "cpu": { + "arguments": 60091, + "type": "constant_cost" }, - "bls12_381_G1_hashToGroup": { - "cpu": { - "arguments": { - "intercept": 52538055, - "slope": 3756 - }, - "type": "linear_in_x" - }, - "memory": { - "arguments": 18, - "type": "constant_cost" - } + "memory": { + "arguments": 32, + "type": "constant_cost" + } + }, + "indexArray": { + "cpu": { + "arguments": 194922, + "type": "constant_cost" }, - "bls12_381_G1_neg": { - "cpu": { - "arguments": 267929, - "type": "constant_cost" - }, - "memory": { - "arguments": 18, - "type": "constant_cost" - } + "memory": { + "arguments": 32, + "type": "constant_cost" + } + }, + "lengthOfArray": { + "cpu": { + "arguments": 198994, + "type": "constant_cost" }, - "bls12_381_G1_scalarMul": { - "cpu": { - "arguments": { - "intercept": 76433006, - "slope": 8868 - }, - "type": "linear_in_x" - }, - "memory": { - "arguments": 18, - "type": "constant_cost" - } + "memory": { + "arguments": 10, + "type": "constant_cost" + } + }, + "listToArray": { + "cpu": { + "arguments": { + "intercept": 307802, + "slope": 8496 + }, + "type": "linear_in_x" }, - "bls12_381_G1_multiScalarMul": { - "cpu": { - "arguments": { - "intercept": 321837444, - "slope": 25087669 - }, - "type": "linear_in_x" - }, - "memory": { - "arguments": 18, - "type": "constant_cost" + "memory": { + "arguments": { + "intercept": 7, + "slope": 1 + }, + "type": "linear_in_x" + } + }, + "quotientInteger": { + "cpu": { + "arguments": { + "constant": 196500, + "model": { + "arguments": { + "intercept": 453240, + "slope": 220 + }, + "type": "multiplied_sizes" } + }, + "type": "const_above_diagonal" }, - "bls12_381_G1_uncompress": { - "cpu": { - "arguments": 52948122, - "type": "constant_cost" - }, - "memory": { - "arguments": 18, - "type": "constant_cost" + "memory": { + "arguments": { + "intercept": 0, + "minimum": 1, + "slope": 1 + }, + "type": "subtracted_sizes" + } + }, + "remainderInteger": { + "cpu": { + "arguments": { + "constant": 196500, + "model": { + "arguments": { + "intercept": 453240, + "slope": 220 + }, + "type": "multiplied_sizes" } + }, + "type": "const_above_diagonal" }, - "bls12_381_G2_add": { - "cpu": { - "arguments": 1995836, - "type": "constant_cost" - }, - "memory": { - "arguments": 36, - "type": "constant_cost" - } + "memory": { + "arguments": { + "intercept": 0, + "minimum": 1, + "slope": 1 + }, + "type": "subtracted_sizes" + } + }, + "serialiseData": { + "cpu": { + "arguments": { + "intercept": 1159724, + "slope": 392670 + }, + "type": "linear_in_x" }, - "bls12_381_G2_compress": { - "cpu": { - "arguments": 3227919, - "type": "constant_cost" - }, - "memory": { - "arguments": 12, - "type": "constant_cost" - } + "memory": { + "arguments": { + "intercept": 0, + "slope": 2 + }, + "type": "linear_in_x" + } + }, + "sha2_256": { + "cpu": { + "arguments": { + "intercept": 806990, + "slope": 30482 + }, + "type": "linear_in_x" }, - "bls12_381_G2_equal": { - "cpu": { - "arguments": 901022, - "type": "constant_cost" - }, - "memory": { - "arguments": 1, - "type": "constant_cost" - } + "memory": { + "arguments": 4, + "type": "constant_cost" + } + }, + "sha3_256": { + "cpu": { + "arguments": { + "intercept": 1927926, + "slope": 82523 + }, + "type": "linear_in_x" }, - "bls12_381_G2_hashToGroup": { - "cpu": { - "arguments": { - "intercept": 166917843, - "slope": 4307 - }, - "type": "linear_in_x" - }, - "memory": { - "arguments": 36, - "type": "constant_cost" - } + "memory": { + "arguments": 4, + "type": "constant_cost" + } + }, + "sliceByteString": { + "cpu": { + "arguments": { + "intercept": 265318, + "slope": 0 + }, + "type": "linear_in_z" }, - "bls12_381_G2_neg": { - "cpu": { - "arguments": 284546, - "type": "constant_cost" - }, - "memory": { - "arguments": 36, - "type": "constant_cost" - } + "memory": { + "arguments": { + "intercept": 4, + "slope": 0 + }, + "type": "linear_in_z" + } + }, + "sndPair": { + "cpu": { + "arguments": 85931, + "type": "constant_cost" }, - "bls12_381_G2_scalarMul": { - "cpu": { - "arguments": { - "intercept": 158221314, - "slope": 26549 - }, - "type": "linear_in_x" - }, - "memory": { - "arguments": 36, - "type": "constant_cost" - } + "memory": { + "arguments": 32, + "type": "constant_cost" + } + }, + "subtractInteger": { + "cpu": { + "arguments": { + "intercept": 205665, + "slope": 812 + }, + "type": "max_size" }, - "bls12_381_G2_multiScalarMul": { - "cpu": { - "arguments": { - "intercept": 617887431, - "slope": 67302824 - }, - "type": "linear_in_x" - }, - "memory": { - "arguments": 36, - "type": "constant_cost" - } + "memory": { + "arguments": { + "intercept": 1, + "slope": 1 + }, + "type": "max_size" + } + }, + "tailList": { + "cpu": { + "arguments": 41182, + "type": "constant_cost" }, - "bls12_381_G2_uncompress": { - "cpu": { - "arguments": 74698472, - "type": "constant_cost" - }, - "memory": { - "arguments": 36, - "type": "constant_cost" - } + "memory": { + "arguments": 32, + "type": "constant_cost" + } + }, + "trace": { + "cpu": { + "arguments": 212342, + "type": "constant_cost" + }, + "memory": { + "arguments": 32, + "type": "constant_cost" + } + }, + "unBData": { + "cpu": { + "arguments": 31220, + "type": "constant_cost" + }, + "memory": { + "arguments": 32, + "type": "constant_cost" + } + }, + "unConstrData": { + "cpu": { + "arguments": 32696, + "type": "constant_cost" + }, + "memory": { + "arguments": 32, + "type": "constant_cost" + } + }, + "unIData": { + "cpu": { + "arguments": 43357, + "type": "constant_cost" + }, + "memory": { + "arguments": 32, + "type": "constant_cost" + } + }, + "unListData": { + "cpu": { + "arguments": 32247, + "type": "constant_cost" + }, + "memory": { + "arguments": 32, + "type": "constant_cost" + } + }, + "unMapData": { + "cpu": { + "arguments": 38314, + "type": "constant_cost" + }, + "memory": { + "arguments": 32, + "type": "constant_cost" + } + }, + "verifyEcdsaSecp256k1Signature": { + "cpu": { + "arguments": 35190005, + "type": "constant_cost" + }, + "memory": { + "arguments": 10, + "type": "constant_cost" + } + }, + "verifyEd25519Signature": { + "cpu": { + "arguments": { + "intercept": 57996947, + "slope": 18975 + }, + "type": "linear_in_z" + }, + "memory": { + "arguments": 10, + "type": "constant_cost" + } + }, + "verifySchnorrSecp256k1Signature": { + "cpu": { + "arguments": { + "intercept": 39121781, + "slope": 32260 + }, + "type": "linear_in_y" + }, + "memory": { + "arguments": 10, + "type": "constant_cost" + } + }, + "andByteString": { + "cpu": { + "arguments": { + "intercept": 100181, + "slope1": 726, + "slope2": 719 + }, + "type": "linear_in_y_and_z" + }, + "memory": { + "arguments": { + "intercept": 0, + "slope": 1 + }, + "type": "linear_in_max_yz" + } + }, + "orByteString": { + "cpu": { + "arguments": { + "intercept": 100181, + "slope1": 726, + "slope2": 719 + }, + "type": "linear_in_y_and_z" }, - "bls12_381_finalVerify": { - "cpu": { - "arguments": 333849714, - "type": "constant_cost" - }, - "memory": { - "arguments": 1, - "type": "constant_cost" - } + "memory": { + "arguments": { + "intercept": 0, + "slope": 1 + }, + "type": "linear_in_max_yz" + } + }, + "xorByteString": { + "cpu": { + "arguments": { + "intercept": 100181, + "slope1": 726, + "slope2": 719 + }, + "type": "linear_in_y_and_z" }, - "bls12_381_millerLoop": { - "cpu": { - "arguments": 254006273, - "type": "constant_cost" - }, - "memory": { - "arguments": 72, - "type": "constant_cost" - } + "memory": { + "arguments": { + "intercept": 0, + "slope": 1 + }, + "type": "linear_in_max_yz" + } + }, + "complementByteString": { + "cpu": { + "arguments": { + "intercept": 107878, + "slope": 680 + }, + "type": "linear_in_x" }, - "bls12_381_mulMlResult": { - "cpu": { - "arguments": 2174038, - "type": "constant_cost" - }, - "memory": { - "arguments": 72, - "type": "constant_cost" - } + "memory": { + "arguments": { + "intercept": 0, + "slope": 1 + }, + "type": "linear_in_x" + } + }, + "readBit": { + "cpu": { + "arguments": 95336, + "type": "constant_cost" }, - "byteStringToInteger": { - "cpu": { - "arguments": { - "c0": 1006041, - "c1": 43623, - "c2": 251 - }, - "type": "quadratic_in_y" - }, - "memory": { - "arguments": { - "intercept": 0, - "slope": 1 - }, - "type": "linear_in_y" - } + "memory": { + "arguments": 1, + "type": "constant_cost" + } + }, + "writeBits": { + "cpu": { + "arguments": { + "intercept": 281145, + "slope": 18848 + }, + "type": "linear_in_y" }, - "chooseData": { - "cpu": { - "arguments": 19537, - "type": "constant_cost" - }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } + "memory": { + "arguments": { + "intercept": 0, + "slope": 1 + }, + "type": "linear_in_x" + } + }, + "replicateByte": { + "cpu": { + "arguments": { + "intercept": 180194, + "slope": 159 + }, + "type": "linear_in_x" }, - "chooseList": { - "cpu": { - "arguments": 175354, - "type": "constant_cost" - }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } + "memory": { + "arguments": { + "intercept": 1, + "slope": 1 + }, + "type": "linear_in_x" + } + }, + "shiftByteString": { + "cpu": { + "arguments": { + "intercept": 158519, + "slope": 8942 + }, + "type": "linear_in_x" }, - "chooseUnit": { - "cpu": { - "arguments": 46417, - "type": "constant_cost" - }, - "memory": { - "arguments": 4, - "type": "constant_cost" - } + "memory": { + "arguments": { + "intercept": 0, + "slope": 1 + }, + "type": "linear_in_x" + } + }, + "rotateByteString": { + "cpu": { + "arguments": { + "intercept": 159378, + "slope": 8813 + }, + "type": "linear_in_x" }, - "consByteString": { - "cpu": { - "arguments": { - "intercept": 221973, - "slope": 511 - }, - "type": "linear_in_y" - }, - "memory": { - "arguments": { - "intercept": 0, - "slope": 1 - }, - "type": "added_sizes" - } + "memory": { + "arguments": { + "intercept": 0, + "slope": 1 + }, + "type": "linear_in_x" + } + }, + "countSetBits": { + "cpu": { + "arguments": { + "intercept": 107490, + "slope": 3298 + }, + "type": "linear_in_x" }, - "constrData": { - "cpu": { - "arguments": 89141, - "type": "constant_cost" - }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } + "memory": { + "arguments": 1, + "type": "constant_cost" + } + }, + "findFirstSetBit": { + "cpu": { + "arguments": { + "intercept": 106057, + "slope": 655 + }, + "type": "linear_in_x" }, - "decodeUtf8": { - "cpu": { - "arguments": { - "intercept": 497525, - "slope": 14068 - }, - "type": "linear_in_x" - }, - "memory": { - "arguments": { - "intercept": 4, - "slope": 2 - }, - "type": "linear_in_x" - } + "memory": { + "arguments": 1, + "type": "constant_cost" + } + }, + "ripemd_160": { + "cpu": { + "arguments": { + "intercept": 1964219, + "slope": 24520 + }, + "type": "linear_in_x" }, - "divideInteger": { - "cpu": { - "arguments": { - "constant": 196500, - "model": { - "arguments": { - "intercept": 453240, - "slope": 220 - }, - "type": "multiplied_sizes" - } - }, - "type": "const_above_diagonal" - }, - "memory": { - "arguments": { - "intercept": 0, - "minimum": 1, - "slope": 1 - }, - "type": "subtracted_sizes" - } + "memory": { + "arguments": 3, + "type": "constant_cost" + } + }, + "expModInteger": { + "cpu": { + "arguments": { + "coefficient00": 607153, + "coefficient11": 231697, + "coefficient12": 53144 + }, + "type": "exp_mod_cost" }, - "encodeUtf8": { - "cpu": { - "arguments": { - "intercept": 1000, - "slope": 28662 - }, - "type": "linear_in_x" - }, - "memory": { - "arguments": { - "intercept": 4, - "slope": 2 - }, - "type": "linear_in_x" - } + "memory": { + "arguments": { + "intercept": 0, + "slope": 1 + }, + "type": "linear_in_z" + } + }, + "dropList": { + "cpu": { + "arguments": { + "intercept": 116711, + "slope": 1957 + }, + "type": "linear_in_x" }, "memory": { "arguments": 4, @@ -468,806 +1250,29 @@ }, "type": "linear_in_x" }, - "fstPair": { - "cpu": { - "arguments": 80436, - "type": "constant_cost" - }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } - }, - "headList": { - "cpu": { - "arguments": 43249, - "type": "constant_cost" - }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } - }, - "iData": { - "cpu": { - "arguments": 1000, - "type": "constant_cost" - }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } - }, - "ifThenElse": { - "cpu": { - "arguments": 80556, - "type": "constant_cost" - }, - "memory": { - "arguments": 1, - "type": "constant_cost" - } - }, - "indexByteString": { - "cpu": { - "arguments": 57667, - "type": "constant_cost" - }, - "memory": { - "arguments": 4, - "type": "constant_cost" - } - }, - "integerToByteString": { - "cpu": { - "arguments": { - "c0": 1293828, - "c1": 28716, - "c2": 63 - }, - "type": "quadratic_in_z" - }, - "memory": { - "arguments": { - "intercept": 0, - "slope": 1 - }, - "type": "literal_in_y_or_linear_in_z" - } - }, - "keccak_256": { - "cpu": { - "arguments": { - "intercept": 2261318, - "slope": 64571 - }, - "type": "linear_in_x" - }, - "memory": { - "arguments": 4, - "type": "constant_cost" - } - }, - "lengthOfByteString": { - "cpu": { - "arguments": 1000, - "type": "constant_cost" - }, - "memory": { - "arguments": 10, - "type": "constant_cost" - } - }, - "lessThanByteString": { - "cpu": { - "arguments": { - "intercept": 197145, - "slope": 156 - }, - "type": "min_size" - }, - "memory": { - "arguments": 1, - "type": "constant_cost" - } - }, - "lessThanEqualsByteString": { - "cpu": { - "arguments": { - "intercept": 197145, - "slope": 156 - }, - "type": "min_size" - }, - "memory": { - "arguments": 1, - "type": "constant_cost" - } - }, - "lessThanEqualsInteger": { - "cpu": { - "arguments": { - "intercept": 204924, - "slope": 473 - }, - "type": "min_size" - }, - "memory": { - "arguments": 1, - "type": "constant_cost" - } - }, - "lessThanInteger": { - "cpu": { - "arguments": { - "intercept": 208896, - "slope": 511 - }, - "type": "min_size" - }, - "memory": { - "arguments": 1, - "type": "constant_cost" - } - }, - "listData": { - "cpu": { - "arguments": 52467, - "type": "constant_cost" - }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } - }, - "mapData": { - "cpu": { - "arguments": 64832, - "type": "constant_cost" - }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } - }, - "mkCons": { - "cpu": { - "arguments": 65493, - "type": "constant_cost" - }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } - }, - "mkNilData": { - "cpu": { - "arguments": 22558, - "type": "constant_cost" - }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } - }, - "mkNilPairData": { - "cpu": { - "arguments": 16563, - "type": "constant_cost" - }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } - }, - "mkPairData": { - "cpu": { - "arguments": 76511, - "type": "constant_cost" - }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } - }, - "modInteger": { - "cpu": { - "arguments": { - "constant": 196500, - "model": { - "arguments": { - "intercept": 453240, - "slope": 220 - }, - "type": "multiplied_sizes" - } - }, - "type": "const_above_diagonal" - }, - "memory": { - "arguments": { - "intercept": 0, - "minimum": 1, - "slope": 1 - }, - "type": "subtracted_sizes" - } - }, - "multiplyInteger": { - "cpu": { - "arguments": { - "intercept": 69522, - "slope": 11687 - }, - "type": "added_sizes" - }, - "memory": { - "arguments": { - "intercept": 0, - "slope": 1 - }, - "type": "added_sizes" - } - }, - "nullList": { - "cpu": { - "arguments": 60091, - "type": "constant_cost" - }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } - }, - "indexArray": { - "cpu": { - "arguments": 194922, - "type": "constant_cost" - }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } - }, - "lengthOfArray": { - "cpu": { - "arguments": 198994, - "type": "constant_cost" - }, - "memory": { - "arguments": 10, - "type": "constant_cost" - } - }, - "listToArray": { - "cpu": { - "arguments": { - "intercept": 307802, - "slope": 8496 - }, - "type": "linear_in_x" - }, - "memory": { - "arguments": { - "intercept": 7, - "slope": 1 - }, - "type": "linear_in_x" - } - }, - "quotientInteger": { - "cpu": { - "arguments": { - "constant": 196500, - "model": { - "arguments": { - "intercept": 453240, - "slope": 220 - }, - "type": "multiplied_sizes" - } - }, - "type": "const_above_diagonal" - }, - "memory": { - "arguments": { - "intercept": 0, - "minimum": 1, - "slope": 1 - }, - "type": "subtracted_sizes" - } - }, - "remainderInteger": { - "cpu": { - "arguments": { - "constant": 196500, - "model": { - "arguments": { - "intercept": 453240, - "slope": 220 - }, - "type": "multiplied_sizes" - } - }, - "type": "const_above_diagonal" - }, - "memory": { - "arguments": { - "intercept": 0, - "minimum": 1, - "slope": 1 - }, - "type": "subtracted_sizes" - } - }, - "serialiseData": { - "cpu": { - "arguments": { - "intercept": 1159724, - "slope": 392670 - }, - "type": "linear_in_x" - }, - "memory": { - "arguments": { - "intercept": 0, - "slope": 2 - }, - "type": "linear_in_x" - } - }, - "sha2_256": { - "cpu": { - "arguments": { - "intercept": 806990, - "slope": 30482 - }, - "type": "linear_in_x" - }, - "memory": { - "arguments": 4, - "type": "constant_cost" - } - }, - "sha3_256": { - "cpu": { - "arguments": { - "intercept": 1927926, - "slope": 82523 - }, - "type": "linear_in_x" - }, - "memory": { - "arguments": 4, - "type": "constant_cost" - } - }, - "sliceByteString": { - "cpu": { - "arguments": { - "intercept": 265318, - "slope": 0 - }, - "type": "linear_in_z" - }, - "memory": { - "arguments": { - "intercept": 4, - "slope": 0 - }, - "type": "linear_in_z" - } - }, - "sndPair": { - "cpu": { - "arguments": 85931, - "type": "constant_cost" - }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } - }, - "subtractInteger": { - "cpu": { - "arguments": { - "intercept": 205665, - "slope": 812 - }, - "type": "max_size" - }, - "memory": { - "arguments": { - "intercept": 1, - "slope": 1 - }, - "type": "max_size" - } - }, - "tailList": { - "cpu": { - "arguments": 41182, - "type": "constant_cost" - }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } - }, - "trace": { - "cpu": { - "arguments": 212342, - "type": "constant_cost" - }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } - }, - "unBData": { - "cpu": { - "arguments": 31220, - "type": "constant_cost" - }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } - }, - "unConstrData": { - "cpu": { - "arguments": 32696, - "type": "constant_cost" - }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } - }, - "unIData": { - "cpu": { - "arguments": 43357, - "type": "constant_cost" - }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } - }, - "unListData": { - "cpu": { - "arguments": 32247, - "type": "constant_cost" - }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } - }, - "unMapData": { - "cpu": { - "arguments": 38314, - "type": "constant_cost" - }, - "memory": { - "arguments": 32, - "type": "constant_cost" - } - }, - "verifyEcdsaSecp256k1Signature": { - "cpu": { - "arguments": 35190005, - "type": "constant_cost" - }, - "memory": { - "arguments": 10, - "type": "constant_cost" - } - }, - "verifyEd25519Signature": { - "cpu": { - "arguments": { - "intercept": 57996947, - "slope": 18975 - }, - "type": "linear_in_z" - }, - "memory": { - "arguments": 10, - "type": "constant_cost" - } - }, - "verifySchnorrSecp256k1Signature": { - "cpu": { - "arguments": { - "intercept": 39121781, - "slope": 32260 - }, - "type": "linear_in_y" - }, - "memory": { - "arguments": 10, - "type": "constant_cost" - } - }, - "andByteString": { - "cpu": { - "arguments": { - "intercept": 100181, - "slope1": 726, - "slope2": 719 - }, - "type": "linear_in_y_and_z" - }, - "memory": { - "arguments": { - "intercept": 0, - "slope": 1 - }, - "type": "linear_in_max_yz" - } - }, - "orByteString": { - "cpu": { - "arguments": { - "intercept": 100181, - "slope1": 726, - "slope2": 719 - }, - "type": "linear_in_y_and_z" - }, - "memory": { - "arguments": { - "intercept": 0, - "slope": 1 - }, - "type": "linear_in_max_yz" - } - }, - "xorByteString": { - "cpu": { - "arguments": { - "intercept": 100181, - "slope1": 726, - "slope2": 719 - }, - "type": "linear_in_y_and_z" - }, - "memory": { - "arguments": { - "intercept": 0, - "slope": 1 - }, - "type": "linear_in_max_yz" - } - }, - "complementByteString": { - "cpu": { - "arguments": { - "intercept": 107878, - "slope": 680 - }, - "type": "linear_in_x" - }, - "memory": { - "arguments": { - "intercept": 0, - "slope": 1 - }, - "type": "linear_in_x" - } - }, - "readBit": { - "cpu": { - "arguments": 95336, - "type": "constant_cost" - }, - "memory": { - "arguments": 1, - "type": "constant_cost" - } - }, - "writeBits": { - "cpu": { - "arguments": { - "intercept": 281145, - "slope": 18848 - }, - "type": "linear_in_y" - }, - "memory": { - "arguments": { - "intercept": 0, - "slope": 1 - }, - "type": "linear_in_x" - } - }, - "replicateByte": { - "cpu": { - "arguments": { - "intercept": 180194, - "slope": 159 - }, - "type": "linear_in_x" - }, - "memory": { - "arguments": { - "intercept": 1, - "slope": 1 - }, - "type": "linear_in_x" - } - }, - "shiftByteString": { - "cpu": { - "arguments": { - "intercept": 158519, - "slope": 8942 - }, - "type": "linear_in_x" - }, - "memory": { - "arguments": { - "intercept": 0, - "slope": 1 - }, - "type": "linear_in_x" - } - }, - "rotateByteString": { - "cpu": { - "arguments": { - "intercept": 159378, - "slope": 8813 - }, - "type": "linear_in_x" - }, - "memory": { - "arguments": { - "intercept": 0, - "slope": 1 - }, - "type": "linear_in_x" - } - }, - "countSetBits": { - "cpu": { - "arguments": { - "intercept": 107490, - "slope": 3298 - }, - "type": "linear_in_x" - }, - "memory": { - "arguments": 1, - "type": "constant_cost" - } - }, - "findFirstSetBit": { - "cpu": { - "arguments": { - "intercept": 106057, - "slope": 655 - }, - "type": "linear_in_x" - }, - "memory": { - "arguments": 1, - "type": "constant_cost" - } - }, - "ripemd_160": { - "cpu": { - "arguments": { - "intercept": 1964219, - "slope": 24520 - }, - "type": "linear_in_x" - }, - "memory": { - "arguments": 3, - "type": "constant_cost" - } - }, - "expModInteger": { - "cpu": { - "arguments": { - "coefficient00": 607153, - "coefficient11": 231697, - "coefficient12": 53144 - }, - "type": "exp_mod_cost" - }, - "memory": { - "arguments": { - "intercept": 0, - "slope": 1 - }, - "type": "linear_in_z" - } - }, - "dropList": { - "cpu": { - "arguments": { - "intercept": 116711, - "slope": 1957 - }, - "type": "linear_in_x" - }, - "memory": { - "arguments": 4, - "type": "constant_cost" - } - }, - "lookupCoin": { - "cpu": { - "arguments": { - "intercept": 272043, - "slope": 16 - }, - "type": "linear_in_z" - }, - "memory": { - "arguments": 1, - "type": "constant_cost" - } - }, - "valueContains": { - "cpu": { - "arguments": { - "intercept": 6684283, - "slope": 1000 - }, - "type": "added_sizes" - }, - "memory": { - "arguments": 1, - "type": "constant_cost" - } - }, - "valueData": { - "cpu": { - "arguments": 167190, - "type": "constant_cost" - }, - "memory": { - "arguments": 1, - "type": "constant_cost" - } - }, - "unValueData": { - "cpu": { - "arguments": { - "intercept": 1000, - "slope": 19835 - }, - "type": "linear_in_x" - }, - "memory": { - "arguments": 1, - "type": "constant_cost" - } + "memory": { + "arguments": 1, + "type": "constant_cost" } - , "insertCoin": { - "cpu": { - "arguments": 1000, - "type": "constant_cost" - }, - "memory": { - "arguments": 10, - "type": "constant_cost" - } + }, + "insertCoin": { + "cpu": { + "arguments": 1000, + "type": "constant_cost" + }, + "memory": { + "arguments": 10, + "type": "constant_cost" } - , "unionValue": { - "cpu": { - "arguments": 1000, - "type": "constant_cost" - }, - "memory": { - "arguments": 10, - "type": "constant_cost" - } + }, + "unionValue": { + "cpu": { + "arguments": 1000, + "type": "constant_cost" + }, + "memory": { + "arguments": 10, + "type": "constant_cost" } + } }