From 535cf8b8ef248cf8eaebbaa859e19f00f2d25355 Mon Sep 17 00:00:00 2001 From: David Terry Date: Thu, 20 May 2021 15:47:42 +0200 Subject: [PATCH 01/21] hevm: add mutators for abi values --- src/hevm/hevm.cabal | 6 +- src/hevm/src/EVM/Mutate.hs | 122 +++++++++++++++++++++++++++++++++++++ 2 files changed, 126 insertions(+), 2 deletions(-) create mode 100644 src/hevm/src/EVM/Mutate.hs diff --git a/src/hevm/hevm.cabal b/src/hevm/hevm.cabal index 9f3717d22..a984fc6f6 100644 --- a/src/hevm/hevm.cabal +++ b/src/hevm/hevm.cabal @@ -63,6 +63,7 @@ library EVM.Types, EVM.UnitTest, EVM.VMTest + EVM.Mutate other-modules: Paths_hevm autogen-modules: @@ -80,7 +81,7 @@ library install-includes: ethjet/tinykeccak.h, ethjet/ethjet.h, ethjet/ethjet-ff.h, ethjet/blake2.h build-depends: - QuickCheck >= 2.13.2 && < 2.15, + QuickCheck >= 2.14.2 && < 2.15, Decimal == 0.5.1, containers >= 0.6.0 && < 0.7, deepseq >= 1.4.4 && < 1.5, @@ -128,7 +129,8 @@ library witherable >= 0.3.5 && < 0.4, wreq >= 0.5.3 && < 0.6, regex-tdfa >= 1.2.3 && < 1.4, - base >= 4.9 && < 5 + base >= 4.9 && < 5, + ListLike >= 4.7.4 && < 4.8 hs-source-dirs: src default-language: diff --git a/src/hevm/src/EVM/Mutate.hs b/src/hevm/src/EVM/Mutate.hs new file mode 100644 index 000000000..960d2e4e5 --- /dev/null +++ b/src/hevm/src/EVM/Mutate.hs @@ -0,0 +1,122 @@ +{- + Mutators for abi values, adapted from echidna +-} +module EVM.Mutate where + +import Data.Bifunctor (second) +import Data.Bool (bool) +import Test.QuickCheck.Gen (Gen, chooseInt, chooseInteger, frequency) +import Data.DoubleWord (Int256, Word256) +import Test.QuickCheck.Arbitrary (arbitrary) + +import EVM.ABI + +import Control.Monad (replicateM) +import qualified Data.ByteString as BS +import qualified Data.Vector as V +import qualified Data.ListLike as LL + +-- | Given an 'AbiValue', generate a random \"similar\" value of the same 'AbiType'. +mutateAbiValue :: AbiValue -> Gen AbiValue +mutateAbiValue (AbiUInt n x) = chooseInt (0, 9) >>= -- 10% of chance of mutation + \case + 0 -> fixAbiUInt n <$> mutateNum x + _ -> return $ AbiUInt n x +mutateAbiValue (AbiInt n x) = chooseInt (0, 9) >>= -- 10% of chance of mutation + \case + 0 -> fixAbiInt n <$> mutateNum x + _ -> return $ AbiInt n x + +mutateAbiValue (AbiAddress x) = return $ AbiAddress x +mutateAbiValue (AbiBool _) = genAbiValue AbiBoolType +mutateAbiValue (AbiBytes n b) = do fs <- replicateM n arbitrary + xs <- mutateLL (Just n) (BS.pack fs) b + return (AbiBytes n xs) + +mutateAbiValue (AbiBytesDynamic b) = AbiBytesDynamic <$> mutateLL Nothing mempty b +mutateAbiValue (AbiString b) = AbiString <$> mutateLL Nothing mempty b +mutateAbiValue (AbiArray n t l) = do fs <- replicateM n $ genAbiValue t + xs <- mutateLL (Just n) (V.fromList fs) l + return (AbiArray n t xs) + +mutateAbiValue (AbiArrayDynamic t l) = AbiArrayDynamic t <$> mutateLL Nothing mempty l +mutateAbiValue (AbiTuple v) = AbiTuple <$> traverse mutateAbiValue v + + +-- | Mutate a list-like data structure using a list of mutators +mutateLL :: LL.ListLike f i + => Maybe Int -- ^ Required size for the mutated list-like value (or Nothing if there are no constrains) + -> f -- ^ Randomly generated list-like value to complement the mutated list, if it is shorter than the requested size + -> f -- ^ List-like value to mutate + -> Gen f +mutateLL mn fs vs = do + f <- genMutator + xs <- f vs + return $ maybe xs (`LL.take` (xs <> fs)) mn + +-- | A list of mutators to randomly select to perform a mutation of list-like values +genMutator :: LL.ListLike f i => Gen (f -> Gen f) +genMutator = frequency . fmap (second pure) $ [(1, return), (10, expandRandList), (10, deleteRandList), (10, swapRandList)] + +-- | +expandRandList :: LL.ListLike f i => f -> Gen f +expandRandList xs + | l == 0 = return xs + | l >= 32 = return xs + | otherwise = do + k <- chooseInt (0, l - 1) + t <- chooseInt (1, min 32 l) + return $ expandAt xs k t + where l = LL.length xs + +expandAt :: LL.ListLike f i => f -> Int -> Int -> f +expandAt xs k t = + case LL.uncons xs of + Nothing -> xs + Just (y,ys) -> if k == 0 + then LL.replicate t y <> ys + else LL.cons y (expandAt ys (k - 1) t) + +-- | Delete a random element from the `ListLike` f +deleteRandList :: LL.ListLike f i => f -> Gen f +deleteRandList xs = + if LL.null xs + then return xs + else do + k <- chooseInt (0, LL.length xs - 1) + return $ deleteAt k xs + +deleteAt :: LL.ListLike f i => Int -> f -> f +deleteAt n f = LL.take n f <> LL.drop (n+1) f + +-- | Given a `ListLike` f, swap two random elements +swapRandList :: LL.ListLike f i => f -> Gen f +swapRandList xs = + if LL.null xs + then return xs + else do + i <- chooseInt (0, LL.length xs - 1) + j <- chooseInt (0, LL.length xs - 1) + return $ if i == j then xs else swapAt xs (min i j) (max i j) + +-- taken from https://stackoverflow.com/questions/30551033/swap-two-elements-in-a-list-by-its-indices/30551130#30551130 +swapAt :: LL.ListLike f i => f -> Int -> Int -> f +swapAt xs i j = left <> LL.cons elemJ middle <> LL.cons elemI right + where elemI = xs `LL.index` i + elemJ = xs `LL.index` j + left = LL.take i xs + middle = LL.take (j - i - 1) (LL.drop (i + 1) xs) + right = LL.drop (j + 1) xs + + +-- | Given an 'Integral' number n, get a random number in [0,2n]. +mutateNum :: Integral a => a -> Gen a +mutateNum x = bool (x +) (x -) <$> arbitrary <*> (fromInteger <$> (chooseInteger (0, toInteger x))) + +-- | Force `x` to be in the range of a uint of size `n` +fixAbiUInt :: Int -> Word256 -> AbiValue +fixAbiUInt n x = AbiUInt n (x `mod` ((2 ^ n) - 1)) + +-- | Force `x` to be in the range of an int of size `n` +fixAbiInt :: Int -> Int256 -> AbiValue +fixAbiInt n x = AbiInt n (x `mod` 2 ^ (n - 1)) From 662173c61bbd165303f087a581a85cf6e01a3f12 Mon Sep 17 00:00:00 2001 From: David Terry Date: Tue, 25 May 2021 14:49:31 +0200 Subject: [PATCH 02/21] hevm: UnitTest: coverage guided fuzzing --- src/hevm/src/EVM/UnitTest.hs | 87 +++++++++++++++++++++--------------- 1 file changed, 51 insertions(+), 36 deletions(-) diff --git a/src/hevm/src/EVM/UnitTest.hs b/src/hevm/src/EVM/UnitTest.hs index 17bc60425..1f391e9e2 100644 --- a/src/hevm/src/EVM/UnitTest.hs +++ b/src/hevm/src/EVM/UnitTest.hs @@ -18,6 +18,7 @@ import EVM.Solidity import EVM.SymExec import EVM.Types import EVM.Transaction (initTx) +import EVM.Mutate (mutateAbiValue) import qualified EVM.Fetch import qualified EVM.FeeSchedule as FeeSchedule @@ -44,7 +45,7 @@ import Data.Decimal (DecimalRaw(..)) import Data.Either (isRight, lefts) import Data.Foldable (toList) import Data.Map (Map) -import Data.Maybe (fromMaybe, catMaybes, fromJust, isJust, fromMaybe, mapMaybe) +import Data.Maybe (fromMaybe, catMaybes, fromJust, isJust, isNothing, fromMaybe, mapMaybe) import Data.Text (isPrefixOf, stripSuffix, intercalate, Text, pack, unpack) import Data.Text.Encoding (encodeUtf8) import System.Environment (lookupEnv) @@ -101,6 +102,8 @@ data TestVMParams = TestVMParams , testChainId :: W256 } +type Corpus = Map (MultiSet OpLocation) (SolcContract, Text, AbiValue) + defaultGasForCreating :: W256 defaultGasForCreating = 0xffffffffffff @@ -191,11 +194,30 @@ checkFailures UnitTestOptions { .. } method bailed = do in pure (shouldFail == failed) _ -> error "internal error: unexpected failure code" --- | Randomly generates the calldata arguments and runs the test -fuzzTest :: UnitTestOptions -> Text -> [AbiType] -> VM -> Property -fuzzTest opts sig types vm = forAllShow (genAbiValue (AbiTupleType $ Vector.fromList types)) (show . ByteStringS . encodeAbiValue) - $ \args -> ioProperty $ - fst <$> runStateT (EVM.Stepper.interpret (oracle opts) (runUnitTest opts sig args)) vm +-- | Either generates the calldata by mutating an example from the corpus, or synthesizes a random example +genWithCorpus :: UnitTestOptions -> Corpus -> Text -> [AbiType] -> Gen AbiValue +genWithCorpus _ corpus sig tps = do + b <- arbitrary :: Gen Bool + if b then genAbiValue (AbiTupleType $ Vector.fromList tps) + else do + -- TODO: also check that the contract matches here + let examples = [cd | (_, sig', cd) <- (fmap snd) . Map.toList $ corpus, sig' == sig] + case examples of + [] -> genAbiValue (AbiTupleType $ Vector.fromList tps) + _ -> Test.QuickCheck.elements examples >>= mutateAbiValue + +-- | Randomly generates the calldata arguments and runs the test, updates the corpus with a new example if we explored a new path +fuzzTest :: UnitTestOptions -> Text -> [AbiType] -> VM -> StateT Corpus IO FuzzResult +fuzzTest opts@UnitTestOptions { .. } sig types vm = do + corpus <- get + args <- liftIO . generate $ genWithCorpus opts corpus sig types + (res, (vm', coverage)) <- liftIO $ runStateT (interpretWithCoverage opts (runUnitTest opts sig args)) (vm, mempty) + let contract' = _contractcode . fromJust $ currentContract vm + code' = fromJust $ lookupCode contract' dapp + when (isNothing $ Map.lookup coverage corpus) $ modify (Map.insert coverage (code', sig, args)) + if res + then pure Pass + else pure $ Fail vm' (show . ByteStringS . encodeAbiValue $ args) tick :: Text -> IO () tick x = Text.putStr x >> hFlush stdout @@ -294,7 +316,7 @@ coverageReport dapp cov = linesByName :: Map Text (Vector ByteString) linesByName = Map.fromList $ zipWith - (\(name, _) lines -> (name, lines)) + (\(name, _) lines' -> (name, lines')) (view sourceFiles sources) (view sourceLines sources) @@ -460,44 +482,37 @@ runOne opts@UnitTestOptions{..} vm testName args = do , vm'' ) +data FuzzResult = Pass | Fail VM String + -- | Define the thread spawner for property based tests fuzzRun :: UnitTestOptions -> VM -> Text -> [AbiType] -> IO (Text, Either Text Text, VM) fuzzRun opts@UnitTestOptions{..} vm testName types = do - let args = Args{ replay = Nothing - , maxSuccess = fuzzRuns - , maxDiscardRatio = 10 - , maxSize = 100 - , chatty = isJust verbose - , maxShrinks = maxBound - } - quickCheckWithResult args (fuzzTest opts testName types vm) >>= \case - Success numTests _ _ _ _ _ -> + (res, _) <- foldM (\(res, corpus) _ -> case res of + Pass -> runStateT (fuzzTest opts testName types vm) corpus + Fail {} -> pure (res, corpus) + ) (Pass, mempty) [0..fuzzRuns] + + case res of + (Pass) -> pure ("\x1b[32m[PASS]\x1b[0m " - <> testName <> " (runs: " <> (pack $ show numTests) <> ")" + <> testName <> " (runs: " <> (pack . show $ fuzzRuns) <> ")" -- this isn't the post vm we actually want, as we -- can't retrieve the correct vm from quickcheck , Right (passOutput vm opts testName) , vm ) - Failure _ _ _ _ _ _ _ _ _ _ failCase _ _ -> - let abiValue = decodeAbiValue (AbiTupleType (Vector.fromList types)) $ BSLazy.fromStrict $ hexText (pack $ concat failCase) - ppOutput = pack $ show abiValue - in do - -- Run the failing test again to get a proper trace - vm' <- execStateT (EVM.Stepper.interpret oracle (runUnitTest opts testName abiValue)) vm - pure ("\x1b[31m[FAIL]\x1b[0m " - <> testName <> ". Counterexample: " <> ppOutput - <> "\nRun:\n dapp test --replay '(\"" <> testName <> "\",\"" - <> (pack (concat failCase)) <> "\")'\nto test this case again, or \n dapp debug --replay '(\"" - <> testName <> "\",\"" <> (pack (concat failCase)) <> "\")'\nto debug it." - , Left (failOutput vm' opts testName) - , vm' - ) - _ -> pure ("\x1b[31m[OOPS]\x1b[0m " - <> testName - , Left (failOutput vm opts testName) - , vm - ) + (Fail vm' cex) -> + pure ("\x1b[31m[FAIL]\x1b[0m " + <> testName <> ". Counterexample: " <> ppOutput + <> "\nRun:\n dapp test --replay '(\"" <> testName <> "\",\"" + <> (pack cex) <> "\")'\nto test this case again, or \n dapp debug --replay '(\"" + <> testName <> "\",\"" <> (pack cex) <> "\")'\nto debug it." + , Left (failOutput vm' opts testName) + , vm' + ) + where + abiValue = decodeAbiValue (AbiTupleType (Vector.fromList types)) $ BSLazy.fromStrict $ hexText (pack cex) + ppOutput = pack $ show abiValue -- | Define the thread spawner for symbolic tests -- TODO: return a list of VM's From ace7bf6fe9250ef2d12b2b2bd362f1f6cea1e913 Mon Sep 17 00:00:00 2001 From: David Terry Date: Tue, 25 May 2021 15:46:59 +0200 Subject: [PATCH 03/21] hevm: allow mutations percentage to be set from the command line --- src/hevm/hevm-cli/hevm-cli.hs | 8 +++++++- src/hevm/src/EVM/Mutate.hs | 10 ++-------- src/hevm/src/EVM/UnitTest.hs | 19 ++++++++----------- 3 files changed, 17 insertions(+), 20 deletions(-) diff --git a/src/hevm/hevm-cli/hevm-cli.hs b/src/hevm/hevm-cli/hevm-cli.hs index 2713de7e9..f79fe6b5a 100644 --- a/src/hevm/hevm-cli/hevm-cli.hs +++ b/src/hevm/hevm-cli/hevm-cli.hs @@ -171,6 +171,7 @@ data Command w , debug :: w ::: Bool "Run interactively" , jsontrace :: w ::: Bool "Print json trace output at every step" , fuzzRuns :: w ::: Maybe Int "Number of times to run fuzz tests" + , mutations :: w ::: Maybe Int "Percentage of fuzz runs that should mutate a previous input vs randomly generating new inputs" , replay :: w ::: Maybe (Text, ByteString) "Custom fuzz case to run/debug" , rpc :: w ::: Maybe URL "Fetch state from a remote node" , verbose :: w ::: Maybe Int "Append call trace: {1} failures {2} all" @@ -291,6 +292,11 @@ unitTestOptions cmd testFile = do , EVM.UnitTest.vmModifier = vmModifier , EVM.UnitTest.testParams = params , EVM.UnitTest.dapp = srcInfo + , EVM.UnitTest.mutations = case mutations cmd of + Nothing -> 50 + Just x -> if x > 100 + then error "Mutations cannot be greater than 100" + else x } main :: IO () @@ -757,7 +763,7 @@ vmFromCommand cmd = do , EVM.vmoptChainId = word chainid 1 , EVM.vmoptCreate = create cmd , EVM.vmoptStorageModel = ConcreteS - , EVM.vmoptTxAccessList = mempty -- TODO: support me soon + , EVM.vmoptTxAccessList = mempty -- TODO: support me soon } word f def = fromMaybe def (f cmd) addr f def = fromMaybe def (f cmd) diff --git a/src/hevm/src/EVM/Mutate.hs b/src/hevm/src/EVM/Mutate.hs index 960d2e4e5..1e66312eb 100644 --- a/src/hevm/src/EVM/Mutate.hs +++ b/src/hevm/src/EVM/Mutate.hs @@ -18,14 +18,8 @@ import qualified Data.ListLike as LL -- | Given an 'AbiValue', generate a random \"similar\" value of the same 'AbiType'. mutateAbiValue :: AbiValue -> Gen AbiValue -mutateAbiValue (AbiUInt n x) = chooseInt (0, 9) >>= -- 10% of chance of mutation - \case - 0 -> fixAbiUInt n <$> mutateNum x - _ -> return $ AbiUInt n x -mutateAbiValue (AbiInt n x) = chooseInt (0, 9) >>= -- 10% of chance of mutation - \case - 0 -> fixAbiInt n <$> mutateNum x - _ -> return $ AbiInt n x +mutateAbiValue (AbiUInt n x) = frequency [(1, fixAbiUInt n <$> mutateNum x), (9, pure $ AbiUInt n x)] +mutateAbiValue (AbiInt n x) = frequency [(1, fixAbiInt n <$> mutateNum x), (9, pure $ AbiInt n x)] mutateAbiValue (AbiAddress x) = return $ AbiAddress x mutateAbiValue (AbiBool _) = genAbiValue AbiBoolType diff --git a/src/hevm/src/EVM/UnitTest.hs b/src/hevm/src/EVM/UnitTest.hs index 1f391e9e2..7b2c3accf 100644 --- a/src/hevm/src/EVM/UnitTest.hs +++ b/src/hevm/src/EVM/UnitTest.hs @@ -82,6 +82,7 @@ data UnitTestOptions = UnitTestOptions , vmModifier :: VM -> VM , dapp :: DappInfo , testParams :: TestVMParams + , mutations :: Int } data TestVMParams = TestVMParams @@ -103,6 +104,7 @@ data TestVMParams = TestVMParams } type Corpus = Map (MultiSet OpLocation) (SolcContract, Text, AbiValue) +data FuzzResult = Pass | Fail VM String defaultGasForCreating :: W256 defaultGasForCreating = 0xffffffffffff @@ -196,15 +198,12 @@ checkFailures UnitTestOptions { .. } method bailed = do -- | Either generates the calldata by mutating an example from the corpus, or synthesizes a random example genWithCorpus :: UnitTestOptions -> Corpus -> Text -> [AbiType] -> Gen AbiValue -genWithCorpus _ corpus sig tps = do - b <- arbitrary :: Gen Bool - if b then genAbiValue (AbiTupleType $ Vector.fromList tps) - else do - -- TODO: also check that the contract matches here - let examples = [cd | (_, sig', cd) <- (fmap snd) . Map.toList $ corpus, sig' == sig] - case examples of - [] -> genAbiValue (AbiTupleType $ Vector.fromList tps) - _ -> Test.QuickCheck.elements examples >>= mutateAbiValue +genWithCorpus UnitTestOptions { .. } corpus sig tps = do + -- TODO: also check that the contract matches here + let examples = [cd | (_, sig', cd) <- (fmap snd) . Map.toList $ corpus, sig' == sig] + if (null examples) + then genAbiValue (AbiTupleType $ Vector.fromList tps) + else frequency [(mutations, Test.QuickCheck.elements examples >>= mutateAbiValue), (100 - mutations, genAbiValue (AbiTupleType $ Vector.fromList tps))] -- | Randomly generates the calldata arguments and runs the test, updates the corpus with a new example if we explored a new path fuzzTest :: UnitTestOptions -> Text -> [AbiType] -> VM -> StateT Corpus IO FuzzResult @@ -482,8 +481,6 @@ runOne opts@UnitTestOptions{..} vm testName args = do , vm'' ) -data FuzzResult = Pass | Fail VM String - -- | Define the thread spawner for property based tests fuzzRun :: UnitTestOptions -> VM -> Text -> [AbiType] -> IO (Text, Either Text Text, VM) fuzzRun opts@UnitTestOptions{..} vm testName types = do From d58267ee5e868628ce5caba919cb3b812b704588 Mon Sep 17 00:00:00 2001 From: David Terry Date: Tue, 25 May 2021 19:53:59 +0200 Subject: [PATCH 04/21] hevm: UnitTest: rework representation of corpus to avoid an uneeded filter --- src/hevm/src/EVM/Solidity.hs | 8 ++++---- src/hevm/src/EVM/UnitTest.hs | 28 ++++++++++++++++------------ 2 files changed, 20 insertions(+), 16 deletions(-) diff --git a/src/hevm/src/EVM/Solidity.hs b/src/hevm/src/EVM/Solidity.hs index 2f29bae0d..ffe476ec9 100644 --- a/src/hevm/src/EVM/Solidity.hs +++ b/src/hevm/src/EVM/Solidity.hs @@ -97,7 +97,7 @@ data StorageItem = StorageItem { _type :: SlotType, _offset :: Int, _slot :: Int - } deriving (Show, Eq) + } deriving (Show, Eq, Ord) data SlotType -- Note that mapping keys can only be elementary; @@ -105,7 +105,7 @@ data SlotType = StorageMapping (NonEmpty AbiType) AbiType | StorageValue AbiType -- | StorageArray AbiType - deriving Eq + deriving (Eq, Ord) instance Show SlotType where show (StorageValue t) = show t @@ -141,7 +141,7 @@ data SolcContract = SolcContract , _storageLayout :: Maybe (Map Text StorageItem) , _runtimeSrcmap :: Seq SrcMap , _creationSrcmap :: Seq SrcMap - } deriving (Show, Eq, Generic) + } deriving (Show, Eq, Generic, Ord) data Method = Method { _methodOutput :: [(Text, AbiType)] @@ -159,7 +159,7 @@ data SourceCache = SourceCache data Reference = Reference { _refStart :: Int, _refLength :: Int - } deriving (Show, Eq) + } deriving (Show, Eq, Ord) instance FromJSON Reference where parseJSON (Object v) = Reference diff --git a/src/hevm/src/EVM/UnitTest.hs b/src/hevm/src/EVM/UnitTest.hs index 7b2c3accf..dcf8712b0 100644 --- a/src/hevm/src/EVM/UnitTest.hs +++ b/src/hevm/src/EVM/UnitTest.hs @@ -45,7 +45,7 @@ import Data.Decimal (DecimalRaw(..)) import Data.Either (isRight, lefts) import Data.Foldable (toList) import Data.Map (Map) -import Data.Maybe (fromMaybe, catMaybes, fromJust, isJust, isNothing, fromMaybe, mapMaybe) +import Data.Maybe (fromMaybe, catMaybes, fromJust, isJust, fromMaybe, mapMaybe) import Data.Text (isPrefixOf, stripSuffix, intercalate, Text, pack, unpack) import Data.Text.Encoding (encodeUtf8) import System.Environment (lookupEnv) @@ -103,7 +103,8 @@ data TestVMParams = TestVMParams , testChainId :: W256 } -type Corpus = Map (MultiSet OpLocation) (SolcContract, Text, AbiValue) +-- | For each tuple of (contract, method) we store the calldata required to reach each known path in the method +type Corpus = Map (SolcContract, Text) (Map (MultiSet OpLocation) AbiValue) data FuzzResult = Pass | Fail VM String defaultGasForCreating :: W256 @@ -197,23 +198,26 @@ checkFailures UnitTestOptions { .. } method bailed = do _ -> error "internal error: unexpected failure code" -- | Either generates the calldata by mutating an example from the corpus, or synthesizes a random example -genWithCorpus :: UnitTestOptions -> Corpus -> Text -> [AbiType] -> Gen AbiValue -genWithCorpus UnitTestOptions { .. } corpus sig tps = do +genWithCorpus :: UnitTestOptions -> Corpus -> SolcContract -> Text -> [AbiType] -> Gen AbiValue +genWithCorpus UnitTestOptions { .. } corpus contract' sig tps = do -- TODO: also check that the contract matches here - let examples = [cd | (_, sig', cd) <- (fmap snd) . Map.toList $ corpus, sig' == sig] - if (null examples) - then genAbiValue (AbiTupleType $ Vector.fromList tps) - else frequency [(mutations, Test.QuickCheck.elements examples >>= mutateAbiValue), (100 - mutations, genAbiValue (AbiTupleType $ Vector.fromList tps))] + --let examples = [cd | (_, sig', cd) <- (fmap snd) . Map.toList $ corpus, sig' == sig] + case Map.lookup (contract', sig) corpus of + Nothing -> genAbiValue (AbiTupleType $ Vector.fromList tps) + Just examples -> frequency + [ (mutations, Test.QuickCheck.elements (fmap snd $ Map.toList examples) >>= mutateAbiValue) + , (100 - mutations, genAbiValue (AbiTupleType $ Vector.fromList tps)) + ] -- | Randomly generates the calldata arguments and runs the test, updates the corpus with a new example if we explored a new path fuzzTest :: UnitTestOptions -> Text -> [AbiType] -> VM -> StateT Corpus IO FuzzResult fuzzTest opts@UnitTestOptions { .. } sig types vm = do + let code' = _contractcode . fromJust $ currentContract vm + contract' = fromJust $ lookupCode code' dapp corpus <- get - args <- liftIO . generate $ genWithCorpus opts corpus sig types + args <- liftIO . generate $ genWithCorpus opts corpus contract' sig types (res, (vm', coverage)) <- liftIO $ runStateT (interpretWithCoverage opts (runUnitTest opts sig args)) (vm, mempty) - let contract' = _contractcode . fromJust $ currentContract vm - code' = fromJust $ lookupCode contract' dapp - when (isNothing $ Map.lookup coverage corpus) $ modify (Map.insert coverage (code', sig, args)) + modify (Map.adjust (Map.insert coverage args) (contract', sig)) if res then pure Pass else pure $ Fail vm' (show . ByteStringS . encodeAbiValue $ args) From d6a62945b2d0fa3d8267de4c6fff6406b4129744 Mon Sep 17 00:00:00 2001 From: David Terry Date: Wed, 26 May 2021 14:51:12 +0200 Subject: [PATCH 05/21] hevm: attempt serialization of corpus --- src/hevm/hevm-cli/hevm-cli.hs | 24 ++++++-- src/hevm/src/EVM.hs | 8 +-- src/hevm/src/EVM/ABI.hs | 54 +++++++++++++++++- src/hevm/src/EVM/Dev.hs | 10 +++- src/hevm/src/EVM/Facts.hs | 13 +++-- src/hevm/src/EVM/Solidity.hs | 25 ++++++++- src/hevm/src/EVM/Types.hs | 21 ++++--- src/hevm/src/EVM/UnitTest.hs | 100 ++++++++++++++++++++++------------ 8 files changed, 193 insertions(+), 62 deletions(-) diff --git a/src/hevm/hevm-cli/hevm-cli.hs b/src/hevm/hevm-cli/hevm-cli.hs index f79fe6b5a..44ddd3a52 100644 --- a/src/hevm/hevm-cli/hevm-cli.hs +++ b/src/hevm/hevm-cli/hevm-cli.hs @@ -12,6 +12,7 @@ module Main where +import qualified Debug.Trace as Debug import EVM (StorageModel(..)) import qualified EVM import EVM.Concrete (createAddress, wordValue) @@ -36,11 +37,12 @@ import EVM.Types hiding (word) import EVM.UnitTest (UnitTestOptions, coverageReport, coverageForUnitTestContract) import EVM.UnitTest (runUnitTestContract) import EVM.UnitTest (getParametersFromEnvironmentVariables, testNumber) -import EVM.Dapp (findUnitTests, dappInfo, DappInfo, emptyDapp) +import EVM.Dapp (findUnitTests, dappInfo, DappInfo(..), emptyDapp) import EVM.Format (showTraceTree, showTree', renderTree, showBranchInfoWithAbi, showLeafInfo) import EVM.RLP (rlpdecode) import qualified EVM.Patricia as Patricia import Data.Map (Map) +import System.Directory (doesFileExist) import qualified EVM.Facts as Facts import qualified EVM.Facts.Git as Git @@ -50,7 +52,7 @@ import GHC.IO.Encoding import GHC.Stack import Control.Concurrent.Async (async, waitCatch) import Control.Lens hiding (pre, passing) -import Control.Monad (void, when, forM_, unless) +import Control.Monad (void, when, forM_, unless, foldM) import Control.Monad.State.Strict (execStateT, liftIO) import Data.ByteString (ByteString) import Data.List (intercalate, isSuffixOf) @@ -171,7 +173,8 @@ data Command w , debug :: w ::: Bool "Run interactively" , jsontrace :: w ::: Bool "Print json trace output at every step" , fuzzRuns :: w ::: Maybe Int "Number of times to run fuzz tests" - , mutations :: w ::: Maybe Int "Percentage of fuzz runs that should mutate a previous input vs randomly generating new inputs" + , mutations :: w ::: Maybe Int "Percentage of fuzz runs that should mutate a previous input vs randomly generating new inputs (default: 50)" + , corpus :: w ::: Maybe FilePath "Path to the location where the corpus of test inputs should be stored (default: .hevm.corpus)" , replay :: w ::: Maybe (Text, ByteString) "Custom fuzz case to run/debug" , rpc :: w ::: Maybe URL "Fetch state from a remote node" , verbose :: w ::: Maybe Int "Append call trace: {1} failures {2} all" @@ -292,6 +295,7 @@ unitTestOptions cmd testFile = do , EVM.UnitTest.vmModifier = vmModifier , EVM.UnitTest.testParams = params , EVM.UnitTest.dapp = srcInfo + , EVM.UnitTest.corpus = fromMaybe ".hevm.corpus" (corpus cmd) , EVM.UnitTest.mutations = case mutations cmd of Nothing -> 50 Just x -> if x > 100 @@ -385,10 +389,21 @@ findJsonFile Nothing = do dappTest :: UnitTestOptions -> String -> Maybe String -> Query () dappTest opts solcFile cache = do out <- liftIO $ readSolc solcFile + let dappInfo' = EVM.UnitTest.dapp opts + corpusPath = (_dappRoot dappInfo') <> "/" <> (EVM.UnitTest.corpus opts) + initalCorpus <- liftIO $ doesFileExist corpusPath >>= \case + True -> liftIO $ JSON.decodeFileStrict' corpusPath >>= \case + Nothing -> error "unable to parse corpus" + Just a -> pure a + False -> pure mempty + case out of Just (contractMap, _) -> do let unitTests = findUnitTests (EVM.UnitTest.match opts) $ Map.elems contractMap - results <- concatMapM (runUnitTestContract opts contractMap) unitTests + (finalCorpus, results) <- foldM (\(corpus, results) test -> do + (corpus', results') <- runUnitTestContract opts corpus contractMap test + pure (corpus', results <> results') + ) (initalCorpus, mempty) unitTests let (passing, vms) = unzip results case cache of Nothing -> @@ -400,6 +415,7 @@ dappTest opts solcFile cache = do in liftIO $ Git.saveFacts (Git.RepoAt path) (Facts.cacheFacts cache') + liftIO $ JSON.encodeFile (EVM.UnitTest.corpus opts) finalCorpus liftIO $ unless (and passing) exitFailure Nothing -> error ("Failed to read Solidity JSON for `" ++ solcFile ++ "'") diff --git a/src/hevm/src/EVM.hs b/src/hevm/src/EVM.hs index a0668e4d5..4122586c7 100644 --- a/src/hevm/src/EVM.hs +++ b/src/hevm/src/EVM.hs @@ -286,7 +286,7 @@ data SubState = SubState data ContractCode = InitCode Buffer -- ^ "Constructor" code, during contract creation | RuntimeCode Buffer -- ^ "Instance" code, after contract creation - deriving (Show) + deriving (Show, Generic) -- runtime err when used for symbolic code instance Eq ContractCode where @@ -436,14 +436,14 @@ currentContract vm = -- * Data constructors makeVm :: VMOpts -> VM -makeVm o = +makeVm o = let txaccessList = vmoptTxAccessList o txorigin = vmoptOrigin o txtoAddr = vmoptAddress o initialAccessedAddrs = fromList $ [txorigin, txtoAddr] ++ [1..9] ++ (Map.keys txaccessList) initialAccessedStorageKeys = fromList $ foldMap (uncurry (map . (,))) (Map.toList txaccessList) touched = if vmoptCreate o then [txorigin] else [txorigin, txtoAddr] - in + in VM { _result = Nothing , _frames = mempty @@ -2283,7 +2283,7 @@ finishFrame how = do -- In other words, we special case address 0x03 and keep it in the set of touched accounts during revert touched <- use (tx . substate . touchedAccounts) - + let substate'' = over touchedAccounts (maybe id cons (find ((==) 3) touched)) substate' revertContracts = assign (env . contracts) reversion diff --git a/src/hevm/src/EVM/ABI.hs b/src/hevm/src/EVM/ABI.hs index f04112ce0..d492aff32 100644 --- a/src/hevm/src/EVM/ABI.hs +++ b/src/hevm/src/EVM/ABI.hs @@ -63,10 +63,10 @@ import Data.Binary.Get (Get, runGet, runGetOrFail, label, getWord8, getWord32 import Data.Binary.Put (Put, runPut, putWord8, putWord32be) import Data.Bits (shiftL, shiftR, (.&.)) import Data.ByteString (ByteString) -import Data.DoubleWord (Word256, Int256, signedWord) +import Data.DoubleWord (Word256, Word128, Word160, Int128, Int256, signedWord) import Data.Functor (($>)) import Data.Text (Text, pack, unpack) -import Data.Text.Encoding (encodeUtf8, decodeUtf8') +import Data.Text.Encoding (encodeUtf8, decodeUtf8, decodeUtf8') import Data.Vector (Vector, toList) import Data.Word (Word32) import Data.List (intercalate) @@ -76,6 +76,7 @@ import GHC.Generics import Test.QuickCheck hiding ((.&.), label) import Text.ParserCombinators.ReadP import Control.Applicative +import Data.Aeson import qualified Data.ByteString as BS import qualified Data.ByteString.Char8 as Char8 @@ -99,6 +100,43 @@ data AbiValue | AbiTuple (Vector AbiValue) deriving (Read, Eq, Ord, Generic) +--instance ToJSON AbiValue where + --toJSON val = case val of + --AbiUInt n v -> object [ "size" .= n, "val" .= show v ] + --AbiInt n v -> object [ "size" .= n, "val" .= show v ] + --AbiAddress a -> toJSON a + --AbiBool b -> toJSON b + --AbiBytes n bs -> object [ "size" .= n, "val" .= show (ByteStringS bs) ] + --AbiBytesDynamic bs -> String . Text.pack . show . ByteStringS $ bs + --AbiString bs -> String . Text.pack . show . ByteStringS $ bs + --AbiArrayDynamic tp vs -> object [ "type" .= show tp, "values" .= toJSON vs ] + --AbiArray n tp vs -> object [ "size" .= n, "type" .= show tp, "values" .= toJSON vs ] + --AbiTuple vs -> toJSON vs + +--instance FromJSON AbiValue where + --parseJSON v = pure $ case v of + +instance ToJSON AbiValue +instance FromJSON AbiValue + +instance ToJSON Int256 +instance FromJSON Int256 + +instance ToJSON Int128 +instance FromJSON Int128 + +instance ToJSON Word256 +instance FromJSON Word256 + +instance ToJSON Word128 +instance FromJSON Word128 + +instance ToJSON ByteString where + toJSON b = toJSON (ByteStringS b) + +instance FromJSON ByteString where + parseJSON = withText "ByteString" $ pure . read . Text.unpack + -- | Pretty-print some 'AbiValue'. instance Show AbiValue where show (AbiUInt _ n) = show n @@ -134,6 +172,9 @@ data AbiType | AbiTupleType (Vector AbiType) deriving (Read, Eq, Ord, Generic) +instance ToJSON AbiType +instance FromJSON AbiType + instance Show AbiType where show = Text.unpack . abiTypeSolidity @@ -147,6 +188,15 @@ data Indexed = Indexed | NotIndexed data Event = Event Text Anonymity [(AbiType, Indexed)] deriving (Show, Ord, Eq, Generic) +instance ToJSON Anonymity +instance FromJSON Anonymity + +instance ToJSON Indexed +instance FromJSON Indexed + +instance ToJSON Event +instance FromJSON Event + abiKind :: AbiType -> AbiKind abiKind = \case AbiBytesDynamicType -> Dynamic diff --git a/src/hevm/src/EVM/Dev.hs b/src/hevm/src/EVM/Dev.hs index dec029f65..2c494c18e 100644 --- a/src/hevm/src/EVM/Dev.hs +++ b/src/hevm/src/EVM/Dev.hs @@ -26,6 +26,7 @@ import Options.Generic import Data.SBV.Trans.Control import Data.Maybe (fromMaybe) import Control.Monad.State.Strict (execStateT) +import Control.Monad (foldM) import qualified Data.Map as Map import qualified Data.ByteString.Lazy as LazyByteString @@ -72,12 +73,17 @@ ghciTest root path statePath = , vmModifier = loadFacts , dapp = emptyDapp , testParams = params + , mutations = 50 + , corpus = ".hevm.corpus" } readSolc path >>= \case Just (contractMap, _) -> do let unitTests = findAllUnitTests (Map.elems contractMap) - results <- runSMT $ query $ concatMapM (runUnitTestContract opts contractMap) unitTests + (_, results) <- runSMT $ query $ foldM (\(c, r) t -> do + (c', r') <- runUnitTestContract opts c contractMap t + pure (c', r <> r') + ) mempty unitTests let (passing, _) = unzip results pure passing @@ -129,6 +135,8 @@ ghciTty root path statePath = , vmModifier = loadFacts , dapp = emptyDapp , testParams = params + , mutations = 50 + , corpus = ".hevm.corpus" } EVM.TTY.main testOpts root path diff --git a/src/hevm/src/EVM/Facts.hs b/src/hevm/src/EVM/Facts.hs index 1974f67f9..f7da994d7 100644 --- a/src/hevm/src/EVM/Facts.hs +++ b/src/hevm/src/EVM/Facts.hs @@ -39,6 +39,7 @@ import EVM (VM, Contract, Cache) import EVM.Symbolic (litWord, forceLit) import EVM (balance, nonce, storage, bytecode, env, contracts, contract, state, cache, fetched) import EVM.Types (Addr, Word, SymWord, Buffer(..)) +import EVM.UnitTest (Corpus) import qualified EVM @@ -71,10 +72,10 @@ default (ASCII) -- Note that Haskell allows this kind of union of records. -- It's convenient here, but typically avoided. data Fact - = BalanceFact { addr :: Addr, what :: Word } - | NonceFact { addr :: Addr, what :: Word } - | StorageFact { addr :: Addr, what :: Word, which :: Word } - | CodeFact { addr :: Addr, blob :: ByteString } + = BalanceFact { addr :: Addr, what :: Word } + | NonceFact { addr :: Addr, what :: Word } + | StorageFact { addr :: Addr, what :: Word, which :: Word } + | CodeFact { addr :: Addr, blob :: ByteString } deriving (Eq, Show) -- A fact path means something like "/0123...abc/storage/0x1", @@ -113,13 +114,13 @@ instance AsASCII ByteString where contractFacts :: Addr -> Contract -> [Fact] contractFacts a x = case view bytecode x of - ConcreteBuffer b -> + ConcreteBuffer b -> storageFacts a x ++ [ BalanceFact a (view balance x) , NonceFact a (view nonce x) , CodeFact a b ] - SymbolicBuffer b -> + SymbolicBuffer _ -> -- here simply ignore storing the bytecode storageFacts a x ++ [ BalanceFact a (view balance x) diff --git a/src/hevm/src/EVM/Solidity.hs b/src/hevm/src/EVM/Solidity.hs index ffe476ec9..3e13c0a5f 100644 --- a/src/hevm/src/EVM/Solidity.hs +++ b/src/hevm/src/EVM/Solidity.hs @@ -97,7 +97,10 @@ data StorageItem = StorageItem { _type :: SlotType, _offset :: Int, _slot :: Int - } deriving (Show, Eq, Ord) + } deriving (Show, Eq, Ord, Generic) + +instance ToJSON StorageItem +instance FromJSON StorageItem data SlotType -- Note that mapping keys can only be elementary; @@ -105,7 +108,10 @@ data SlotType = StorageMapping (NonEmpty AbiType) AbiType | StorageValue AbiType -- | StorageArray AbiType - deriving (Eq, Ord) + deriving (Eq, Ord, Generic) + +instance ToJSON SlotType +instance FromJSON SlotType instance Show SlotType where show (StorageValue t) = show t @@ -143,6 +149,9 @@ data SolcContract = SolcContract , _creationSrcmap :: Seq SrcMap } deriving (Show, Eq, Generic, Ord) +instance ToJSON SolcContract +instance FromJSON SolcContract + data Method = Method { _methodOutput :: [(Text, AbiType)] , _methodInputs :: [(Text, AbiType)] @@ -150,6 +159,9 @@ data Method = Method , _methodSignature :: Text } deriving (Show, Eq, Ord, Generic) +instance ToJSON Method +instance FromJSON Method + data SourceCache = SourceCache { _sourceFiles :: [(Text, ByteString)] , _sourceLines :: [(Vector ByteString)] @@ -161,6 +173,9 @@ data Reference = Reference _refLength :: Int } deriving (Show, Eq, Ord) +instance ToJSON Reference where + toJSON (Reference start len) = object [ "start" .= start, "length" .= len ] + instance FromJSON Reference where parseJSON (Object v) = Reference <$> v .: "start" @@ -177,6 +192,9 @@ instance Monoid SourceCache where data JumpType = JumpInto | JumpFrom | JumpRegular deriving (Show, Eq, Ord, Generic) +instance ToJSON JumpType +instance FromJSON JumpType + data SrcMap = SM { srcMapOffset :: {-# UNPACK #-} Int, srcMapLength :: {-# UNPACK #-} Int, @@ -185,6 +203,9 @@ data SrcMap = SM { srcMapModifierDepth :: {-# UNPACK #-} Int } deriving (Show, Eq, Ord, Generic) +instance ToJSON SrcMap +instance FromJSON SrcMap + data SrcMapParseState = F1 String Int | F2 Int String Int diff --git a/src/hevm/src/EVM/Types.hs b/src/hevm/src/EVM/Types.hs index 9cdc48af4..eaf223179 100644 --- a/src/hevm/src/EVM/Types.hs +++ b/src/hevm/src/EVM/Types.hs @@ -138,6 +138,9 @@ instance Read ByteStringS where instance JSON.ToJSON ByteStringS where toJSON = JSON.String . Text.pack . show +instance JSON.FromJSON ByteStringS where + parseJSON = withText "ByteStringS" $ pure . read . Text.unpack + -- | Symbolic words of 256 bits, possibly annotated with additional -- "insightful" information data SymWord = S Whiff (SWord 256) @@ -269,6 +272,16 @@ instance Show Whiff where newtype Addr = Addr { addressWord160 :: Word160 } deriving (Num, Integral, Real, Ord, Enum, Eq, Bits, Generic) +instance ToJSON Addr where + toJSON = String . Text.pack . show + +instance FromJSON Addr where + parseJSON v = do + s <- Text.unpack <$> parseJSON v + case reads s of + [(x, "")] -> return x + _ -> fail $ "invalid address (" ++ s ++ ")" + newtype SAddr = SAddr { saddressWord160 :: SWord 160 } deriving (Num) @@ -349,6 +362,7 @@ instance Read W256 where instance Show W256 where showsPrec _ s = ("0x" ++) . showHex s +instance ToJSONKey W256 instance JSON.ToJSON W256 where toJSON = JSON.String . Text.pack . show @@ -387,13 +401,6 @@ instance FromJSON W256 where [(x, "")] -> return x _ -> fail $ "invalid hex word (" ++ s ++ ")" -instance FromJSON Addr where - parseJSON v = do - s <- Text.unpack <$> parseJSON v - case reads s of - [(x, "")] -> return x - _ -> fail $ "invalid address (" ++ s ++ ")" - #if MIN_VERSION_aeson(1, 0, 0) instance FromJSONKey W256 where diff --git a/src/hevm/src/EVM/UnitTest.hs b/src/hevm/src/EVM/UnitTest.hs index dcf8712b0..127d66455 100644 --- a/src/hevm/src/EVM/UnitTest.hs +++ b/src/hevm/src/EVM/UnitTest.hs @@ -1,9 +1,12 @@ {-# Language LambdaCase #-} {-# Language DataKinds #-} {-# Language ImplicitParams #-} +{-# LANGUAGE FlexibleInstances #-} module EVM.UnitTest where +import Debug.Trace + import Prelude hiding (Word) import EVM @@ -44,12 +47,13 @@ import Data.SBV.Control (CheckSatResult(..), checkSat) import Data.Decimal (DecimalRaw(..)) import Data.Either (isRight, lefts) import Data.Foldable (toList) -import Data.Map (Map) +import Data.Map hiding (mapMaybe, toList, map, filter, null, take) import Data.Maybe (fromMaybe, catMaybes, fromJust, isJust, fromMaybe, mapMaybe) import Data.Text (isPrefixOf, stripSuffix, intercalate, Text, pack, unpack) import Data.Text.Encoding (encodeUtf8) import System.Environment (lookupEnv) import System.IO (hFlush, stdout) +import GHC.Generics (Generic) import qualified Control.Monad.Par.Class as Par import qualified Data.ByteString as BS @@ -83,6 +87,7 @@ data UnitTestOptions = UnitTestOptions , dapp :: DappInfo , testParams :: TestVMParams , mutations :: Int + , corpus :: FilePath } data TestVMParams = TestVMParams @@ -104,7 +109,9 @@ data TestVMParams = TestVMParams } -- | For each tuple of (contract, method) we store the calldata required to reach each known path in the method -type Corpus = Map (SolcContract, Text) (Map (MultiSet OpLocation) AbiValue) +-- | The keys in the corpus are hashed to keep the size of the serialized representation manageable +type Corpus = Map W256 (Map W256 AbiValue) + data FuzzResult = Pass | Fail VM String defaultGasForCreating :: W256 @@ -199,28 +206,41 @@ checkFailures UnitTestOptions { .. } method bailed = do -- | Either generates the calldata by mutating an example from the corpus, or synthesizes a random example genWithCorpus :: UnitTestOptions -> Corpus -> SolcContract -> Text -> [AbiType] -> Gen AbiValue -genWithCorpus UnitTestOptions { .. } corpus contract' sig tps = do +genWithCorpus opts corpus contract' sig tps = do -- TODO: also check that the contract matches here - --let examples = [cd | (_, sig', cd) <- (fmap snd) . Map.toList $ corpus, sig' == sig] - case Map.lookup (contract', sig) corpus of + case Map.lookup (hashCall (contract', sig)) corpus of Nothing -> genAbiValue (AbiTupleType $ Vector.fromList tps) Just examples -> frequency - [ (mutations, Test.QuickCheck.elements (fmap snd $ Map.toList examples) >>= mutateAbiValue) - , (100 - mutations, genAbiValue (AbiTupleType $ Vector.fromList tps)) + [ (mutations opts, Test.QuickCheck.elements (Map.elems examples) >>= mutateAbiValue) + , (100 - (mutations opts), genAbiValue (AbiTupleType $ Vector.fromList tps)) ] -- | Randomly generates the calldata arguments and runs the test, updates the corpus with a new example if we explored a new path fuzzTest :: UnitTestOptions -> Text -> [AbiType] -> VM -> StateT Corpus IO FuzzResult -fuzzTest opts@UnitTestOptions { .. } sig types vm = do +fuzzTest opts sig types vm = do let code' = _contractcode . fromJust $ currentContract vm - contract' = fromJust $ lookupCode code' dapp + contract' = fromJust $ lookupCode code' (dapp opts) corpus <- get args <- liftIO . generate $ genWithCorpus opts corpus contract' sig types (res, (vm', coverage)) <- liftIO $ runStateT (interpretWithCoverage opts (runUnitTest opts sig args)) (vm, mempty) - modify (Map.adjust (Map.insert coverage args) (contract', sig)) + modify $ updateCorpus (hashCall (contract', sig)) (hashTrace coverage) args if res then pure Pass else pure $ Fail vm' (show . ByteStringS . encodeAbiValue $ args) + where + updateCorpus k1 k2 v c = case Map.lookup k1 c of + Nothing -> Map.insert k1 (Map.insert k2 v mempty) c + Just m' -> Map.insert k1 (Map.insert k2 v m') c + +hashCall :: (SolcContract, Text) -> W256 +hashCall (contract', sig) = keccak . encodeUtf8 $ + (Text.pack . show . _runtimeCodehash $ contract') <> (Text.pack . show . _creationCodehash $ contract') <> sig + +hashTrace :: MultiSet OpLocation -> W256 +hashTrace = keccak . encodeUtf8 . Text.pack . show . (fmap hashLoc) . MultiSet.toList + +hashLoc :: OpLocation -> W256 +hashLoc (OpLocation code ix) = keccak . encodeUtf8 . Text.pack $ (show code) <> (show ix) tick :: Text -> IO () tick x = Text.putStr x >> hFlush stdout @@ -229,7 +249,7 @@ tick x = Text.putStr x >> hFlush stdout data OpLocation = OpLocation { srcCode :: ContractCode , srcOpIx :: Int - } deriving (Show, Eq, Ord) + } deriving (Show, Eq, Ord, Generic) srcMapForOpLocation :: DappInfo -> OpLocation -> Maybe SrcMap srcMapForOpLocation dapp (OpLocation hash opIx) = srcMap dapp hash opIx @@ -379,11 +399,12 @@ coverageForUnitTestContract runUnitTestContract :: UnitTestOptions + -> Corpus -> Map Text SolcContract -> (Text, [(Test, [AbiType])]) - -> SBV.Query [(Bool, VM)] + -> SBV.Query (Corpus, [(Bool, VM)]) runUnitTestContract - opts@(UnitTestOptions {..}) contractMap (name, testSigs) = do + opts@(UnitTestOptions {..}) corpus' contractMap (name, testSigs) = do -- Print a header liftIO $ putStrLn $ "Running " ++ show (length testSigs) ++ " tests for " @@ -410,20 +431,20 @@ runUnitTestContract Text.putStrLn "\x1b[31m[BAIL]\x1b[0m setUp() " tick "\n" tick $ failOutput vm1 opts "setUp()" - pure [(False, vm1)] + pure (corpus', [(False, vm1)]) Just (VMSuccess _) -> do let - runCache :: ([(Either Text Text, VM)], VM) -> (Test, [AbiType]) - -> SBV.Query ([(Either Text Text, VM)], VM) - runCache (results, vm) (test, types) = do - (t, r, vm') <- runTest opts vm (test, types) + runCache :: ([(Either Text Text, VM)], VM, Corpus) -> (Test, [AbiType]) + -> SBV.Query ([(Either Text Text, VM)], VM, Corpus) + runCache (results, vm, corp) (test, types) = do + (t, r, vm', corp') <- runTest opts vm corp (test, types) liftIO $ Text.putStrLn t let vmCached = vm & set (cache . fetched) (view (cache . fetched) vm') - pure (((r, vm'): results), vmCached) + pure (((r, vm'): results), vmCached, corp') -- Run all the test cases and print their status updates, -- accumulating the vm cache throughout - (details, _) <- foldM runCache ([], vm1) testSigs + (details, _, finalCorpus) <- foldM runCache ([], vm1, corpus') testSigs let running = [x | (Right x, _) <- details] let bailing = [x | (Left x, _) <- details] @@ -433,20 +454,24 @@ runUnitTestContract tick (Text.unlines (filter (not . Text.null) running)) tick (Text.unlines (filter (not . Text.null) bailing)) - pure [(isRight r, vm) | (r, vm) <- details] + pure (finalCorpus, [(isRight r, vm) | (r, vm) <- details]) -runTest :: UnitTestOptions -> VM -> (Test, [AbiType]) -> SBV.Query (Text, Either Text Text, VM) -runTest opts@UnitTestOptions{..} vm (ConcreteTest testName, []) = liftIO $ runOne opts vm testName emptyAbi -runTest opts@UnitTestOptions{..} vm (ConcreteTest testName, types) = liftIO $ case replay of - Nothing -> - fuzzRun opts vm testName types +runTest :: UnitTestOptions -> VM -> Corpus -> (Test, [AbiType]) -> SBV.Query (Text, Either Text Text, VM, Corpus) +runTest opts@UnitTestOptions{..} vm corpus' (ConcreteTest testName, []) = do + (msg, verboseMsg, postvm) <- liftIO (runOne opts vm testName emptyAbi) + pure (msg, verboseMsg, postvm, corpus') +runTest opts@UnitTestOptions{..} vm corpus' (ConcreteTest testName, types) = liftIO $ case replay of + Nothing -> fuzzRun opts vm corpus' testName types Just (sig, callData) -> if sig == testName - then runOne opts vm testName $ - decodeAbiValue (AbiTupleType (Vector.fromList types)) callData - else fuzzRun opts vm testName types -runTest opts vm (SymbolicTest testName, types) = symRun opts vm testName types + then do + (msg, verboseMsg, postvm) <- runOne opts vm testName $ decodeAbiValue (AbiTupleType (Vector.fromList types)) callData + pure (msg, verboseMsg, postvm, corpus') + else fuzzRun opts vm corpus' testName types +runTest opts vm corpus' (SymbolicTest testName, types) = do + (msg, verboseMsg, postvm) <- symRun opts vm testName types + pure (msg, verboseMsg, postvm, corpus') -- | Define the thread spawner for normal test cases runOne :: UnitTestOptions -> VM -> ABIMethod -> AbiValue -> IO (Text, Either Text Text, VM) @@ -486,12 +511,13 @@ runOne opts@UnitTestOptions{..} vm testName args = do ) -- | Define the thread spawner for property based tests -fuzzRun :: UnitTestOptions -> VM -> Text -> [AbiType] -> IO (Text, Either Text Text, VM) -fuzzRun opts@UnitTestOptions{..} vm testName types = do - (res, _) <- foldM (\(res, corpus) _ -> case res of - Pass -> runStateT (fuzzTest opts testName types vm) corpus - Fail {} -> pure (res, corpus) - ) (Pass, mempty) [0..fuzzRuns] +fuzzRun :: UnitTestOptions -> VM -> Corpus -> Text -> [AbiType] -> IO (Text, Either Text Text, VM, Corpus) +fuzzRun opts@UnitTestOptions{..} vm corpus' testName types = do + + (res, finalCorpus) <- foldM (\(res, corp) _ -> case res of + Pass -> runStateT (fuzzTest opts testName types vm) corp + Fail {} -> pure (res, corp) + ) (Pass, corpus') [0..fuzzRuns] case res of (Pass) -> @@ -501,6 +527,7 @@ fuzzRun opts@UnitTestOptions{..} vm testName types = do -- can't retrieve the correct vm from quickcheck , Right (passOutput vm opts testName) , vm + , finalCorpus ) (Fail vm' cex) -> pure ("\x1b[31m[FAIL]\x1b[0m " @@ -510,6 +537,7 @@ fuzzRun opts@UnitTestOptions{..} vm testName types = do <> testName <> "\",\"" <> (pack cex) <> "\")'\nto debug it." , Left (failOutput vm' opts testName) , vm' + , finalCorpus ) where abiValue = decodeAbiValue (AbiTupleType (Vector.fromList types)) $ BSLazy.fromStrict $ hexText (pack cex) From e89fdd0a622894ebd1d523d0ad5244b608bea913 Mon Sep 17 00:00:00 2001 From: David Terry Date: Wed, 26 May 2021 15:29:11 +0200 Subject: [PATCH 06/21] hevm: UnitTest: skip hashing of traces before corpus insertion --- src/hevm/src/EVM.hs | 4 ++++ src/hevm/src/EVM/Types.hs | 7 +++++++ src/hevm/src/EVM/UnitTest.hs | 31 +++++++++++++++++++++++-------- 3 files changed, 34 insertions(+), 8 deletions(-) diff --git a/src/hevm/src/EVM.hs b/src/hevm/src/EVM.hs index 4122586c7..21149173a 100644 --- a/src/hevm/src/EVM.hs +++ b/src/hevm/src/EVM.hs @@ -30,6 +30,7 @@ import qualified EVM.Precompiled import Control.Lens hiding (op, (:<), (|>), (.>)) import Control.Monad.State.Strict hiding (state) +import Data.Aeson (ToJSON, FromJSON) import Data.ByteString (ByteString) import Data.ByteString.Lazy (fromStrict) import Data.Map.Strict (Map) @@ -288,6 +289,9 @@ data ContractCode | RuntimeCode Buffer -- ^ "Instance" code, after contract creation deriving (Show, Generic) +instance ToJSON ContractCode +instance FromJSON ContractCode + -- runtime err when used for symbolic code instance Eq ContractCode where (InitCode x) == (InitCode y) = forceBuffer x == forceBuffer y diff --git a/src/hevm/src/EVM/Types.hs b/src/hevm/src/EVM/Types.hs index eaf223179..9b58e8b9b 100644 --- a/src/hevm/src/EVM/Types.hs +++ b/src/hevm/src/EVM/Types.hs @@ -51,6 +51,13 @@ data Buffer = ConcreteBuffer ByteString | SymbolicBuffer [SWord 8] +instance ToJSON Buffer where + toJSON (ConcreteBuffer bs) = String . Text.pack . show . ByteStringS $ bs + toJSON (SymbolicBuffer _) = error "cannot serialize a symbolic buffer to JSON" + +instance FromJSON Buffer where + parseJSON = withText "Buffer" $ pure . ConcreteBuffer . read . Text.unpack + newtype W256 = W256 Word256 deriving ( Num, Integral, Real, Ord, Enum, Eq diff --git a/src/hevm/src/EVM/UnitTest.hs b/src/hevm/src/EVM/UnitTest.hs index 127d66455..60922e7ec 100644 --- a/src/hevm/src/EVM/UnitTest.hs +++ b/src/hevm/src/EVM/UnitTest.hs @@ -26,6 +26,9 @@ import qualified EVM.Fetch import qualified EVM.FeeSchedule as FeeSchedule +import Data.Aeson +import Data.Aeson.Types + import EVM.Stepper (Stepper, interpret) import qualified EVM.Stepper as Stepper import qualified Control.Monad.Operational as Operational @@ -110,7 +113,7 @@ data TestVMParams = TestVMParams -- | For each tuple of (contract, method) we store the calldata required to reach each known path in the method -- | The keys in the corpus are hashed to keep the size of the serialized representation manageable -type Corpus = Map W256 (Map W256 AbiValue) +type Corpus = Map W256 (Map (MultiSet OpLocation) AbiValue) data FuzzResult = Pass | Fail VM String @@ -223,7 +226,7 @@ fuzzTest opts sig types vm = do corpus <- get args <- liftIO . generate $ genWithCorpus opts corpus contract' sig types (res, (vm', coverage)) <- liftIO $ runStateT (interpretWithCoverage opts (runUnitTest opts sig args)) (vm, mempty) - modify $ updateCorpus (hashCall (contract', sig)) (hashTrace coverage) args + modify $ updateCorpus (hashCall (contract', sig)) coverage args if res then pure Pass else pure $ Fail vm' (show . ByteStringS . encodeAbiValue $ args) @@ -236,12 +239,6 @@ hashCall :: (SolcContract, Text) -> W256 hashCall (contract', sig) = keccak . encodeUtf8 $ (Text.pack . show . _runtimeCodehash $ contract') <> (Text.pack . show . _creationCodehash $ contract') <> sig -hashTrace :: MultiSet OpLocation -> W256 -hashTrace = keccak . encodeUtf8 . Text.pack . show . (fmap hashLoc) . MultiSet.toList - -hashLoc :: OpLocation -> W256 -hashLoc (OpLocation code ix) = keccak . encodeUtf8 . Text.pack $ (show code) <> (show ix) - tick :: Text -> IO () tick x = Text.putStr x >> hFlush stdout @@ -251,6 +248,24 @@ data OpLocation = OpLocation , srcOpIx :: Int } deriving (Show, Eq, Ord, Generic) +instance FromJSON OpLocation +instance FromJSONKey OpLocation +instance ToJSON OpLocation + +instance (Ord a, FromJSON a) => FromJSON (MultiSet a) where + parseJSON = fmap MultiSet.fromList . parseJSON + +instance ToJSON1 MultiSet where + liftToJSON t _ = listValue t . MultiSet.toList + liftToEncoding t _ = listEncoding t . MultiSet.toList + +instance (ToJSON a) => ToJSON (MultiSet a) where + toJSON = toJSON1 + toEncoding = toEncoding1 + +instance ToJSONKey (MultiSet OpLocation) +instance FromJSONKey (MultiSet OpLocation) + srcMapForOpLocation :: DappInfo -> OpLocation -> Maybe SrcMap srcMapForOpLocation dapp (OpLocation hash opIx) = srcMap dapp hash opIx From 17df0c4cacbb9ce24bfbcfe0b1aa9a0c1149360f Mon Sep 17 00:00:00 2001 From: David Terry Date: Wed, 26 May 2021 17:40:56 +0200 Subject: [PATCH 07/21] hevm: test: hlint + whitespace --- src/hevm/test/test.hs | 14 ++++++-------- 1 file changed, 6 insertions(+), 8 deletions(-) diff --git a/src/hevm/test/test.hs b/src/hevm/test/test.hs index b7689e794..95cc69f8b 100644 --- a/src/hevm/test/test.hs +++ b/src/hevm/test/test.hs @@ -3,7 +3,6 @@ {-# Language ScopedTypeVariables #-} {-# Language LambdaCase #-} {-# Language QuasiQuotes #-} -{-# Language TypeSynonymInstances #-} {-# Language FlexibleInstances #-} {-# Language GeneralizedNewtypeDeriving #-} {-# Language DataKinds #-} @@ -497,7 +496,7 @@ main = defaultMain $ testGroup "hevm" |] -- should find a counterexample Right _ <- runSMTWith cvc4 $ query $ fst <$> checkAssert c (Just ("f(uint256,uint256)", [AbiUIntType 256, AbiUIntType 256])) [] - putStrLn $ "found counterexample:" + putStrLn "found counterexample:" , @@ -529,7 +528,7 @@ main = defaultMain $ testGroup "hevm" (Map.insert aAddr (initialContract (RuntimeCode $ ConcreteBuffer a) & set EVM.storage (EVM.Symbolic [] store))) verify vm Nothing Nothing (Just checkAssertions) - putStrLn $ "found counterexample:" + putStrLn "found counterexample:" , testCase "calling unique contracts (read from storage)" $ do let code = @@ -553,7 +552,7 @@ main = defaultMain $ testGroup "hevm" vm0 <- abstractVM (Just ("call_A()", [])) [] c SymbolicS let vm = vm0 & set (state . callvalue) 0 verify vm Nothing Nothing (Just checkAssertions) - putStrLn $ "found counterexample:" + putStrLn "found counterexample:" , testCase "keccak concrete and sym agree" $ do @@ -572,14 +571,14 @@ main = defaultMain $ testGroup "hevm" vm0 <- abstractVM (Just ("kecc(uint256)", [AbiUIntType 256])) [] c SymbolicS let vm = vm0 & set (state . callvalue) 0 verify vm Nothing Nothing (Just checkAssertions) - putStrLn $ "found counterexample:" + putStrLn "found counterexample:" , testCase "safemath distributivity (yul)" $ do Left _ <- runSMTWith cvc4 $ query $ do let yulsafeDistributivity = hex "6355a79a6260003560e01c14156016576015601f565b5b60006000fd60a1565b603d602d604435600435607c565b6039602435600435607c565b605d565b6052604b604435602435605d565b600435607c565b141515605a57fe5b5b565b6000828201821115151560705760006000fd5b82820190505b92915050565b6000818384048302146000841417151560955760006000fd5b82820290505b92915050565b" vm <- abstractVM (Just ("distributivity(uint256,uint256,uint256)", [AbiUIntType 256, AbiUIntType 256, AbiUIntType 256])) [] yulsafeDistributivity SymbolicS verify vm Nothing Nothing (Just checkAssertions) - putStrLn $ "Proven" + putStrLn "Proven" , testCase "safemath distributivity (sol)" $ do let code = @@ -602,7 +601,7 @@ main = defaultMain $ testGroup "hevm" Left _ <- runSMTWith z3 $ query $ do vm <- abstractVM (Just ("distributivity(uint256,uint256,uint256)", [AbiUIntType 256, AbiUIntType 256, AbiUIntType 256])) [] c SymbolicS verify vm Nothing Nothing (Just checkAssertions) - putStrLn $ "Proven" + putStrLn "Proven" ] , testGroup "Equivalence checking" @@ -753,4 +752,3 @@ bothM f (a, a') = do b <- f a b' <- f a' return (b, b') - From 45580b71ea43b911a7005aea2788087589cac1f2 Mon Sep 17 00:00:00 2001 From: David Terry Date: Wed, 26 May 2021 17:42:26 +0200 Subject: [PATCH 08/21] hevm: test: compiler warnings --- src/hevm/test/test.hs | 14 +++++++------- 1 file changed, 7 insertions(+), 7 deletions(-) diff --git a/src/hevm/test/test.hs b/src/hevm/test/test.hs index 95cc69f8b..d957b36d2 100644 --- a/src/hevm/test/test.hs +++ b/src/hevm/test/test.hs @@ -17,7 +17,7 @@ import Prelude hiding (fail) import qualified Data.Text as Text import qualified Data.ByteString as BS -import qualified Data.ByteString.Lazy as BS (fromStrict, toStrict) +import qualified Data.ByteString.Lazy as BS (fromStrict) import qualified Data.ByteString.Base16 as Hex import Test.Tasty import Test.Tasty.QuickCheck @@ -37,14 +37,14 @@ import Data.SBV.Control import qualified Data.Map as Map import Data.Binary.Get (runGetOrFail) -import EVM hiding (Query) +import EVM hiding (Query, code, path) import EVM.SymExec import EVM.ABI import EVM.Exec import qualified EVM.Patricia as Patricia import EVM.Precompiled import EVM.RLP -import EVM.Solidity +import EVM.Solidity hiding (solc) import EVM.Types instance MonadFail Query where @@ -319,7 +319,7 @@ main = defaultMain $ testGroup "hevm" (Right _, vm) <- verifyContract c (Just ("f(uint256,uint256)", [AbiUIntType 256, AbiUIntType 256])) [] SymbolicS pre (Just post) case view (state . calldata . _1) vm of SymbolicBuffer bs -> BS.pack <$> mapM (getValue.fromSized) bs - ConcreteBuffer bs -> error "unexpected" + ConcreteBuffer _ -> error "unexpected" let [AbiUInt 256 x, AbiUInt 256 y] = decodeAbiValues [AbiUIntType 256, AbiUIntType 256] bs assertEqual "Catch storage collisions" x y @@ -519,7 +519,7 @@ main = defaultMain $ testGroup "hevm" aAddr = Addr 0x35D1b3F3D7966A1DFe207aa4514C12a259A0492B Just c <- solcRuntime "C" code Just a <- solcRuntime "A" code - Right cex <- runSMT $ query $ do + Right _ <- runSMT $ query $ do vm0 <- abstractVM (Just ("call_A()", [])) [] c SymbolicS store <- freshArray (show aAddr) Nothing let vm = vm0 @@ -548,7 +548,7 @@ main = defaultMain $ testGroup "hevm" } |] Just c <- solcRuntime "C" code - Right cex <- runSMT $ query $ do + Right _ <- runSMT $ query $ do vm0 <- abstractVM (Just ("call_A()", [])) [] c SymbolicS let vm = vm0 & set (state . callvalue) 0 verify vm Nothing Nothing (Just checkAssertions) @@ -619,7 +619,7 @@ main = defaultMain $ testGroup "hevm" let aPrgm = hex "602060006000376000805160008114601d5760018114602457fe6029565b8191506029565b600191505b50600160015250" bPrgm = hex "6020600060003760005160008114601c5760028114602057fe6021565b6021565b5b506001600152" runSMTWith z3 $ query $ do - Right counterexample <- equivalenceCheck aPrgm bPrgm Nothing Nothing + Right _ <- equivalenceCheck aPrgm bPrgm Nothing Nothing return () ] From 5fc658f1feed6c688ef72406455c07d9a58a277b Mon Sep 17 00:00:00 2001 From: David Terry Date: Thu, 27 May 2021 09:45:11 +0200 Subject: [PATCH 09/21] hevm: test: test json serialization / deserialization routines --- src/hevm/hevm.cabal | 1 + src/hevm/src/EVM/ABI.hs | 3 ++- src/hevm/test/test.hs | 15 +++++++++++++++ 3 files changed, 18 insertions(+), 1 deletion(-) diff --git a/src/hevm/hevm.cabal b/src/hevm/hevm.cabal index a984fc6f6..74137d401 100644 --- a/src/hevm/hevm.cabal +++ b/src/hevm/hevm.cabal @@ -211,6 +211,7 @@ test-suite test secp256k1 build-depends: HUnit >= 1.6, + aeson, QuickCheck, base, base16-bytestring, diff --git a/src/hevm/src/EVM/ABI.hs b/src/hevm/src/EVM/ABI.hs index d492aff32..33525ecd5 100644 --- a/src/hevm/src/EVM/ABI.hs +++ b/src/hevm/src/EVM/ABI.hs @@ -132,7 +132,7 @@ instance ToJSON Word128 instance FromJSON Word128 instance ToJSON ByteString where - toJSON b = toJSON (ByteStringS b) + toJSON = String . Text.pack . show instance FromJSON ByteString where parseJSON = withText "ByteString" $ pure . read . Text.unpack @@ -175,6 +175,7 @@ data AbiType instance ToJSON AbiType instance FromJSON AbiType + instance Show AbiType where show = Text.unpack . abiTypeSolidity diff --git a/src/hevm/test/test.hs b/src/hevm/test/test.hs index d957b36d2..b52575a14 100644 --- a/src/hevm/test/test.hs +++ b/src/hevm/test/test.hs @@ -10,6 +10,8 @@ module Main where +import Debug.Trace + import Data.Text (Text) import Data.ByteString (ByteString) @@ -37,6 +39,8 @@ import Data.SBV.Control import qualified Data.Map as Map import Data.Binary.Get (runGetOrFail) +import Data.Aeson (fromJSON, toJSON, Result(..)) + import EVM hiding (Query, code, path) import EVM.SymExec import EVM.ABI @@ -95,6 +99,17 @@ main = defaultMain $ testGroup "hevm" -- traceM ("encoded (hevm): " ++ show (AbiBytesDynamic hevmEncoded)) assertEqual "abi encoding mismatch" solidityEncoded (AbiBytesDynamic hevmEncoded) ] + , testGroup "Corpus Serialization" + [ testProperty "AbiValue" $ forAll (arbitrary >>= genAbiValue) $ + \val -> case (fromJSON . toJSON $ val) of + Error _ -> False + Data.Aeson.Success v -> val == v + , testPropery "MultiSet" $ do + + + + assertFailure "whoops" + ] , testGroup "Precompiled contracts" [ testGroup "Example (reverse)" From 85c495f3198680b239988d1004e81ea7c89c3e97 Mon Sep 17 00:00:00 2001 From: David Terry Date: Thu, 27 May 2021 12:06:16 +0200 Subject: [PATCH 10/21] hevm: fix & test corpus serialization --- src/hevm/hevm.cabal | 3 +- src/hevm/src/EVM.hs | 14 ++++++--- src/hevm/src/EVM/ABI.hs | 5 ++++ src/hevm/src/EVM/Types.hs | 21 ++++++++++++-- src/hevm/src/EVM/UnitTest.hs | 15 ++++++++++ src/hevm/test/test.hs | 55 +++++++++++++++++++++++++++++++++--- 6 files changed, 102 insertions(+), 11 deletions(-) diff --git a/src/hevm/hevm.cabal b/src/hevm/hevm.cabal index 74137d401..9e71b7513 100644 --- a/src/hevm/hevm.cabal +++ b/src/hevm/hevm.cabal @@ -211,8 +211,9 @@ test-suite test secp256k1 build-depends: HUnit >= 1.6, - aeson, QuickCheck, + aeson, + multiset, base, base16-bytestring, binary, diff --git a/src/hevm/src/EVM.hs b/src/hevm/src/EVM.hs index 21149173a..0137a73ad 100644 --- a/src/hevm/src/EVM.hs +++ b/src/hevm/src/EVM.hs @@ -27,7 +27,7 @@ import EVM.FeeSchedule (FeeSchedule (..)) import Options.Generic as Options import qualified EVM.Precompiled -import Control.Lens hiding (op, (:<), (|>), (.>)) +import Control.Lens hiding (op, (:<), (|>), (.>), elements) import Control.Monad.State.Strict hiding (state) import Data.Aeson (ToJSON, FromJSON) @@ -39,6 +39,7 @@ import Data.Maybe (fromMaybe) import Data.Sequence (Seq) import Data.Vector.Storable (Vector) import Data.Foldable (toList) +import Test.QuickCheck (Arbitrary(..), elements) import Data.Tree import Data.List (find) @@ -289,6 +290,11 @@ data ContractCode | RuntimeCode Buffer -- ^ "Instance" code, after contract creation deriving (Show, Generic) +instance Arbitrary ContractCode where + arbitrary = do + buf <- arbitrary + elements [InitCode buf, RuntimeCode buf] + instance ToJSON ContractCode instance FromJSON ContractCode @@ -1590,8 +1596,8 @@ makeUnique sw@(S w val) cont = case maybeLitWord sw of Unique a -> do assign result Nothing cont (C w $ fromSizzle a) - InconsistentU -> vmError $ DeadPath - TimeoutU -> vmError $ SMTTimeout + InconsistentU -> vmError DeadPath + TimeoutU -> vmError SMTTimeout Multiple -> vmError $ NotUnique w Just a -> cont a @@ -2127,7 +2133,7 @@ create self this xGas' xValue xs newAddr initCode = do then do assign (state . stack) (0 : xs) assign (state . returndata) mempty - pushTrace $ ErrorTrace $ CallDepthLimitReached + pushTrace $ ErrorTrace CallDepthLimitReached next else if collision $ view (env . contracts . at newAddr) vm0 then burn xGas $ do diff --git a/src/hevm/src/EVM/ABI.hs b/src/hevm/src/EVM/ABI.hs index 33525ecd5..d2204353c 100644 --- a/src/hevm/src/EVM/ABI.hs +++ b/src/hevm/src/EVM/ABI.hs @@ -137,6 +137,11 @@ instance ToJSON ByteString where instance FromJSON ByteString where parseJSON = withText "ByteString" $ pure . read . Text.unpack +instance Arbitrary ByteString where + arbitrary = do + s <- arbitrary + pure $ encodeUtf8 . pack $ s + -- | Pretty-print some 'AbiValue'. instance Show AbiValue where show (AbiUInt _ n) = show n diff --git a/src/hevm/src/EVM/Types.hs b/src/hevm/src/EVM/Types.hs index 9b58e8b9b..8c3328383 100644 --- a/src/hevm/src/EVM/Types.hs +++ b/src/hevm/src/EVM/Types.hs @@ -29,6 +29,7 @@ import Data.Maybe (fromMaybe) import Numeric (readHex, showHex) import Options.Generic import Control.Arrow ((>>>)) +import Test.QuickCheck (Arbitrary(..), chooseInteger) import qualified Data.ByteArray as BA import qualified Data.Aeson as JSON @@ -37,6 +38,7 @@ import qualified Data.ByteString as BS import qualified Data.Serialize.Get as Cereal import qualified Data.Text as Text import qualified Data.Text.Encoding as Text +import qualified Data.ByteString.Builder as B import qualified Text.Read -- Some stuff for "generic programming", needed to create Word512 @@ -51,8 +53,13 @@ data Buffer = ConcreteBuffer ByteString | SymbolicBuffer [SWord 8] +instance Arbitrary Buffer where + arbitrary = do + contents <- arbitrary + pure $ ConcreteBuffer (Text.encodeUtf8 . Text.pack $ contents) + instance ToJSON Buffer where - toJSON (ConcreteBuffer bs) = String . Text.pack . show . ByteStringS $ bs + toJSON (ConcreteBuffer bs) = String . Text.pack . show $ bs toJSON (SymbolicBuffer _) = error "cannot serialize a symbolic buffer to JSON" instance FromJSON Buffer where @@ -64,6 +71,11 @@ newtype W256 = W256 Word256 , Bits, FiniteBits, Bounded, Generic ) +instance Arbitrary W256 where + arbitrary = do + v <- chooseInteger (0, 2 ^ (256 :: Integer)) + pure $ W256 (fromInteger v) + data Word = C Whiff W256 --maybe to remove completely in the future instance Show Word where @@ -369,7 +381,12 @@ instance Read W256 where instance Show W256 where showsPrec _ s = ("0x" ++) . showHex s -instance ToJSONKey W256 +instance ToJSONKey W256 where + toJSONKey = JSON.toJSONKeyText w256Text + +w256Text :: W256 -> Text +w256Text = Text.pack . show + instance JSON.ToJSON W256 where toJSON = JSON.String . Text.pack . show diff --git a/src/hevm/src/EVM/UnitTest.hs b/src/hevm/src/EVM/UnitTest.hs index 60922e7ec..0202a1a89 100644 --- a/src/hevm/src/EVM/UnitTest.hs +++ b/src/hevm/src/EVM/UnitTest.hs @@ -115,6 +115,11 @@ data TestVMParams = TestVMParams -- | The keys in the corpus are hashed to keep the size of the serialized representation manageable type Corpus = Map W256 (Map (MultiSet OpLocation) AbiValue) +instance Arbitrary (MultiSet OpLocation) where + arbitrary = do + coverage <- listOf (arbitrary :: Gen OpLocation) + pure $ MultiSet.fromList coverage + data FuzzResult = Pass | Fail VM String defaultGasForCreating :: W256 @@ -248,6 +253,16 @@ data OpLocation = OpLocation , srcOpIx :: Int } deriving (Show, Eq, Ord, Generic) +instance Arbitrary OpLocation where + arbitrary = do + src <- arbitrary :: Gen ContractCode + opIx <- chooseInt (0, codesize src) + pure $ OpLocation src opIx + where + codesize (InitCode (ConcreteBuffer c)) = BS.length c + codesize (RuntimeCode (ConcreteBuffer c)) = BS.length c + codesize _ = error "cannot compute length for symbolic bytecode" + instance FromJSON OpLocation instance FromJSONKey OpLocation instance ToJSON OpLocation diff --git a/src/hevm/test/test.hs b/src/hevm/test/test.hs index b52575a14..c58c53038 100644 --- a/src/hevm/test/test.hs +++ b/src/hevm/test/test.hs @@ -38,6 +38,7 @@ import Data.SBV hiding ((===), forAll, sList) import Data.SBV.Control import qualified Data.Map as Map import Data.Binary.Get (runGetOrFail) +import Data.MultiSet (MultiSet) import Data.Aeson (fromJSON, toJSON, Result(..)) @@ -50,6 +51,7 @@ import EVM.Precompiled import EVM.RLP import EVM.Solidity hiding (solc) import EVM.Types +import EVM.UnitTest instance MonadFail Query where fail = io . fail @@ -99,16 +101,61 @@ main = defaultMain $ testGroup "hevm" -- traceM ("encoded (hevm): " ++ show (AbiBytesDynamic hevmEncoded)) assertEqual "abi encoding mismatch" solidityEncoded (AbiBytesDynamic hevmEncoded) ] + , testGroup "Corpus Serialization" - [ testProperty "AbiValue" $ forAll (arbitrary >>= genAbiValue) $ - \val -> case (fromJSON . toJSON $ val) of + + [ testProperty "AbiValue" $ do + val <- arbitrary :: Gen AbiValue + pure $ case (fromJSON . toJSON $ val) of + Error _ -> False + Data.Aeson.Success v -> val == v + + , testProperty "ByteString" $ do + val <- arbitrary :: Gen ByteString + pure $ case (fromJSON . toJSON $ val) of Error _ -> False Data.Aeson.Success v -> val == v - , testPropery "MultiSet" $ do + , testProperty "OpLocation" $ do + val <- arbitrary :: Gen OpLocation + pure $ case (fromJSON . toJSON $ val) of + Error _ -> False + Data.Aeson.Success v -> val == v + + , testProperty "MultiSet OpLocation" $ do + val <- arbitrary :: Gen (MultiSet OpLocation) + pure $ case (fromJSON . toJSON $ val) of + Error _ -> False + Data.Aeson.Success v -> val == v + + , testProperty "W256" $ do + val <- arbitrary :: Gen W256 + pure $ case (fromJSON . toJSON $ val) of + Error _ -> False + Data.Aeson.Success v -> val == v + + , testProperty "Corpus" $ withMaxSuccess 20 $ do + val <- arbitrary :: Gen Corpus + pure $ case (fromJSON . toJSON $ val) of + Error _ -> False + Data.Aeson.Success v -> val == v + + --, testProperty "Debuggg" $ do + --src <- arbitrary :: Gen Corpus + + --let json = toJSON (trace ("src: " <> show src) src) + + --let res = fromJSON (trace ("json: " <> show json) json) + --pure $ case trace ("res: " <> show res) res of + --Error _ -> False + --Data.Aeson.Success v -> v == src - assertFailure "whoops" + --, testProperty "Corpus" $ do + --corpus' <- arbitrary :: Gen Corpus + --pure $ case (fromJSON . toJSON $ corpus') of + --Error _ -> False + --Data.Aeson.Success v -> v == corpus' ] , testGroup "Precompiled contracts" From f97d2560ffd7fc187f40ca749819e5e316ea8a99 Mon Sep 17 00:00:00 2001 From: David Terry Date: Thu, 27 May 2021 12:42:10 +0200 Subject: [PATCH 11/21] hevm: fix nix build --- src/hevm/hevm.cabal | 4 ++-- src/hevm/src/EVM/ABI.hs | 18 +----------------- src/hevm/src/EVM/Mutate.hs | 14 +++++++------- src/hevm/src/EVM/Types.hs | 4 ++-- src/hevm/src/EVM/UnitTest.hs | 2 +- src/hevm/test/test.hs | 17 ----------------- 6 files changed, 13 insertions(+), 46 deletions(-) diff --git a/src/hevm/hevm.cabal b/src/hevm/hevm.cabal index 9e71b7513..a1074145f 100644 --- a/src/hevm/hevm.cabal +++ b/src/hevm/hevm.cabal @@ -81,7 +81,7 @@ library install-includes: ethjet/tinykeccak.h, ethjet/ethjet.h, ethjet/ethjet-ff.h, ethjet/blake2.h build-depends: - QuickCheck >= 2.14.2 && < 2.15, + QuickCheck >= 2.13.2 && < 2.14, Decimal == 0.5.1, containers >= 0.6.0 && < 0.7, deepseq >= 1.4.4 && < 1.5, @@ -130,7 +130,7 @@ library wreq >= 0.5.3 && < 0.6, regex-tdfa >= 1.2.3 && < 1.4, base >= 4.9 && < 5, - ListLike >= 4.7.4 && < 4.8 + ListLike >= 4.7.2 && < 4.8 hs-source-dirs: src default-language: diff --git a/src/hevm/src/EVM/ABI.hs b/src/hevm/src/EVM/ABI.hs index d2204353c..4e9a36708 100644 --- a/src/hevm/src/EVM/ABI.hs +++ b/src/hevm/src/EVM/ABI.hs @@ -66,7 +66,7 @@ import Data.ByteString (ByteString) import Data.DoubleWord (Word256, Word128, Word160, Int128, Int256, signedWord) import Data.Functor (($>)) import Data.Text (Text, pack, unpack) -import Data.Text.Encoding (encodeUtf8, decodeUtf8, decodeUtf8') +import Data.Text.Encoding (encodeUtf8, decodeUtf8') import Data.Vector (Vector, toList) import Data.Word (Word32) import Data.List (intercalate) @@ -100,22 +100,6 @@ data AbiValue | AbiTuple (Vector AbiValue) deriving (Read, Eq, Ord, Generic) ---instance ToJSON AbiValue where - --toJSON val = case val of - --AbiUInt n v -> object [ "size" .= n, "val" .= show v ] - --AbiInt n v -> object [ "size" .= n, "val" .= show v ] - --AbiAddress a -> toJSON a - --AbiBool b -> toJSON b - --AbiBytes n bs -> object [ "size" .= n, "val" .= show (ByteStringS bs) ] - --AbiBytesDynamic bs -> String . Text.pack . show . ByteStringS $ bs - --AbiString bs -> String . Text.pack . show . ByteStringS $ bs - --AbiArrayDynamic tp vs -> object [ "type" .= show tp, "values" .= toJSON vs ] - --AbiArray n tp vs -> object [ "size" .= n, "type" .= show tp, "values" .= toJSON vs ] - --AbiTuple vs -> toJSON vs - ---instance FromJSON AbiValue where - --parseJSON v = pure $ case v of - instance ToJSON AbiValue instance FromJSON AbiValue diff --git a/src/hevm/src/EVM/Mutate.hs b/src/hevm/src/EVM/Mutate.hs index 1e66312eb..671a02ad6 100644 --- a/src/hevm/src/EVM/Mutate.hs +++ b/src/hevm/src/EVM/Mutate.hs @@ -5,7 +5,7 @@ module EVM.Mutate where import Data.Bifunctor (second) import Data.Bool (bool) -import Test.QuickCheck.Gen (Gen, chooseInt, chooseInteger, frequency) +import Test.QuickCheck.Gen (Gen, choose, frequency) import Data.DoubleWord (Int256, Word256) import Test.QuickCheck.Arbitrary (arbitrary) @@ -58,8 +58,8 @@ expandRandList xs | l == 0 = return xs | l >= 32 = return xs | otherwise = do - k <- chooseInt (0, l - 1) - t <- chooseInt (1, min 32 l) + k <- choose (0, l - 1) + t <- choose (1, min 32 l) return $ expandAt xs k t where l = LL.length xs @@ -77,7 +77,7 @@ deleteRandList xs = if LL.null xs then return xs else do - k <- chooseInt (0, LL.length xs - 1) + k <- choose (0, LL.length xs - 1) return $ deleteAt k xs deleteAt :: LL.ListLike f i => Int -> f -> f @@ -89,8 +89,8 @@ swapRandList xs = if LL.null xs then return xs else do - i <- chooseInt (0, LL.length xs - 1) - j <- chooseInt (0, LL.length xs - 1) + i <- choose (0, LL.length xs - 1) + j <- choose (0, LL.length xs - 1) return $ if i == j then xs else swapAt xs (min i j) (max i j) -- taken from https://stackoverflow.com/questions/30551033/swap-two-elements-in-a-list-by-its-indices/30551130#30551130 @@ -105,7 +105,7 @@ swapAt xs i j = left <> LL.cons elemJ middle <> LL.cons elemI right -- | Given an 'Integral' number n, get a random number in [0,2n]. mutateNum :: Integral a => a -> Gen a -mutateNum x = bool (x +) (x -) <$> arbitrary <*> (fromInteger <$> (chooseInteger (0, toInteger x))) +mutateNum x = bool (x +) (x -) <$> arbitrary <*> (fromInteger <$> (choose (0, toInteger x))) -- | Force `x` to be in the range of a uint of size `n` fixAbiUInt :: Int -> Word256 -> AbiValue diff --git a/src/hevm/src/EVM/Types.hs b/src/hevm/src/EVM/Types.hs index 8c3328383..6fa9728e3 100644 --- a/src/hevm/src/EVM/Types.hs +++ b/src/hevm/src/EVM/Types.hs @@ -29,7 +29,7 @@ import Data.Maybe (fromMaybe) import Numeric (readHex, showHex) import Options.Generic import Control.Arrow ((>>>)) -import Test.QuickCheck (Arbitrary(..), chooseInteger) +import Test.QuickCheck (Arbitrary(..), choose) import qualified Data.ByteArray as BA import qualified Data.Aeson as JSON @@ -73,7 +73,7 @@ newtype W256 = W256 Word256 instance Arbitrary W256 where arbitrary = do - v <- chooseInteger (0, 2 ^ (256 :: Integer)) + v <- choose (0, 2 ^ (256 :: Integer)) pure $ W256 (fromInteger v) data Word = C Whiff W256 --maybe to remove completely in the future diff --git a/src/hevm/src/EVM/UnitTest.hs b/src/hevm/src/EVM/UnitTest.hs index 0202a1a89..b11b9596d 100644 --- a/src/hevm/src/EVM/UnitTest.hs +++ b/src/hevm/src/EVM/UnitTest.hs @@ -256,7 +256,7 @@ data OpLocation = OpLocation instance Arbitrary OpLocation where arbitrary = do src <- arbitrary :: Gen ContractCode - opIx <- chooseInt (0, codesize src) + opIx <- choose (0, codesize src) pure $ OpLocation src opIx where codesize (InitCode (ConcreteBuffer c)) = BS.length c diff --git a/src/hevm/test/test.hs b/src/hevm/test/test.hs index c58c53038..65daab40b 100644 --- a/src/hevm/test/test.hs +++ b/src/hevm/test/test.hs @@ -139,23 +139,6 @@ main = defaultMain $ testGroup "hevm" pure $ case (fromJSON . toJSON $ val) of Error _ -> False Data.Aeson.Success v -> val == v - - --, testProperty "Debuggg" $ do - --src <- arbitrary :: Gen Corpus - - --let json = toJSON (trace ("src: " <> show src) src) - - --let res = fromJSON (trace ("json: " <> show json) json) - - --pure $ case trace ("res: " <> show res) res of - --Error _ -> False - --Data.Aeson.Success v -> v == src - - --, testProperty "Corpus" $ do - --corpus' <- arbitrary :: Gen Corpus - --pure $ case (fromJSON . toJSON $ corpus') of - --Error _ -> False - --Data.Aeson.Success v -> v == corpus' ] , testGroup "Precompiled contracts" From d42bafbc476478644c9fbdf32ca845f19af93d99 Mon Sep 17 00:00:00 2001 From: David Terry Date: Thu, 27 May 2021 15:46:02 +0200 Subject: [PATCH 12/21] hevm: UnitTest: reduce on disk corpus size --- src/hevm/src/EVM/UnitTest.hs | 40 ++++++++++++------------------------ src/hevm/test/test.hs | 12 ----------- 2 files changed, 13 insertions(+), 39 deletions(-) diff --git a/src/hevm/src/EVM/UnitTest.hs b/src/hevm/src/EVM/UnitTest.hs index b11b9596d..2abcbeefe 100644 --- a/src/hevm/src/EVM/UnitTest.hs +++ b/src/hevm/src/EVM/UnitTest.hs @@ -5,8 +5,6 @@ module EVM.UnitTest where -import Debug.Trace - import Prelude hiding (Word) import EVM @@ -113,7 +111,7 @@ data TestVMParams = TestVMParams -- | For each tuple of (contract, method) we store the calldata required to reach each known path in the method -- | The keys in the corpus are hashed to keep the size of the serialized representation manageable -type Corpus = Map W256 (Map (MultiSet OpLocation) AbiValue) +type Corpus = Map W256 (Map W256 AbiValue) instance Arbitrary (MultiSet OpLocation) where arbitrary = do @@ -231,7 +229,7 @@ fuzzTest opts sig types vm = do corpus <- get args <- liftIO . generate $ genWithCorpus opts corpus contract' sig types (res, (vm', coverage)) <- liftIO $ runStateT (interpretWithCoverage opts (runUnitTest opts sig args)) (vm, mempty) - modify $ updateCorpus (hashCall (contract', sig)) coverage args + modify $ updateCorpus (hashCall (contract', sig)) (hashCoverage coverage) args if res then pure Pass else pure $ Fail vm' (show . ByteStringS . encodeAbiValue $ args) @@ -244,45 +242,32 @@ hashCall :: (SolcContract, Text) -> W256 hashCall (contract', sig) = keccak . encodeUtf8 $ (Text.pack . show . _runtimeCodehash $ contract') <> (Text.pack . show . _creationCodehash $ contract') <> sig +hashCoverage :: MultiSet OpLocation -> W256 +hashCoverage = MultiSet.fold (\loc acc -> keccak ((word256Bytes acc) <> (word256Bytes . codeHash $ loc))) (W256 0) + tick :: Text -> IO () tick x = Text.putStr x >> hFlush stdout -- | This is like an unresolved source mapping. data OpLocation = OpLocation - { srcCode :: ContractCode - , srcOpIx :: Int + { srcCode :: ContractCode + , codeHash :: W256 + , srcOpIx :: Int } deriving (Show, Eq, Ord, Generic) instance Arbitrary OpLocation where arbitrary = do - src <- arbitrary :: Gen ContractCode + src <- arbitrary + hash <- arbitrary opIx <- choose (0, codesize src) - pure $ OpLocation src opIx + pure $ OpLocation src hash opIx where codesize (InitCode (ConcreteBuffer c)) = BS.length c codesize (RuntimeCode (ConcreteBuffer c)) = BS.length c codesize _ = error "cannot compute length for symbolic bytecode" -instance FromJSON OpLocation -instance FromJSONKey OpLocation -instance ToJSON OpLocation - -instance (Ord a, FromJSON a) => FromJSON (MultiSet a) where - parseJSON = fmap MultiSet.fromList . parseJSON - -instance ToJSON1 MultiSet where - liftToJSON t _ = listValue t . MultiSet.toList - liftToEncoding t _ = listEncoding t . MultiSet.toList - -instance (ToJSON a) => ToJSON (MultiSet a) where - toJSON = toJSON1 - toEncoding = toEncoding1 - -instance ToJSONKey (MultiSet OpLocation) -instance FromJSONKey (MultiSet OpLocation) - srcMapForOpLocation :: DappInfo -> OpLocation -> Maybe SrcMap -srcMapForOpLocation dapp (OpLocation hash opIx) = srcMap dapp hash opIx +srcMapForOpLocation dapp (OpLocation code' _ opIx) = srcMap dapp code' opIx type CoverageState = (VM, MultiSet OpLocation) @@ -294,6 +279,7 @@ currentOpLocation vm = Just c -> OpLocation (view contractcode c) + (view codehash c) (fromMaybe (error "internal error: op ix") (vmOpIx vm)) execWithCoverage :: StateT CoverageState IO VMResult diff --git a/src/hevm/test/test.hs b/src/hevm/test/test.hs index 65daab40b..004f6eddb 100644 --- a/src/hevm/test/test.hs +++ b/src/hevm/test/test.hs @@ -116,18 +116,6 @@ main = defaultMain $ testGroup "hevm" Error _ -> False Data.Aeson.Success v -> val == v - , testProperty "OpLocation" $ do - val <- arbitrary :: Gen OpLocation - pure $ case (fromJSON . toJSON $ val) of - Error _ -> False - Data.Aeson.Success v -> val == v - - , testProperty "MultiSet OpLocation" $ do - val <- arbitrary :: Gen (MultiSet OpLocation) - pure $ case (fromJSON . toJSON $ val) of - Error _ -> False - Data.Aeson.Success v -> val == v - , testProperty "W256" $ do val <- arbitrary :: Gen W256 pure $ case (fromJSON . toJSON $ val) of From 10f6d071b56de7caf69b24e297cc7909c3c3d277 Mon Sep 17 00:00:00 2001 From: David Terry Date: Thu, 27 May 2021 17:31:45 +0200 Subject: [PATCH 13/21] hevm: UnitTest: use blake3 for hashing corpus keys --- src/hevm/hevm.cabal | 5 ++-- src/hevm/src/EVM/UnitTest.hs | 50 ++++++++++++++++++++++++++++-------- src/hevm/test/test.hs | 9 ++++++- 3 files changed, 51 insertions(+), 13 deletions(-) diff --git a/src/hevm/hevm.cabal b/src/hevm/hevm.cabal index a1074145f..0ea457761 100644 --- a/src/hevm/hevm.cabal +++ b/src/hevm/hevm.cabal @@ -130,7 +130,8 @@ library wreq >= 0.5.3 && < 0.6, regex-tdfa >= 1.2.3 && < 1.4, base >= 4.9 && < 5, - ListLike >= 4.7.2 && < 4.8 + ListLike >= 4.7.2 && < 4.8, + blake3 >= 0.2 && < 0.3 hs-source-dirs: src default-language: @@ -213,7 +214,7 @@ test-suite test HUnit >= 1.6, QuickCheck, aeson, - multiset, + blake3, base, base16-bytestring, binary, diff --git a/src/hevm/src/EVM/UnitTest.hs b/src/hevm/src/EVM/UnitTest.hs index 2abcbeefe..3feb21cad 100644 --- a/src/hevm/src/EVM/UnitTest.hs +++ b/src/hevm/src/EVM/UnitTest.hs @@ -24,9 +24,6 @@ import qualified EVM.Fetch import qualified EVM.FeeSchedule as FeeSchedule -import Data.Aeson -import Data.Aeson.Types - import EVM.Stepper (Stepper, interpret) import qualified EVM.Stepper as Stepper import qualified Control.Monad.Operational as Operational @@ -38,6 +35,14 @@ import qualified Control.Monad.State.Strict as State import Control.Monad.Par.Class (spawn_) import Control.Monad.Par.IO (runParIO) +import qualified BLAKE3 +import qualified Data.ByteArray() +import GHC.TypeLits (KnownNat) +import Data.ByteArray.Encoding (convertFromBase, Base(..)) +import Data.Aeson (ToJSON(..), FromJSON(..), ToJSONKey(..), FromJSONKey(..), Value(..), withText) +import Data.Aeson.Types (toJSONKeyText) +import Data.ByteString.Base16 as BS16 + import qualified Data.ByteString.Lazy as BSLazy import qualified Data.SBV.Trans.Control as SBV (Query, getValue, resetAssertions) import qualified Data.SBV.Internals as SBV (State) @@ -51,7 +56,7 @@ import Data.Foldable (toList) import Data.Map hiding (mapMaybe, toList, map, filter, null, take) import Data.Maybe (fromMaybe, catMaybes, fromJust, isJust, fromMaybe, mapMaybe) import Data.Text (isPrefixOf, stripSuffix, intercalate, Text, pack, unpack) -import Data.Text.Encoding (encodeUtf8) +import Data.Text.Encoding (encodeUtf8, decodeUtf8) import System.Environment (lookupEnv) import System.IO (hFlush, stdout) import GHC.Generics (Generic) @@ -111,7 +116,7 @@ data TestVMParams = TestVMParams -- | For each tuple of (contract, method) we store the calldata required to reach each known path in the method -- | The keys in the corpus are hashed to keep the size of the serialized representation manageable -type Corpus = Map W256 (Map W256 AbiValue) +type Corpus = Map (BLAKE3.Digest 32) (Map (BLAKE3.Digest 32) AbiValue) instance Arbitrary (MultiSet OpLocation) where arbitrary = do @@ -238,12 +243,37 @@ fuzzTest opts sig types vm = do Nothing -> Map.insert k1 (Map.insert k2 v mempty) c Just m' -> Map.insert k1 (Map.insert k2 v m') c -hashCall :: (SolcContract, Text) -> W256 -hashCall (contract', sig) = keccak . encodeUtf8 $ - (Text.pack . show . _runtimeCodehash $ contract') <> (Text.pack . show . _creationCodehash $ contract') <> sig +hashCall :: (SolcContract, Text) -> BLAKE3.Digest 32 +hashCall (contract', sig) = BLAKE3.hash + [encodeUtf8 . Text.pack $ (show . _runtimeCodehash $ contract') <> (show . _creationCodehash $ contract') <> (Text.unpack sig)] + +hashCoverage :: MultiSet OpLocation -> BLAKE3.Digest 32 +hashCoverage cov = BLAKE3.finalize $ MultiSet.fold (\loc acc -> BLAKE3.update acc [word256Bytes . codeHash $ loc]) (BLAKE3.hasher) cov + +instance Arbitrary (BLAKE3.Digest 32) where + arbitrary = do + msg <- arbitrary :: Gen ByteString + pure $ BLAKE3.hash [msg] + +instance Ord (BLAKE3.Digest 32) where + x <= y = show x <= show y + +instance ToJSONKey (BLAKE3.Digest 32) +instance FromJSONKey (BLAKE3.Digest 32) + +digestText :: BLAKE3.Digest 32 -> Text +digestText = Text.pack . show + +instance ToJSON (BLAKE3.Digest 32) where + toJSON = String . Text.pack . show + +instance FromJSON (BLAKE3.Digest 32) where + parseJSON = withText "BLAKE3.Digest 32" $ pure . read . Text.unpack -hashCoverage :: MultiSet OpLocation -> W256 -hashCoverage = MultiSet.fold (\loc acc -> keccak ((word256Bytes acc) <> (word256Bytes . codeHash $ loc))) (W256 0) +instance KnownNat a => Read (BLAKE3.Digest a) where + readsPrec _ x = [bimap decode (Text.unpack . decodeUtf8) bytes] + where bytes = BS16.decode (encodeUtf8 (Text.pack x)) + decode = fromJust . BLAKE3.digest tick :: Text -> IO () tick x = Text.putStr x >> hFlush stdout diff --git a/src/hevm/test/test.hs b/src/hevm/test/test.hs index 004f6eddb..34f8d4a84 100644 --- a/src/hevm/test/test.hs +++ b/src/hevm/test/test.hs @@ -38,7 +38,8 @@ import Data.SBV hiding ((===), forAll, sList) import Data.SBV.Control import qualified Data.Map as Map import Data.Binary.Get (runGetOrFail) -import Data.MultiSet (MultiSet) +import qualified BLAKE3 + import Data.Aeson (fromJSON, toJSON, Result(..)) @@ -116,6 +117,12 @@ main = defaultMain $ testGroup "hevm" Error _ -> False Data.Aeson.Success v -> val == v + , testProperty "Blake3 Digest" $ do + val <- arbitrary :: Gen (BLAKE3.Digest 32) + pure $ case (fromJSON . toJSON $ val) of + Error _ -> False + Data.Aeson.Success v -> val == v + , testProperty "W256" $ do val <- arbitrary :: Gen W256 pure $ case (fromJSON . toJSON $ val) of From 87fec27503bd13b2687800984fb74e16cf574ccd Mon Sep 17 00:00:00 2001 From: David Terry Date: Fri, 28 May 2021 10:12:21 +0200 Subject: [PATCH 14/21] hevm: UnitTest: no more word256Bytes --- src/hevm/src/EVM/UnitTest.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/hevm/src/EVM/UnitTest.hs b/src/hevm/src/EVM/UnitTest.hs index 3feb21cad..64ebaae5a 100644 --- a/src/hevm/src/EVM/UnitTest.hs +++ b/src/hevm/src/EVM/UnitTest.hs @@ -248,7 +248,7 @@ hashCall (contract', sig) = BLAKE3.hash [encodeUtf8 . Text.pack $ (show . _runtimeCodehash $ contract') <> (show . _creationCodehash $ contract') <> (Text.unpack sig)] hashCoverage :: MultiSet OpLocation -> BLAKE3.Digest 32 -hashCoverage cov = BLAKE3.finalize $ MultiSet.fold (\loc acc -> BLAKE3.update acc [word256Bytes . codeHash $ loc]) (BLAKE3.hasher) cov +hashCoverage cov = BLAKE3.finalize $ MultiSet.fold (\loc acc -> BLAKE3.update acc [encodeUtf8 . Text.pack . show . codeHash $ loc]) (BLAKE3.hasher) cov instance Arbitrary (BLAKE3.Digest 32) where arbitrary = do From 6286f51522cabe47c168e79a89a7973418c01a42 Mon Sep 17 00:00:00 2001 From: David Terry Date: Fri, 28 May 2021 12:16:39 +0200 Subject: [PATCH 15/21] hevm: UnitTest: replace coverage traces with a hash accumulator. ~7% speedup --- src/hevm/src/EVM/UnitTest.hs | 66 ++++++++++++++++++++++++++++++++---- 1 file changed, 59 insertions(+), 7 deletions(-) diff --git a/src/hevm/src/EVM/UnitTest.hs b/src/hevm/src/EVM/UnitTest.hs index 64ebaae5a..44d578601 100644 --- a/src/hevm/src/EVM/UnitTest.hs +++ b/src/hevm/src/EVM/UnitTest.hs @@ -38,9 +38,7 @@ import Control.Monad.Par.IO (runParIO) import qualified BLAKE3 import qualified Data.ByteArray() import GHC.TypeLits (KnownNat) -import Data.ByteArray.Encoding (convertFromBase, Base(..)) import Data.Aeson (ToJSON(..), FromJSON(..), ToJSONKey(..), FromJSONKey(..), Value(..), withText) -import Data.Aeson.Types (toJSONKeyText) import Data.ByteString.Base16 as BS16 import qualified Data.ByteString.Lazy as BSLazy @@ -233,8 +231,9 @@ fuzzTest opts sig types vm = do contract' = fromJust $ lookupCode code' (dapp opts) corpus <- get args <- liftIO . generate $ genWithCorpus opts corpus contract' sig types - (res, (vm', coverage)) <- liftIO $ runStateT (interpretWithCoverage opts (runUnitTest opts sig args)) (vm, mempty) - modify $ updateCorpus (hashCall (contract', sig)) (hashCoverage coverage) args + (res, (vm', hasher)) <- liftIO $ runStateT (interpretWithTraceId opts (runUnitTest opts sig args)) (vm, BLAKE3.hasher) + let traceId = BLAKE3.finalize hasher + modify $ updateCorpus (hashCall (contract', sig)) traceId args if res then pure Pass else pure $ Fail vm' (show . ByteStringS . encodeAbiValue $ args) @@ -247,9 +246,6 @@ hashCall :: (SolcContract, Text) -> BLAKE3.Digest 32 hashCall (contract', sig) = BLAKE3.hash [encodeUtf8 . Text.pack $ (show . _runtimeCodehash $ contract') <> (show . _creationCodehash $ contract') <> (Text.unpack sig)] -hashCoverage :: MultiSet OpLocation -> BLAKE3.Digest 32 -hashCoverage cov = BLAKE3.finalize $ MultiSet.fold (\loc acc -> BLAKE3.update acc [encodeUtf8 . Text.pack . show . codeHash $ loc]) (BLAKE3.hasher) cov - instance Arbitrary (BLAKE3.Digest 32) where arbitrary = do msg <- arbitrary :: Gen ByteString @@ -275,6 +271,62 @@ instance KnownNat a => Read (BLAKE3.Digest a) where where bytes = BS16.decode (encodeUtf8 (Text.pack x)) decode = fromJust . BLAKE3.digest +type TraceIdState = (VM, BLAKE3.Hasher) + +-- | This interpreter is similar to interpretWithCoverage, except instead of +-- collecting the full trace, we instead return a hash of the trace. This +-- avoids the overhead associated with the MultiSet used in interpretWithCoverage +interpretWithTraceId + :: UnitTestOptions + -> Stepper a + -> StateT TraceIdState IO a +interpretWithTraceId opts = + eval . Operational.view + + where + eval + :: Operational.ProgramView Stepper.Action a + -> StateT TraceIdState IO a + + eval (Operational.Return x) = + pure x + + eval (action Operational.:>>= k) = + case action of + Stepper.Exec -> + execWithTraceId >>= interpretWithTraceId opts . k + Stepper.Run -> + runWithTraceId >>= interpretWithTraceId opts . k + Stepper.Wait q -> do + m <- liftIO (oracle opts q) + zoom _1 (State.state (runState m)) >> interpretWithTraceId opts (k ()) + Stepper.Ask _ -> + error "cannot make choice in this interpreter" + Stepper.EVM m -> + zoom _1 (State.state (runState m)) >>= interpretWithTraceId opts . k + +execWithTraceId :: StateT TraceIdState IO VMResult +execWithTraceId = do _ <- runWithTraceId + fromJust <$> use (_1 . result) + +runWithTraceId :: StateT TraceIdState IO VM +runWithTraceId = do + -- This is just like `exec` except for every instruction evaluated, + -- we also updae a hash accumulator for each instruction visited + vm0 <- use _1 + case view result vm0 of + Nothing -> do + vm1 <- zoom _1 (State.state (runState exec1) >> get) + zoom _2 (modify (flip BLAKE3.update ([encodeUtf8 . Text.pack . show . loc $ vm1]))) + runWithTraceId + Just _ -> pure vm0 + where + loc vm = + case currentContract vm of + Nothing -> + error "internal error: why no contract?" + Just c -> (view codehash c, fromMaybe (error "internal error: op ix") (vmOpIx vm)) + tick :: Text -> IO () tick x = Text.putStr x >> hFlush stdout From d6edbac5890e2c307e5a623af6fbafd213911748 Mon Sep 17 00:00:00 2001 From: David Terry Date: Fri, 28 May 2021 13:42:13 +0200 Subject: [PATCH 16/21] hevm: UnitTest: replace blake3 with xxhash (~6% improvement) --- src/hevm/hevm.cabal | 2 +- src/hevm/src/EVM/Types.hs | 1 - src/hevm/src/EVM/UnitTest.hs | 53 +++++++++--------------------------- 3 files changed, 14 insertions(+), 42 deletions(-) diff --git a/src/hevm/hevm.cabal b/src/hevm/hevm.cabal index 0ea457761..fd9487063 100644 --- a/src/hevm/hevm.cabal +++ b/src/hevm/hevm.cabal @@ -131,7 +131,7 @@ library regex-tdfa >= 1.2.3 && < 1.4, base >= 4.9 && < 5, ListLike >= 4.7.2 && < 4.8, - blake3 >= 0.2 && < 0.3 + xxhash-ffi >= 0.2.0.0 && < 0.3 hs-source-dirs: src default-language: diff --git a/src/hevm/src/EVM/Types.hs b/src/hevm/src/EVM/Types.hs index 6fa9728e3..e1679c17f 100644 --- a/src/hevm/src/EVM/Types.hs +++ b/src/hevm/src/EVM/Types.hs @@ -38,7 +38,6 @@ import qualified Data.ByteString as BS import qualified Data.Serialize.Get as Cereal import qualified Data.Text as Text import qualified Data.Text.Encoding as Text -import qualified Data.ByteString.Builder as B import qualified Text.Read -- Some stuff for "generic programming", needed to create Word512 diff --git a/src/hevm/src/EVM/UnitTest.hs b/src/hevm/src/EVM/UnitTest.hs index 44d578601..b0a35a507 100644 --- a/src/hevm/src/EVM/UnitTest.hs +++ b/src/hevm/src/EVM/UnitTest.hs @@ -35,11 +35,7 @@ import qualified Control.Monad.State.Strict as State import Control.Monad.Par.Class (spawn_) import Control.Monad.Par.IO (runParIO) -import qualified BLAKE3 -import qualified Data.ByteArray() -import GHC.TypeLits (KnownNat) -import Data.Aeson (ToJSON(..), FromJSON(..), ToJSONKey(..), FromJSONKey(..), Value(..), withText) -import Data.ByteString.Base16 as BS16 +import Data.Digest.XXHash.FFI import qualified Data.ByteString.Lazy as BSLazy import qualified Data.SBV.Trans.Control as SBV (Query, getValue, resetAssertions) @@ -54,7 +50,7 @@ import Data.Foldable (toList) import Data.Map hiding (mapMaybe, toList, map, filter, null, take) import Data.Maybe (fromMaybe, catMaybes, fromJust, isJust, fromMaybe, mapMaybe) import Data.Text (isPrefixOf, stripSuffix, intercalate, Text, pack, unpack) -import Data.Text.Encoding (encodeUtf8, decodeUtf8) +import Data.Text.Encoding (encodeUtf8) import System.Environment (lookupEnv) import System.IO (hFlush, stdout) import GHC.Generics (Generic) @@ -114,7 +110,7 @@ data TestVMParams = TestVMParams -- | For each tuple of (contract, method) we store the calldata required to reach each known path in the method -- | The keys in the corpus are hashed to keep the size of the serialized representation manageable -type Corpus = Map (BLAKE3.Digest 32) (Map (BLAKE3.Digest 32) AbiValue) +type Corpus = Map Word64 (Map Word64 AbiValue) instance Arbitrary (MultiSet OpLocation) where arbitrary = do @@ -213,6 +209,9 @@ checkFailures UnitTestOptions { .. } method bailed = do in pure (shouldFail == failed) _ -> error "internal error: unexpected failure code" +xxhash :: ByteString -> Word64 +xxhash bs = xxh64 bs 42069 + -- | Either generates the calldata by mutating an example from the corpus, or synthesizes a random example genWithCorpus :: UnitTestOptions -> Corpus -> SolcContract -> Text -> [AbiType] -> Gen AbiValue genWithCorpus opts corpus contract' sig tps = do @@ -231,8 +230,7 @@ fuzzTest opts sig types vm = do contract' = fromJust $ lookupCode code' (dapp opts) corpus <- get args <- liftIO . generate $ genWithCorpus opts corpus contract' sig types - (res, (vm', hasher)) <- liftIO $ runStateT (interpretWithTraceId opts (runUnitTest opts sig args)) (vm, BLAKE3.hasher) - let traceId = BLAKE3.finalize hasher + (res, (vm', traceId)) <- liftIO $ runStateT (interpretWithTraceId opts (runUnitTest opts sig args)) (vm, 0) modify $ updateCorpus (hashCall (contract', sig)) traceId args if res then pure Pass @@ -242,36 +240,11 @@ fuzzTest opts sig types vm = do Nothing -> Map.insert k1 (Map.insert k2 v mempty) c Just m' -> Map.insert k1 (Map.insert k2 v m') c -hashCall :: (SolcContract, Text) -> BLAKE3.Digest 32 -hashCall (contract', sig) = BLAKE3.hash - [encodeUtf8 . Text.pack $ (show . _runtimeCodehash $ contract') <> (show . _creationCodehash $ contract') <> (Text.unpack sig)] - -instance Arbitrary (BLAKE3.Digest 32) where - arbitrary = do - msg <- arbitrary :: Gen ByteString - pure $ BLAKE3.hash [msg] - -instance Ord (BLAKE3.Digest 32) where - x <= y = show x <= show y - -instance ToJSONKey (BLAKE3.Digest 32) -instance FromJSONKey (BLAKE3.Digest 32) - -digestText :: BLAKE3.Digest 32 -> Text -digestText = Text.pack . show - -instance ToJSON (BLAKE3.Digest 32) where - toJSON = String . Text.pack . show - -instance FromJSON (BLAKE3.Digest 32) where - parseJSON = withText "BLAKE3.Digest 32" $ pure . read . Text.unpack - -instance KnownNat a => Read (BLAKE3.Digest a) where - readsPrec _ x = [bimap decode (Text.unpack . decodeUtf8) bytes] - where bytes = BS16.decode (encodeUtf8 (Text.pack x)) - decode = fromJust . BLAKE3.digest +hashCall :: (SolcContract, Text) -> Word64 +hashCall (contract', sig) = xxhash . + encodeUtf8 . Text.pack $ (show . _runtimeCodehash $ contract') <> (show . _creationCodehash $ contract') <> (Text.unpack sig) -type TraceIdState = (VM, BLAKE3.Hasher) +type TraceIdState = (VM, Word64) -- | This interpreter is similar to interpretWithCoverage, except instead of -- collecting the full trace, we instead return a hash of the trace. This @@ -317,7 +290,7 @@ runWithTraceId = do case view result vm0 of Nothing -> do vm1 <- zoom _1 (State.state (runState exec1) >> get) - zoom _2 (modify (flip BLAKE3.update ([encodeUtf8 . Text.pack . show . loc $ vm1]))) + zoom _2 (modify (\acc -> xxhash ((encodeUtf8 . Text.pack . show $ acc) <> loc vm1))) runWithTraceId Just _ -> pure vm0 where @@ -325,7 +298,7 @@ runWithTraceId = do case currentContract vm of Nothing -> error "internal error: why no contract?" - Just c -> (view codehash c, fromMaybe (error "internal error: op ix") (vmOpIx vm)) + Just c -> encodeUtf8 . Text.pack . show $ (view codehash c, fromMaybe (error "internal error: op ix") (vmOpIx vm)) tick :: Text -> IO () tick x = Text.putStr x >> hFlush stdout From fa47e66ea30f8d2e2b32e0c758835cf1fabbb484 Mon Sep 17 00:00:00 2001 From: David Terry Date: Fri, 28 May 2021 13:50:50 +0200 Subject: [PATCH 17/21] hevm: UnitTest: represent traces as a list (640% faster) --- src/hevm/src/EVM/UnitTest.hs | 10 +++++----- 1 file changed, 5 insertions(+), 5 deletions(-) diff --git a/src/hevm/src/EVM/UnitTest.hs b/src/hevm/src/EVM/UnitTest.hs index b0a35a507..370ad29bf 100644 --- a/src/hevm/src/EVM/UnitTest.hs +++ b/src/hevm/src/EVM/UnitTest.hs @@ -110,7 +110,7 @@ data TestVMParams = TestVMParams -- | For each tuple of (contract, method) we store the calldata required to reach each known path in the method -- | The keys in the corpus are hashed to keep the size of the serialized representation manageable -type Corpus = Map Word64 (Map Word64 AbiValue) +type Corpus = Map Word64 (Map [(W256, Int)] AbiValue) instance Arbitrary (MultiSet OpLocation) where arbitrary = do @@ -230,7 +230,7 @@ fuzzTest opts sig types vm = do contract' = fromJust $ lookupCode code' (dapp opts) corpus <- get args <- liftIO . generate $ genWithCorpus opts corpus contract' sig types - (res, (vm', traceId)) <- liftIO $ runStateT (interpretWithTraceId opts (runUnitTest opts sig args)) (vm, 0) + (res, (vm', traceId)) <- liftIO $ runStateT (interpretWithTraceId opts (runUnitTest opts sig args)) (vm, []) modify $ updateCorpus (hashCall (contract', sig)) traceId args if res then pure Pass @@ -244,7 +244,7 @@ hashCall :: (SolcContract, Text) -> Word64 hashCall (contract', sig) = xxhash . encodeUtf8 . Text.pack $ (show . _runtimeCodehash $ contract') <> (show . _creationCodehash $ contract') <> (Text.unpack sig) -type TraceIdState = (VM, Word64) +type TraceIdState = (VM, [(W256, Int)]) -- | This interpreter is similar to interpretWithCoverage, except instead of -- collecting the full trace, we instead return a hash of the trace. This @@ -290,7 +290,7 @@ runWithTraceId = do case view result vm0 of Nothing -> do vm1 <- zoom _1 (State.state (runState exec1) >> get) - zoom _2 (modify (\acc -> xxhash ((encodeUtf8 . Text.pack . show $ acc) <> loc vm1))) + zoom _2 (modify (\acc -> loc vm1 : acc)) runWithTraceId Just _ -> pure vm0 where @@ -298,7 +298,7 @@ runWithTraceId = do case currentContract vm of Nothing -> error "internal error: why no contract?" - Just c -> encodeUtf8 . Text.pack . show $ (view codehash c, fromMaybe (error "internal error: op ix") (vmOpIx vm)) + Just c -> (view codehash c, fromMaybe (error "internal error: op ix") (vmOpIx vm)) tick :: Text -> IO () tick x = Text.putStr x >> hFlush stdout From 537fed0f954373bf7114b0c25e64d8215fc04fd3 Mon Sep 17 00:00:00 2001 From: David Terry Date: Fri, 28 May 2021 18:07:22 +0200 Subject: [PATCH 18/21] hevm: UnitTest: rm hashCall --- src/hevm/hevm.cabal | 1 - src/hevm/hevm.prof | 3138 ++++++++++++++++++++++++++++++++++ src/hevm/src/EVM/UnitTest.hs | 31 +- src/hevm/test/test.hs | 6 - 4 files changed, 3148 insertions(+), 28 deletions(-) create mode 100644 src/hevm/hevm.prof diff --git a/src/hevm/hevm.cabal b/src/hevm/hevm.cabal index fd9487063..ad7ff22aa 100644 --- a/src/hevm/hevm.cabal +++ b/src/hevm/hevm.cabal @@ -131,7 +131,6 @@ library regex-tdfa >= 1.2.3 && < 1.4, base >= 4.9 && < 5, ListLike >= 4.7.2 && < 4.8, - xxhash-ffi >= 0.2.0.0 && < 0.3 hs-source-dirs: src default-language: diff --git a/src/hevm/hevm.prof b/src/hevm/hevm.prof new file mode 100644 index 000000000..ee0b1b342 --- /dev/null +++ b/src/hevm/hevm.prof @@ -0,0 +1,3138 @@ + Fri May 28 14:23 2021 Time and Allocation Profiling Report (Final) + + hevm +RTS -N -p -RTS dapp-test --dapp-root /home/me/code/mine/scratch/solidity + + total time = 0.52 secs (1929 ticks @ 1000 us, 8 processors) + total alloc = 2,365,287,016 bytes (excludes profiling overheads) + +COST CENTRE MODULE SRC %time %alloc + +exec1 EVM src/EVM.hs:(547,1)-(1323,42) 18.8 14.4 +burn EVM src/EVM.hs:(1826,1)-(1838,38) 8.3 14.0 +num EVM.Types src/EVM/Types.hs:492:1-18 7.5 6.0 +jstring Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:317:1-32 7.3 10.3 +mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 6.6 4.8 +runWithTraceId EVM.UnitTest src/EVM/UnitTest.hs:(286,1)-(301,90) 5.9 7.5 +hashCall EVM.UnitTest src/EVM/UnitTest.hs:(244,1)-(245,127) 4.0 8.3 +limitStack EVM src/EVM.hs:(1809,1)-(1813,17) 3.4 0.8 +vmOpIx EVM src/EVM.hs:(2603,1)-(2605,57) 3.1 2.1 +currentContract EVM src/EVM.hs:(443,1)-(444,65) 2.8 1.1 +fuzzTest EVM.UnitTest src/EVM/UnitTest.hs:(228,1)-(241,53) 2.6 0.0 +checkJump EVM src/EVM.hs:(2526,1)-(2539,35) 2.4 1.1 +stripBytecodeMetadata EVM.Solidity src/EVM/Solidity.hs:(569,1)-(573,22) 1.8 0.0 +withPtr Basement.Block.Base Basement/Block/Base.hs:(402,1)-(411,31) 1.7 1.9 +array_ Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:169:35-59 1.7 2.9 +genLiteral Data.SBV.Core.Model Data/SBV/Core/Model.hs:99:1-48 1.5 1.3 +next EVM src/EVM.hs:543:1-46 0.8 4.7 +index EVM.Symbolic src/EVM/Symbolic.hs:(207,1)-(208,47) 0.8 2.2 +makeSrcMaps EVM.Solidity src/EVM/Solidity.hs:(227,1)-(271,126) 0.8 1.0 +pushSym EVM src/EVM.hs:2477:1-34 0.6 1.7 +bytesRead Data.Serialize.Get src/Data/Serialize/Get.hs:838:1-45 0.4 1.5 + + + individual inherited +COST CENTRE MODULE SRC no. entries %time %alloc %time %alloc + +MAIN MAIN 1725 0 0.0 0.0 100.0 100.0 + CAF Main 3448 0 0.0 0.0 0.0 0.0 + main Main hevm-cli/hevm-cli.hs:(307,1)-(354,100) 3450 1 0.0 0.0 0.0 0.0 + parseRecord Main hevm-cli/hevm-cli.hs:(237,3)-(238,62) 3514 1 0.0 0.0 0.0 0.0 + parseRecordWithModifiers Options.Generic src/Options/Generic.hs:1006:1-78 3515 1 0.0 0.0 0.0 0.0 + help Options.Applicative.Builder src/Options/Applicative/Builder.hs:185:1-55 3569 18 0.0 0.0 0.0 0.0 + optionMod Options.Applicative.Builder.Internal src/Options/Applicative/Builder/Internal.hs:129:1-25 3570 0 0.0 0.0 0.0 0.0 + long Options.Applicative.Builder src/Options/Applicative/Builder.hs:161:1-32 3567 18 0.0 0.0 0.0 0.0 + fieldMod Options.Applicative.Builder.Internal src/Options/Applicative/Builder/Internal.hs:132:1-28 3568 18 0.0 0.0 0.0 0.0 + option Options.Applicative.Builder src/Options/Applicative/Builder.hs:(367,1)-(372,65) 3571 14 0.0 0.0 0.0 0.0 + mkParser Options.Applicative.Builder.Internal src/Options/Applicative/Builder/Internal.hs:(163,1)-(167,36) 3572 14 0.0 0.0 0.0 0.0 + mkOption Options.Applicative.Builder.Internal src/Options/Applicative/Builder/Internal.hs:173:1-43 3573 2 0.0 0.0 0.0 0.0 + optNames Options.Applicative.Builder.Internal src/Options/Applicative/Builder/Internal.hs:35:5-12 3574 2 0.0 0.0 0.0 0.0 + long Options.Applicative.Builder src/Options/Applicative/Builder.hs:161:1-32 3575 0 0.0 0.0 0.0 0.0 + optNames Options.Applicative.Builder.Internal src/Options/Applicative/Builder/Internal.hs:35:5-12 3577 1 0.0 0.0 0.0 0.0 + fieldMod Options.Applicative.Builder.Internal src/Options/Applicative/Builder/Internal.hs:132:1-28 3576 0 0.0 0.0 0.0 0.0 + metavar Options.Applicative.Builder src/Options/Applicative/Builder.hs:201:1-55 3538 13 0.0 0.0 0.0 0.0 + optionMod Options.Applicative.Builder.Internal src/Options/Applicative/Builder/Internal.hs:129:1-25 3539 0 0.0 0.0 0.0 0.0 + command Options.Applicative.Builder src/Options/Applicative/Builder.hs:(234,1)-(235,50) 3536 4 0.0 0.0 0.0 0.0 + fieldMod Options.Applicative.Builder.Internal src/Options/Applicative/Builder/Internal.hs:132:1-28 3537 4 0.0 0.0 0.0 0.0 + subparser Options.Applicative.Builder src/Options/Applicative/Builder.hs:(270,1)-(274,39) 3540 4 0.0 0.0 0.0 0.0 + mkCommand Options.Applicative.Builder.Internal src/Options/Applicative/Builder/Internal.hs:(154,1)-(157,59) 3548 4 0.0 0.0 0.0 0.0 + command Options.Applicative.Builder src/Options/Applicative/Builder.hs:(234,1)-(235,50) 3551 0 0.0 0.0 0.0 0.0 + cmdCommands Options.Applicative.Builder.Internal src/Options/Applicative/Builder/Internal.hs:44:5-15 3554 3 0.0 0.0 0.0 0.0 + fieldMod Options.Applicative.Builder.Internal src/Options/Applicative/Builder/Internal.hs:132:1-28 3552 0 0.0 0.0 0.0 0.0 + mkParser Options.Applicative.Builder.Internal src/Options/Applicative/Builder/Internal.hs:(163,1)-(167,36) 3544 4 0.0 0.0 0.0 0.0 + mkOption Options.Applicative.Builder.Internal src/Options/Applicative/Builder/Internal.hs:173:1-43 3545 4 0.0 0.0 0.0 0.0 + info Options.Applicative.Builder src/Options/Applicative/Builder.hs:(443,1)-(452,34) 3559 1 0.0 0.0 0.0 0.0 + lispCaseModifiers Options.Generic src/Options/Generic.hs:(816,1)-(820,29) 3553 0 0.0 0.0 0.0 0.0 + switch Options.Applicative.Builder src/Options/Applicative/Builder.hs:333:1-24 3591 0 0.0 0.0 0.0 0.0 + flag Options.Applicative.Builder src/Options/Applicative/Builder.hs:299:1-45 3592 4 0.0 0.0 0.0 0.0 + flag' Options.Applicative.Builder src/Options/Applicative/Builder.hs:(319,1)-(323,43) 3593 4 0.0 0.0 0.0 0.0 + mkParser Options.Applicative.Builder.Internal src/Options/Applicative/Builder/Internal.hs:(163,1)-(167,36) 3594 4 0.0 0.0 0.0 0.0 + metavar Options.Applicative.Builder src/Options/Applicative/Builder.hs:201:1-55 3597 0 0.0 0.0 0.0 0.0 + optionMod Options.Applicative.Builder.Internal src/Options/Applicative/Builder/Internal.hs:129:1-25 3598 0 0.0 0.0 0.0 0.0 + unitTestOptions Main hevm-cli/hevm-cli.hs:(262,1)-(304,5) 4244 0 0.0 0.0 0.0 0.0 + CAF EVM 3447 0 0.0 0.0 0.1 0.0 + blankState EVM src/EVM.hs:(385,1)-(399,3) 4842 1 0.0 0.0 0.0 0.0 + genLiteral Data.SBV.Core.Model Data/SBV/Core/Model.hs:99:1-48 4843 2 0.0 0.0 0.0 0.0 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 4906 1 0.0 0.0 0.0 0.0 + svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 4907 1 0.0 0.0 0.0 0.0 + svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 4908 1 0.0 0.0 0.0 0.0 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 4909 1 0.0 0.0 0.0 0.0 + cheatCode EVM src/EVM.hs:1936:1-42 5957 1 0.0 0.0 0.0 0.0 + num EVM.Types src/EVM/Types.hs:492:1-18 5958 1 0.0 0.0 0.0 0.0 + keccak EVM.Types src/EVM/Types.hs:(580,1)-(583,12) 5959 0 0.0 0.0 0.0 0.0 + keccakBytes EVM.Types src/EVM/Types.hs:(570,1)-(573,15) 5961 0 0.0 0.0 0.0 0.0 + hash Crypto.Hash Crypto/Hash.hs:58:1-47 5962 1 0.0 0.0 0.0 0.0 + hashFinalize Crypto.Hash Crypto/Hash.hs:(92,1)-(95,17) 5963 1 0.0 0.0 0.0 0.0 + allocAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:74:1-45 5971 1 0.0 0.0 0.0 0.0 + new Basement.Block.Base Basement/Block/Base.hs:304:1-76 5972 1 0.0 0.0 0.0 0.0 + unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 5973 1 0.0 0.0 0.0 0.0 + withMutablePtrHint Basement.Block.Base Basement/Block/Base.hs:(475,1)-(489,39) 5974 1 0.0 0.0 0.0 0.0 + copy Data.ByteArray.Methods Data/ByteArray/Methods.hs:(223,1)-(226,21) 5979 1 0.0 0.0 0.0 0.0 + isMutablePinned Basement.Block.Base Basement/Block/Base.hs:100:1-90 5975 1 0.0 0.0 0.0 0.0 + compatIsMutableByteArrayPinned# Basement.Compat.Primitive Basement/Compat/Primitive.hs:70:1-65 5976 1 0.0 0.0 0.0 0.0 + toPinnedStatus# Basement.Compat.Primitive Basement/Compat/Primitive.hs:(47,1)-(48,27) 5977 1 0.0 0.0 0.0 0.0 + unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 5978 1 0.0 0.0 0.0 0.0 + hashInit Crypto.Hash Crypto/Hash.hs:(66,1)-(67,24) 5969 1 0.0 0.0 0.0 0.0 + allocAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:74:1-45 5970 1 0.0 0.0 0.0 0.0 + hashUpdate Crypto.Hash Crypto/Hash.hs:(71,1)-(73,37) 5964 1 0.0 0.0 0.0 0.0 + hashUpdates Crypto.Hash Crypto/Hash.hs:(81,1)-(86,32) 5966 1 0.0 0.0 0.0 0.0 + copyAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:(237,1)-(240,21) 5968 1 0.0 0.0 0.0 0.0 + null Data.ByteArray.Methods Data/ByteArray/Methods.hs:92:1-22 5967 1 0.0 0.0 0.0 0.0 + null Data.ByteArray.Methods Data/ByteArray/Methods.hs:92:1-22 5965 1 0.0 0.0 0.0 0.0 + unpack Data.ByteArray.Methods Data/ByteArray/Methods.hs:(104,1)-(110,34) 5980 1 0.0 0.0 0.0 0.0 + unsafeCast Basement.Block Basement/Block.hs:421:1-32 5981 33 0.0 0.0 0.0 0.0 + withPtr Basement.Block.Base Basement/Block/Base.hs:(402,1)-(411,31) 5982 32 0.0 0.0 0.0 0.0 + isPinned Basement.Block.Base Basement/Block/Base.hs:97:1-67 5983 32 0.0 0.0 0.0 0.0 + compatIsByteArrayPinned# Basement.Compat.Primitive Basement/Compat/Primitive.hs:67:1-51 5984 32 0.0 0.0 0.0 0.0 + toPinnedStatus# Basement.Compat.Primitive Basement/Compat/Primitive.hs:(47,1)-(48,27) 5985 32 0.0 0.0 0.0 0.0 + unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 5986 32 0.0 0.0 0.0 0.0 + word EVM.Types src/EVM/Types.hs:521:1-21 5960 0 0.0 0.0 0.0 0.0 + word256 EVM.Types src/EVM/Types.hs:(510,1)-(518,67) 5987 1 0.0 0.0 0.0 0.0 + padLeft EVM.Types src/EVM/Types.hs:495:1-54 5988 1 0.0 0.0 0.0 0.0 + bytesRead Data.Serialize.Get src/Data/Serialize/Get.hs:838:1-45 5989 0 0.0 0.0 0.0 0.0 + exec1 EVM src/EVM.hs:(547,1)-(1323,42) 4428 1 0.0 0.0 0.0 0.0 + genLiteral Data.SBV.Core.Model Data/SBV/Core/Model.hs:99:1-48 4558 3 0.0 0.0 0.0 0.0 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 4562 3 0.0 0.0 0.0 0.0 + svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 4563 3 0.0 0.0 0.0 0.0 + svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 4564 3 0.0 0.0 0.0 0.0 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 4565 3 0.0 0.0 0.0 0.0 + finishFrame EVM src/EVM.hs:(2237,1)-(2357,20) 5235 1 0.0 0.0 0.0 0.0 + next EVM src/EVM.hs:543:1-46 4513 1 0.0 0.0 0.0 0.0 + opSize EVM src/EVM.hs:(2542,1)-(2543,37) 4515 1 0.0 0.0 0.0 0.0 + num EVM.Types src/EVM/Types.hs:492:1-18 5952 1 0.0 0.0 0.0 0.0 + forceConcrete EVM src/EVM.hs:(1846,1)-(1848,22) 4484 0 0.0 0.0 0.0 0.0 + next EVM src/EVM.hs:543:1-46 4485 1 0.0 0.0 0.0 0.0 + opSize EVM src/EVM.hs:(2542,1)-(2543,37) 4487 1 0.0 0.0 0.0 0.0 + litWord EVM.Symbolic src/EVM/Symbolic.hs:24:1-52 6150 0 0.0 0.0 0.0 0.0 + limitStack EVM src/EVM.hs:(1809,1)-(1813,17) 4615 0 0.0 0.0 0.0 0.0 + next EVM src/EVM.hs:543:1-46 4616 1 0.0 0.0 0.0 0.0 + opSize EVM src/EVM.hs:(2542,1)-(2543,37) 4617 1 0.0 0.0 0.0 0.0 + litWord EVM.Symbolic src/EVM/Symbolic.hs:24:1-52 5176 0 0.0 0.0 0.0 0.0 + litWord EVM.Symbolic src/EVM/Symbolic.hs:24:1-52 6099 0 0.0 0.0 0.0 0.0 + notStatic EVM src/EVM.hs:(1816,1)-(1820,17) 4611 0 0.0 0.0 0.0 0.0 + next EVM src/EVM.hs:543:1-46 4612 1 0.0 0.0 0.0 0.0 + opSize EVM src/EVM.hs:(2542,1)-(2543,37) 4614 1 0.0 0.0 0.0 0.0 + stackOp2 EVM src/EVM.hs:(2500,1)-(2507,14) 4573 0 0.0 0.0 0.0 0.0 + .^ Data.SBV.Core.Model Data/SBV/Core/Model.hs:(1262,1)-(1280,49) 4575 0 0.0 0.0 0.0 0.0 + genLiteral Data.SBV.Core.Model Data/SBV/Core/Model.hs:99:1-48 4584 1 0.0 0.0 0.0 0.0 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 4585 1 0.0 0.0 0.0 0.0 + svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 4586 1 0.0 0.0 0.0 0.0 + svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 4587 1 0.0 0.0 0.0 0.0 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 4588 1 0.0 0.0 0.0 0.0 + finalize EVM src/EVM.hs:(1721,1)-(1790,66) 4712 1 0.0 0.0 0.0 0.0 + initialContract EVM src/EVM.hs:(516,1)-(533,39) 4759 1 0.0 0.0 0.0 0.0 + mkCodeOps EVM src/EVM.hs:(2721,1)-(2739,79) 4791 1 0.0 0.0 0.0 0.0 + marray# Data.Primitive.Array Data/Primitive/Array.hs:92:5-11 4796 1 0.0 0.0 0.0 0.0 + sChunks Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:122:30-36 4794 1 0.0 0.0 0.0 0.0 + sSize Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:124:30-34 4793 1 0.0 0.0 0.0 0.0 + unId Data.Vector.Fusion.Util Data/Vector/Fusion/Util.hs:25:21-24 4795 1 0.0 0.0 0.0 0.0 + upperBound Data.Vector.Fusion.Bundle.Size Data/Vector/Fusion/Bundle/Size.hs:(126,1)-(128,30) 4792 1 0.0 0.0 0.0 0.0 + mkOpIxMap EVM src/EVM.hs:(2549,1)-(2586,83) 4789 1 0.0 0.0 0.0 0.0 + len EVM.Symbolic src/EVM/Symbolic.hs:(161,1)-(162,38) 4790 1 0.0 0.0 0.0 0.0 + stripBytecodeMetadata EVM.Solidity src/EVM/Solidity.hs:(569,1)-(573,22) 4767 1 0.0 0.0 0.0 0.0 + keccak EVM.Types src/EVM/Types.hs:(580,1)-(583,12) 4760 0 0.0 0.0 0.0 0.0 + keccakBytes EVM.Types src/EVM/Types.hs:(570,1)-(573,15) 4762 0 0.0 0.0 0.0 0.0 + hash Crypto.Hash Crypto/Hash.hs:58:1-47 4763 1 0.0 0.0 0.0 0.0 + hashFinalize Crypto.Hash Crypto/Hash.hs:(92,1)-(95,17) 4764 1 0.0 0.0 0.0 0.0 + allocAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:74:1-45 4770 1 0.0 0.0 0.0 0.0 + new Basement.Block.Base Basement/Block/Base.hs:304:1-76 4771 1 0.0 0.0 0.0 0.0 + unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 4772 1 0.0 0.0 0.0 0.0 + withMutablePtrHint Basement.Block.Base Basement/Block/Base.hs:(475,1)-(489,39) 4773 1 0.0 0.0 0.0 0.0 + copy Data.ByteArray.Methods Data/ByteArray/Methods.hs:(223,1)-(226,21) 4778 1 0.0 0.0 0.0 0.0 + isMutablePinned Basement.Block.Base Basement/Block/Base.hs:100:1-90 4774 1 0.0 0.0 0.0 0.0 + compatIsMutableByteArrayPinned# Basement.Compat.Primitive Basement/Compat/Primitive.hs:70:1-65 4775 1 0.0 0.0 0.0 0.0 + toPinnedStatus# Basement.Compat.Primitive Basement/Compat/Primitive.hs:(47,1)-(48,27) 4776 1 0.0 0.0 0.0 0.0 + unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 4777 1 0.0 0.0 0.0 0.0 + hashInit Crypto.Hash Crypto/Hash.hs:(66,1)-(67,24) 4768 1 0.0 0.0 0.0 0.0 + allocAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:74:1-45 4769 1 0.0 0.0 0.0 0.0 + hashUpdate Crypto.Hash Crypto/Hash.hs:(71,1)-(73,37) 4765 1 0.0 0.0 0.0 0.0 + null Data.ByteArray.Methods Data/ByteArray/Methods.hs:92:1-22 4766 1 0.0 0.0 0.0 0.0 + unpack Data.ByteArray.Methods Data/ByteArray/Methods.hs:(104,1)-(110,34) 4779 1 0.0 0.0 0.0 0.0 + unsafeCast Basement.Block Basement/Block.hs:421:1-32 4780 33 0.0 0.0 0.0 0.0 + withPtr Basement.Block.Base Basement/Block/Base.hs:(402,1)-(411,31) 4781 32 0.0 0.0 0.0 0.0 + isPinned Basement.Block.Base Basement/Block/Base.hs:97:1-67 4782 32 0.0 0.0 0.0 0.0 + compatIsByteArrayPinned# Basement.Compat.Primitive Basement/Compat/Primitive.hs:67:1-51 4783 32 0.0 0.0 0.0 0.0 + toPinnedStatus# Basement.Compat.Primitive Basement/Compat/Primitive.hs:(47,1)-(48,27) 4784 32 0.0 0.0 0.0 0.0 + unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 4785 32 0.0 0.0 0.0 0.0 + word EVM.Types src/EVM/Types.hs:521:1-21 4761 0 0.0 0.0 0.0 0.0 + word256 EVM.Types src/EVM/Types.hs:(510,1)-(518,67) 4786 1 0.0 0.0 0.0 0.0 + padLeft EVM.Types src/EVM/Types.hs:495:1-54 4787 1 0.0 0.0 0.0 0.0 + bytesRead Data.Serialize.Get src/Data/Serialize/Get.hs:838:1-45 4788 0 0.0 0.0 0.0 0.0 + popTrace EVM src/EVM.hs:(2450,1)-(2454,42) 4895 1 0.0 0.0 0.0 0.0 + push EVM src/EVM.hs:2474:1-30 5203 1 0.0 0.0 0.0 0.0 + num EVM.Types src/EVM/Types.hs:492:1-18 5212 1 0.0 0.0 0.0 0.0 + resetState EVM src/EVM.hs:(2210,1)-(2213,26) 4837 1 0.0 0.0 0.0 0.0 + touchAccount EVM src/EVM.hs:1895:1-57 4715 1 0.0 0.0 0.0 0.0 + accessMemoryRange EVM src/EVM.hs:(2383,1)-(2387,53) 4459 0 0.0 0.0 0.0 0.0 + accessMemoryWord EVM src/EVM.hs:2391:1-53 4457 0 0.0 0.0 0.0 0.0 + accessStorage EVM src/EVM.hs:(1674,1)-(1702,35) 4530 0 0.0 0.0 0.0 0.0 + genLiteral Data.SBV.Core.Model Data/SBV/Core/Model.hs:99:1-48 4545 1 0.0 0.0 0.0 0.0 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 4595 1 0.0 0.0 0.0 0.0 + svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 4596 1 0.0 0.0 0.0 0.0 + svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 4597 1 0.0 0.0 0.0 0.0 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 4598 1 0.0 0.0 0.0 0.0 + accessUnboundedMemoryRange EVM src/EVM.hs:(2368,1)-(2375,14) 4474 0 0.0 0.0 0.0 0.0 + num EVM.Types src/EVM/Types.hs:492:1-18 4478 1 0.0 0.0 0.0 0.0 + accountEmpty EVM src/EVM.hs:(1712,1)-(1717,26) 4800 0 0.0 0.0 0.0 0.0 + burn EVM src/EVM.hs:(1826,1)-(1838,38) 4441 0 0.1 0.0 0.1 0.0 + copyBytesToMemory EVM src/EVM.hs:(2395,1)-(2400,45) 4661 0 0.0 0.0 0.0 0.0 + copyCallBytesToMemory EVM src/EVM.hs:(2404,1)-(2409,66) 6268 0 0.0 0.0 0.0 0.0 + costOfCall EVM src/EVM.hs:(2748,1)-(2762,40) 6070 0 0.0 0.0 0.0 0.0 + create EVM src/EVM.hs:(2123,1)-(2184,30) 5123 0 0.0 0.0 0.0 0.0 + litWord EVM.Symbolic src/EVM/Symbolic.hs:24:1-52 5124 0 0.0 0.0 0.0 0.0 + delegateCall EVM src/EVM.hs:(2052,1)-(2108,31) 6024 0 0.0 0.0 0.0 0.0 + finishFrame EVM src/EVM.hs:(2237,1)-(2357,20) 5202 0 0.0 0.0 0.0 0.0 + initialContract EVM src/EVM.hs:(516,1)-(533,39) 4799 0 0.0 0.0 0.0 0.0 + makeVm EVM src/EVM.hs:(449,1)-(512,30) 4423 0 0.0 0.0 0.0 0.0 + CAF EVM.ABI 3446 0 0.0 0.0 0.0 0.0 + abiKind EVM.ABI src/EVM/ABI.hs:(191,1)-(197,33) 5601 1 0.0 0.0 0.0 0.0 + abiTypeSolidity EVM.ABI src/EVM/ABI.hs:(213,1)-(223,104) 6439 1 0.0 0.0 0.0 0.0 + abiValueType EVM.ABI src/EVM/ABI.hs:(200,1)-(210,58) 5603 1 0.0 0.0 0.0 0.0 + decodeAbiValue EVM.ABI src/EVM/ABI.hs:364:1-32 5888 1 0.0 0.0 0.0 0.0 + emptyAbi EVM.ABI src/EVM/ABI.hs:429:1-26 4953 1 0.0 0.0 0.0 0.0 + marray# Data.Primitive.Array Data/Primitive/Array.hs:92:5-11 4958 1 0.0 0.0 0.0 0.0 + sChunks Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:122:30-36 4956 1 0.0 0.0 0.0 0.0 + sSize Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:124:30-34 4955 1 0.0 0.0 0.0 0.0 + unId Data.Vector.Fusion.Util Data/Vector/Fusion/Util.hs:25:21-24 4957 1 0.0 0.0 0.0 0.0 + upperBound Data.Vector.Fusion.Bundle.Size Data/Vector/Fusion/Bundle/Size.hs:(126,1)-(128,30) 4954 1 0.0 0.0 0.0 0.0 + encodeAbiValue EVM.ABI src/EVM/ABI.hs:361:1-50 6372 1 0.0 0.0 0.0 0.0 + genAbiValue EVM.ABI src/EVM/ABI.hs:(440,1)-(466,62) 5584 1 0.0 0.0 0.0 0.0 + sized Test.QuickCheck.Gen Test/QuickCheck/Gen.hs:99:1-52 5620 1 0.0 0.0 0.0 0.0 + getAbi EVM.ABI src/EVM/ABI.hs:(226,1)-(259,66) 5891 1 0.0 0.0 0.0 0.0 + parseTypeName EVM.ABI src/EVM/ABI.hs:375:1-50 5606 1 0.0 0.0 0.0 0.0 + putAbi EVM.ABI src/EVM/ABI.hs:(262,1)-(291,15) 4951 1 0.0 0.0 0.0 0.0 + CAF EVM.Concrete 3445 0 0.0 0.0 0.0 0.0 + readMemoryWord EVM.Concrete src/EVM/Concrete.hs:(62,1)-(70,19) 4988 0 0.0 0.0 0.0 0.0 + setMemoryWord EVM.Concrete src/EVM/Concrete.hs:(82,1)-(83,43) 4692 0 0.0 0.0 0.0 0.0 + CAF EVM.Dapp 3444 0 0.0 0.0 0.0 0.0 + unitTestMarkerAbi EVM.Dapp src/EVM/Dapp.hs:111:1-54 4204 1 0.0 0.0 0.0 0.0 + abiKeccak EVM.Types src/EVM/Types.hs:(586,1)-(590,14) 4205 0 0.0 0.0 0.0 0.0 + word32 EVM.Types src/EVM/Types.hs:(576,1)-(577,52) 4232 1 0.0 0.0 0.0 0.0 + keccakBytes EVM.Types src/EVM/Types.hs:(570,1)-(573,15) 4206 0 0.0 0.0 0.0 0.0 + hash Crypto.Hash Crypto/Hash.hs:58:1-47 4207 1 0.0 0.0 0.0 0.0 + hashFinalize Crypto.Hash Crypto/Hash.hs:(92,1)-(95,17) 4208 1 0.0 0.0 0.0 0.0 + allocAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:74:1-45 4216 1 0.0 0.0 0.0 0.0 + new Basement.Block.Base Basement/Block/Base.hs:304:1-76 4217 1 0.0 0.0 0.0 0.0 + unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 4218 1 0.0 0.0 0.0 0.0 + withMutablePtrHint Basement.Block.Base Basement/Block/Base.hs:(475,1)-(489,39) 4219 1 0.0 0.0 0.0 0.0 + copy Data.ByteArray.Methods Data/ByteArray/Methods.hs:(223,1)-(226,21) 4224 1 0.0 0.0 0.0 0.0 + isMutablePinned Basement.Block.Base Basement/Block/Base.hs:100:1-90 4220 1 0.0 0.0 0.0 0.0 + compatIsMutableByteArrayPinned# Basement.Compat.Primitive Basement/Compat/Primitive.hs:70:1-65 4221 1 0.0 0.0 0.0 0.0 + toPinnedStatus# Basement.Compat.Primitive Basement/Compat/Primitive.hs:(47,1)-(48,27) 4222 1 0.0 0.0 0.0 0.0 + unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 4223 1 0.0 0.0 0.0 0.0 + hashInit Crypto.Hash Crypto/Hash.hs:(66,1)-(67,24) 4214 1 0.0 0.0 0.0 0.0 + allocAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:74:1-45 4215 1 0.0 0.0 0.0 0.0 + hashUpdate Crypto.Hash Crypto/Hash.hs:(71,1)-(73,37) 4209 1 0.0 0.0 0.0 0.0 + hashUpdates Crypto.Hash Crypto/Hash.hs:(81,1)-(86,32) 4211 1 0.0 0.0 0.0 0.0 + copyAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:(237,1)-(240,21) 4213 1 0.0 0.0 0.0 0.0 + null Data.ByteArray.Methods Data/ByteArray/Methods.hs:92:1-22 4212 1 0.0 0.0 0.0 0.0 + null Data.ByteArray.Methods Data/ByteArray/Methods.hs:92:1-22 4210 1 0.0 0.0 0.0 0.0 + unpack Data.ByteArray.Methods Data/ByteArray/Methods.hs:(104,1)-(110,34) 4225 1 0.0 0.0 0.0 0.0 + unsafeCast Basement.Block Basement/Block.hs:421:1-32 4226 33 0.0 0.0 0.0 0.0 + withPtr Basement.Block.Base Basement/Block/Base.hs:(402,1)-(411,31) 4227 32 0.0 0.0 0.0 0.0 + isPinned Basement.Block.Base Basement/Block/Base.hs:97:1-67 4228 32 0.0 0.0 0.0 0.0 + compatIsByteArrayPinned# Basement.Compat.Primitive Basement/Compat/Primitive.hs:67:1-51 4229 32 0.0 0.0 0.0 0.0 + toPinnedStatus# Basement.Compat.Primitive Basement/Compat/Primitive.hs:(47,1)-(48,27) 4230 32 0.0 0.0 0.0 0.0 + unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 4231 32 0.0 0.0 0.0 0.0 + unitTestMethods EVM.Dapp src/EVM/Dapp.hs:(150,1)-(155,27) 4234 1 0.0 0.0 0.0 0.0 + mkTest EVM.Dapp src/EVM/Dapp.hs:(117,1)-(120,23) 4237 0 0.0 0.0 0.0 0.0 + CAF EVM.Format 3437 0 0.0 0.0 0.0 0.0 + parenthesise EVM.Format src/EVM/Format.hs:112:1-51 6438 0 0.0 0.0 0.0 0.0 + showAbiValue EVM.Format src/EVM/Format.hs:(83,1)-(96,30) 6469 0 0.0 0.0 0.0 0.0 + CAF EVM.RLP 3431 0 0.0 0.0 0.0 0.0 + rlpAddrFull EVM.RLP src/EVM/RLP.hs:85:1-38 4353 1 0.0 0.0 0.0 0.0 + num EVM.Types src/EVM/Types.hs:492:1-18 4356 1 0.0 0.0 0.0 0.0 + octets EVM.RLP src/EVM/RLP.hs:(66,1)-(67,85) 4364 0 0.0 0.0 0.0 0.0 + rlpWord256 EVM.RLP src/EVM/RLP.hs:(78,1)-(79,28) 4362 0 0.0 0.0 0.0 0.0 + CAF EVM.Solidity 3430 0 0.0 0.0 0.0 0.0 + makeSrcMaps EVM.Solidity src/EVM/Solidity.hs:(227,1)-(271,126) 4202 1 0.0 0.0 0.0 0.0 + readJSON EVM.Solidity src/EVM/Solidity.hs:(329,1)-(331,28) 3839 0 0.0 0.0 0.0 0.0 + readStdJSON EVM.Solidity src/EVM/Solidity.hs:(364,1)-(407,39) 3922 0 0.0 0.0 0.0 0.0 + union Data.HashMap.Base Data/HashMap/Base.hs:1287:1-23 3928 1 0.0 0.0 0.0 0.0 + signature EVM.Solidity src/EVM/Solidity.hs:(468,1)-(478,7) 4174 0 0.0 0.0 0.0 0.0 + CAF EVM.Stepper 3429 0 0.0 0.0 0.0 0.0 + evm EVM.Stepper src/EVM/Stepper.hs:78:1-21 4277 1 0.0 0.0 0.0 0.0 + exec EVM.Stepper src/EVM/Stepper.hs:66:1-21 4292 1 0.0 0.0 0.0 0.0 + execFully EVM.Stepper src/EVM/Stepper.hs:(82,1)-(91,20) 4291 1 0.0 0.0 0.0 0.0 + interpret EVM.Stepper src/EVM/Stepper.hs:(117,1)-(141,33) 4293 0 0.0 0.0 0.0 0.0 + exec EVM.Exec src/EVM/Exec.hs:(48,1)-(51,23) 4294 129 0.0 0.0 0.0 0.0 + CAF EVM.Symbolic 3428 0 0.0 0.0 0.0 0.0 + litAddr EVM.Symbolic src/EVM/Symbolic.hs:27:1-36 4389 1 0.0 0.0 0.0 0.0 + readMemoryWord EVM.Symbolic src/EVM/Symbolic.hs:(183,1)-(184,75) 5015 0 0.0 0.0 0.0 0.0 + litWord EVM.Symbolic src/EVM/Symbolic.hs:24:1-52 5016 0 0.0 0.0 0.0 0.0 + readMemoryWord32 EVM.Symbolic src/EVM/Symbolic.hs:(187,1)-(188,75) 6263 0 0.0 0.0 0.0 0.0 + num EVM.Types src/EVM/Types.hs:492:1-18 6264 0 0.0 0.0 0.0 0.0 + readSWordWithBound EVM.Symbolic src/EVM/Symbolic.hs:(136,1)-(157,48) 4981 0 0.0 0.0 0.0 0.0 + litWord EVM.Symbolic src/EVM/Symbolic.hs:24:1-52 4982 0 0.0 0.0 0.0 0.0 + slt EVM.Symbolic src/EVM/Symbolic.hs:(75,1)-(76,79) 5678 0 0.0 0.0 0.0 0.0 + genLiteral Data.SBV.Core.Model Data/SBV/Core/Model.hs:99:1-48 5706 1 0.0 0.0 0.0 0.0 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 5707 1 0.0 0.0 0.0 0.0 + svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 5708 1 0.0 0.0 0.0 0.0 + svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 5709 1 0.0 0.0 0.0 0.0 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 5710 1 0.0 0.0 0.0 0.0 + CAF EVM.Transaction 3426 0 0.0 0.0 0.0 0.0 + setupTx EVM.Transaction src/EVM/Transaction.hs:(171,1)-(176,38) 5289 0 0.0 0.0 0.0 0.0 + CAF EVM.Types 3423 0 0.0 0.0 0.0 0.0 + abiKeccak EVM.Types src/EVM/Types.hs:(586,1)-(590,14) 4166 1 0.0 0.0 0.0 0.0 + keccak EVM.Types src/EVM/Types.hs:(580,1)-(583,12) 4125 1 0.0 0.0 0.0 0.0 + keccakBytes EVM.Types src/EVM/Types.hs:(570,1)-(573,15) 4129 1 0.0 0.0 0.0 0.0 + word EVM.Types src/EVM/Types.hs:521:1-21 4127 1 0.0 0.0 0.0 0.0 + hexText EVM.Types src/EVM/Types.hs:(460,1)-(463,52) 6382 0 0.0 0.0 0.0 0.0 + w256lit EVM.Types src/EVM/Types.hs:346:1-48 4451 0 0.0 0.0 0.0 0.0 + CAF EVM.UnitTest 3422 0 0.0 0.0 0.0 0.0 + defaultBalanceForCreator EVM.UnitTest src/EVM/UnitTest.hs:129:1-53 4891 1 0.0 0.0 0.0 0.0 + defaultGasForCreating EVM.UnitTest src/EVM/UnitTest.hs:123:1-38 4392 1 0.0 0.0 0.0 0.0 + defaultGasForInvoking EVM.UnitTest src/EVM/UnitTest.hs:126:1-38 4894 1 0.0 0.0 0.0 0.0 + defaultMaxCodeSize EVM.UnitTest src/EVM/UnitTest.hs:135:1-31 4395 1 0.0 0.0 0.0 0.0 + execWithTraceId EVM.UnitTest src/EVM/UnitTest.hs:(282,1)-(283,51) 5335 1 0.0 0.0 0.0 0.0 + runWithTraceId EVM.UnitTest src/EVM/UnitTest.hs:(286,1)-(301,90) 5337 1 0.0 0.0 0.0 0.0 + abiCall EVM.UnitTest src/EVM/UnitTest.hs:(842,1)-(845,53) 4914 0 0.0 0.0 0.0 0.0 + litWord EVM.Symbolic src/EVM/Symbolic.hs:24:1-52 4915 0 0.0 0.0 0.0 0.0 + checkFailures EVM.UnitTest src/EVM/UnitTest.hs:(195,1)-(210,58) 5765 0 0.0 0.0 0.0 0.0 + failOutput EVM.UnitTest src/EVM/UnitTest.hs:(756,1)-(767,3) 6423 0 0.0 0.0 0.0 0.0 + formatTestLog EVM.UnitTest src/EVM/UnitTest.hs:(779,1)-(835,61) 6450 0 0.0 0.0 0.0 0.0 + formatTestLogs EVM.UnitTest src/EVM/UnitTest.hs:(770,1)-(773,47) 6451 0 0.0 0.0 0.0 0.0 + fuzzRun EVM.UnitTest src/EVM/UnitTest.hs:(586,1)-(615,40) 5940 0 0.0 0.0 0.0 0.0 + getParametersFromEnvironmentVariables EVM.UnitTest src/EVM/UnitTest.hs:(910,1)-(942,38) 4341 0 0.0 0.0 0.0 0.0 + createAddress EVM.Concrete src/EVM/Concrete.hs:108:1-72 4342 1 0.0 0.0 0.0 0.0 + num EVM.Types src/EVM/Types.hs:492:1-18 4343 1 0.0 0.0 0.0 0.0 + rlpList EVM.RLP src/EVM/RLP.hs:63:1-30 4351 1 0.0 0.0 0.0 0.0 + rlpencode EVM.RLP src/EVM/RLP.hs:(50,1)-(52,70) 4352 3 0.0 0.0 0.0 0.0 + encodeLen EVM.RLP src/EVM/RLP.hs:(55,1)-(60,44) 4359 2 0.0 0.0 0.0 0.0 + num EVM.Types src/EVM/Types.hs:492:1-18 4360 2 0.0 0.0 0.0 0.0 + rlpWord256 EVM.RLP src/EVM/RLP.hs:(78,1)-(79,28) 4361 1 0.0 0.0 0.0 0.0 + octets EVM.RLP src/EVM/RLP.hs:(66,1)-(67,85) 4363 1 0.0 0.0 0.0 0.0 + keccak EVM.Types src/EVM/Types.hs:(580,1)-(583,12) 4344 0 0.0 0.0 0.0 0.0 + keccakBytes EVM.Types src/EVM/Types.hs:(570,1)-(573,15) 4346 0 0.0 0.0 0.0 0.0 + hash Crypto.Hash Crypto/Hash.hs:58:1-47 4347 1 0.0 0.0 0.0 0.0 + hashFinalize Crypto.Hash Crypto/Hash.hs:(92,1)-(95,17) 4348 1 0.0 0.0 0.0 0.0 + allocAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:74:1-45 4370 1 0.0 0.0 0.0 0.0 + new Basement.Block.Base Basement/Block/Base.hs:304:1-76 4371 1 0.0 0.0 0.0 0.0 + unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 4372 1 0.0 0.0 0.0 0.0 + withMutablePtrHint Basement.Block.Base Basement/Block/Base.hs:(475,1)-(489,39) 4373 1 0.0 0.0 0.0 0.0 + copy Data.ByteArray.Methods Data/ByteArray/Methods.hs:(223,1)-(226,21) 4378 1 0.0 0.0 0.0 0.0 + isMutablePinned Basement.Block.Base Basement/Block/Base.hs:100:1-90 4374 1 0.0 0.0 0.0 0.0 + compatIsMutableByteArrayPinned# Basement.Compat.Primitive Basement/Compat/Primitive.hs:70:1-65 4375 1 0.0 0.0 0.0 0.0 + toPinnedStatus# Basement.Compat.Primitive Basement/Compat/Primitive.hs:(47,1)-(48,27) 4376 1 0.0 0.0 0.0 0.0 + unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 4377 1 0.0 0.0 0.0 0.0 + hashInit Crypto.Hash Crypto/Hash.hs:(66,1)-(67,24) 4368 1 0.0 0.0 0.0 0.0 + allocAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:74:1-45 4369 1 0.0 0.0 0.0 0.0 + hashUpdate Crypto.Hash Crypto/Hash.hs:(71,1)-(73,37) 4349 1 0.0 0.0 0.0 0.0 + hashUpdates Crypto.Hash Crypto/Hash.hs:(81,1)-(86,32) 4365 1 0.0 0.0 0.0 0.0 + copyAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:(237,1)-(240,21) 4367 1 0.0 0.0 0.0 0.0 + null Data.ByteArray.Methods Data/ByteArray/Methods.hs:92:1-22 4366 1 0.0 0.0 0.0 0.0 + null Data.ByteArray.Methods Data/ByteArray/Methods.hs:92:1-22 4350 1 0.0 0.0 0.0 0.0 + unpack Data.ByteArray.Methods Data/ByteArray/Methods.hs:(104,1)-(110,34) 4379 1 0.0 0.0 0.0 0.0 + unsafeCast Basement.Block Basement/Block.hs:421:1-32 4380 33 0.0 0.0 0.0 0.0 + withPtr Basement.Block.Base Basement/Block/Base.hs:(402,1)-(411,31) 4381 32 0.0 0.0 0.0 0.0 + isPinned Basement.Block.Base Basement/Block/Base.hs:97:1-67 4382 32 0.0 0.0 0.0 0.0 + compatIsByteArrayPinned# Basement.Compat.Primitive Basement/Compat/Primitive.hs:67:1-51 4383 32 0.0 0.0 0.0 0.0 + toPinnedStatus# Basement.Compat.Primitive Basement/Compat/Primitive.hs:(47,1)-(48,27) 4384 32 0.0 0.0 0.0 0.0 + unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 4385 32 0.0 0.0 0.0 0.0 + word EVM.Types src/EVM/Types.hs:521:1-21 4345 0 0.0 0.0 0.0 0.0 + word256 EVM.Types src/EVM/Types.hs:(510,1)-(518,67) 4386 1 0.0 0.0 0.0 0.0 + padLeft EVM.Types src/EVM/Types.hs:495:1-54 4387 1 0.0 0.0 0.0 0.0 + bytesRead Data.Serialize.Get src/Data/Serialize/Get.hs:838:1-45 4388 0 0.0 0.0 0.0 0.0 + rlpAddrFull EVM.RLP src/EVM/RLP.hs:85:1-38 4354 0 0.0 0.0 0.0 0.0 + octetsFull EVM.RLP src/EVM/RLP.hs:(70,1)-(71,67) 4355 1 0.0 0.0 0.0 0.0 + num EVM.Types src/EVM/Types.hs:492:1-18 4357 0 0.0 0.0 0.0 0.0 + indentLines EVM.UnitTest src/EVM/UnitTest.hs:(736,1)-(738,45) 6501 0 0.0 0.0 0.0 0.0 + initialUnitTestVm EVM.UnitTest src/EVM/UnitTest.hs:(862,1)-(892,61) 4340 0 0.0 0.0 0.0 0.0 + genLiteral Data.SBV.Core.Model Data/SBV/Core/Model.hs:99:1-48 4618 1 0.0 0.0 0.0 0.0 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 4619 1 0.0 0.0 0.0 0.0 + initialContract EVM src/EVM.hs:(516,1)-(533,39) 4718 1 0.0 0.0 0.0 0.0 + mkCodeOps EVM src/EVM.hs:(2721,1)-(2739,79) 4750 1 0.0 0.0 0.0 0.0 + marray# Data.Primitive.Array Data/Primitive/Array.hs:92:5-11 4755 1 0.0 0.0 0.0 0.0 + sChunks Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:122:30-36 4753 1 0.0 0.0 0.0 0.0 + sSize Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:124:30-34 4752 1 0.0 0.0 0.0 0.0 + unId Data.Vector.Fusion.Util Data/Vector/Fusion/Util.hs:25:21-24 4754 1 0.0 0.0 0.0 0.0 + upperBound Data.Vector.Fusion.Bundle.Size Data/Vector/Fusion/Bundle/Size.hs:(126,1)-(128,30) 4751 1 0.0 0.0 0.0 0.0 + mkOpIxMap EVM src/EVM.hs:(2549,1)-(2586,83) 4748 1 0.0 0.0 0.0 0.0 + len EVM.Symbolic src/EVM/Symbolic.hs:(161,1)-(162,38) 4749 1 0.0 0.0 0.0 0.0 + stripBytecodeMetadata EVM.Solidity src/EVM/Solidity.hs:(569,1)-(573,22) 4726 1 0.0 0.0 0.0 0.0 + keccak EVM.Types src/EVM/Types.hs:(580,1)-(583,12) 4719 0 0.0 0.0 0.0 0.0 + keccakBytes EVM.Types src/EVM/Types.hs:(570,1)-(573,15) 4721 0 0.0 0.0 0.0 0.0 + hash Crypto.Hash Crypto/Hash.hs:58:1-47 4722 1 0.0 0.0 0.0 0.0 + hashFinalize Crypto.Hash Crypto/Hash.hs:(92,1)-(95,17) 4723 1 0.0 0.0 0.0 0.0 + allocAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:74:1-45 4729 1 0.0 0.0 0.0 0.0 + new Basement.Block.Base Basement/Block/Base.hs:304:1-76 4730 1 0.0 0.0 0.0 0.0 + unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 4731 1 0.0 0.0 0.0 0.0 + withMutablePtrHint Basement.Block.Base Basement/Block/Base.hs:(475,1)-(489,39) 4732 1 0.0 0.0 0.0 0.0 + copy Data.ByteArray.Methods Data/ByteArray/Methods.hs:(223,1)-(226,21) 4737 1 0.0 0.0 0.0 0.0 + isMutablePinned Basement.Block.Base Basement/Block/Base.hs:100:1-90 4733 1 0.0 0.0 0.0 0.0 + compatIsMutableByteArrayPinned# Basement.Compat.Primitive Basement/Compat/Primitive.hs:70:1-65 4734 1 0.0 0.0 0.0 0.0 + toPinnedStatus# Basement.Compat.Primitive Basement/Compat/Primitive.hs:(47,1)-(48,27) 4735 1 0.0 0.0 0.0 0.0 + unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 4736 1 0.0 0.0 0.0 0.0 + hashInit Crypto.Hash Crypto/Hash.hs:(66,1)-(67,24) 4727 1 0.0 0.0 0.0 0.0 + allocAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:74:1-45 4728 1 0.0 0.0 0.0 0.0 + hashUpdate Crypto.Hash Crypto/Hash.hs:(71,1)-(73,37) 4724 1 0.0 0.0 0.0 0.0 + null Data.ByteArray.Methods Data/ByteArray/Methods.hs:92:1-22 4725 1 0.0 0.0 0.0 0.0 + unpack Data.ByteArray.Methods Data/ByteArray/Methods.hs:(104,1)-(110,34) 4738 1 0.0 0.0 0.0 0.0 + unsafeCast Basement.Block Basement/Block.hs:421:1-32 4739 33 0.0 0.0 0.0 0.0 + withPtr Basement.Block.Base Basement/Block/Base.hs:(402,1)-(411,31) 4740 32 0.0 0.0 0.0 0.0 + isPinned Basement.Block.Base Basement/Block/Base.hs:97:1-67 4741 32 0.0 0.0 0.0 0.0 + compatIsByteArrayPinned# Basement.Compat.Primitive Basement/Compat/Primitive.hs:67:1-51 4742 32 0.0 0.0 0.0 0.0 + toPinnedStatus# Basement.Compat.Primitive Basement/Compat/Primitive.hs:(47,1)-(48,27) 4743 32 0.0 0.0 0.0 0.0 + unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 4744 32 0.0 0.0 0.0 0.0 + word EVM.Types src/EVM/Types.hs:521:1-21 4720 0 0.0 0.0 0.0 0.0 + word256 EVM.Types src/EVM/Types.hs:(510,1)-(518,67) 4745 1 0.0 0.0 0.0 0.0 + padLeft EVM.Types src/EVM/Types.hs:495:1-54 4746 1 0.0 0.0 0.0 0.0 + bytesRead Data.Serialize.Get src/Data/Serialize/Get.hs:838:1-45 4747 0 0.0 0.0 0.0 0.0 + svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 4620 1 0.0 0.0 0.0 0.0 + svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 4621 1 0.0 0.0 0.0 0.0 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 4622 1 0.0 0.0 0.0 0.0 + berlin EVM.FeeSchedule src/EVM/FeeSchedule.hs:185:1-25 4397 0 0.0 0.0 0.0 0.0 + eip2929 EVM.FeeSchedule src/EVM/FeeSchedule.hs:(175,1)-(182,3) 4398 1 0.0 0.0 0.0 0.0 + istanbul EVM.FeeSchedule src/EVM/FeeSchedule.hs:170:1-61 4399 1 0.0 0.0 0.0 0.0 + eip1108 EVM.FeeSchedule src/EVM/FeeSchedule.hs:(136,1)-(141,3) 4407 1 0.0 0.0 0.0 0.0 + eip1884 EVM.FeeSchedule src/EVM/FeeSchedule.hs:(146,1)-(150,3) 4406 1 0.0 0.0 0.0 0.0 + eip2028 EVM.FeeSchedule src/EVM/FeeSchedule.hs:(155,1)-(157,3) 4405 1 0.0 0.0 0.0 0.0 + eip2200 EVM.FeeSchedule src/EVM/FeeSchedule.hs:(162,1)-(167,3) 4404 1 0.0 0.0 0.0 0.0 + metropolis EVM.FeeSchedule src/EVM/FeeSchedule.hs:131:1-40 4400 1 0.0 0.0 0.0 0.0 + eip150 EVM.FeeSchedule src/EVM/FeeSchedule.hs:(62,1)-(69,3) 4401 1 0.0 0.0 0.0 0.0 + eip160 EVM.FeeSchedule src/EVM/FeeSchedule.hs:(74,1)-(75,20) 4403 1 0.0 0.0 0.0 0.0 + homestead EVM.FeeSchedule src/EVM/FeeSchedule.hs:(78,1)-(128,3) 4402 1 0.0 0.0 0.0 0.0 + initializeUnitTest EVM.UnitTest src/EVM/UnitTest.hs:(142,1)-(172,17) 4287 0 0.0 0.0 0.0 0.0 + pushTrace EVM src/EVM.hs:(2438,1)-(2441,59) 4288 2 0.0 0.0 0.0 0.0 + withTraceLocation EVM src/EVM.hs:(2426,1)-(2435,5) 4290 2 0.0 0.0 0.0 0.0 + abiKeccak EVM.Types src/EVM/Types.hs:(586,1)-(590,14) 4804 0 0.0 0.0 0.0 0.0 + word32 EVM.Types src/EVM/Types.hs:(576,1)-(577,52) 4831 1 0.0 0.0 0.0 0.0 + keccakBytes EVM.Types src/EVM/Types.hs:(570,1)-(573,15) 4805 0 0.0 0.0 0.0 0.0 + hash Crypto.Hash Crypto/Hash.hs:58:1-47 4806 1 0.0 0.0 0.0 0.0 + hashFinalize Crypto.Hash Crypto/Hash.hs:(92,1)-(95,17) 4807 1 0.0 0.0 0.0 0.0 + allocAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:74:1-45 4815 1 0.0 0.0 0.0 0.0 + new Basement.Block.Base Basement/Block/Base.hs:304:1-76 4816 1 0.0 0.0 0.0 0.0 + unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 4817 1 0.0 0.0 0.0 0.0 + withMutablePtrHint Basement.Block.Base Basement/Block/Base.hs:(475,1)-(489,39) 4818 1 0.0 0.0 0.0 0.0 + copy Data.ByteArray.Methods Data/ByteArray/Methods.hs:(223,1)-(226,21) 4823 1 0.0 0.0 0.0 0.0 + isMutablePinned Basement.Block.Base Basement/Block/Base.hs:100:1-90 4819 1 0.0 0.0 0.0 0.0 + compatIsMutableByteArrayPinned# Basement.Compat.Primitive Basement/Compat/Primitive.hs:70:1-65 4820 1 0.0 0.0 0.0 0.0 + toPinnedStatus# Basement.Compat.Primitive Basement/Compat/Primitive.hs:(47,1)-(48,27) 4821 1 0.0 0.0 0.0 0.0 + unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 4822 1 0.0 0.0 0.0 0.0 + hashInit Crypto.Hash Crypto/Hash.hs:(66,1)-(67,24) 4813 1 0.0 0.0 0.0 0.0 + allocAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:74:1-45 4814 1 0.0 0.0 0.0 0.0 + hashUpdate Crypto.Hash Crypto/Hash.hs:(71,1)-(73,37) 4808 1 0.0 0.0 0.0 0.0 + hashUpdates Crypto.Hash Crypto/Hash.hs:(81,1)-(86,32) 4810 1 0.0 0.0 0.0 0.0 + copyAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:(237,1)-(240,21) 4812 1 0.0 0.0 0.0 0.0 + null Data.ByteArray.Methods Data/ByteArray/Methods.hs:92:1-22 4811 1 0.0 0.0 0.0 0.0 + null Data.ByteArray.Methods Data/ByteArray/Methods.hs:92:1-22 4809 1 0.0 0.0 0.0 0.0 + unpack Data.ByteArray.Methods Data/ByteArray/Methods.hs:(104,1)-(110,34) 4824 1 0.0 0.0 0.0 0.0 + unsafeCast Basement.Block Basement/Block.hs:421:1-32 4825 33 0.0 0.0 0.0 0.0 + withPtr Basement.Block.Base Basement/Block/Base.hs:(402,1)-(411,31) 4826 32 0.0 0.0 0.0 0.0 + isPinned Basement.Block.Base Basement/Block/Base.hs:97:1-67 4827 32 0.0 0.0 0.0 0.0 + compatIsByteArrayPinned# Basement.Compat.Primitive Basement/Compat/Primitive.hs:67:1-51 4828 32 0.0 0.0 0.0 0.0 + toPinnedStatus# Basement.Compat.Primitive Basement/Compat/Primitive.hs:(47,1)-(48,27) 4829 32 0.0 0.0 0.0 0.0 + unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 4830 32 0.0 0.0 0.0 0.0 + runUnitTestContract EVM.UnitTest src/EVM/UnitTest.hs:(477,1)-(528,68) 5941 0 0.0 0.0 0.0 0.0 + CAF EVM.Mutate 3420 0 0.0 0.0 0.0 0.0 + fixAbiUInt EVM.Mutate src/EVM/Mutate.hs:112:1-50 6331 0 0.0 0.0 0.0 0.0 + CAF EVM.Exec 3417 0 0.0 0.0 0.0 0.0 + ethrunAddress EVM.Exec src/EVM/Exec.hs:19:1-63 4358 1 0.0 0.0 0.0 0.0 + CAF Data.SBV.Control 3234 0 0.0 0.0 0.0 0.0 + query Data.SBV.Control Data/SBV/Control.hs:105:1-40 3627 1 0.0 0.0 0.0 0.0 + CAF Data.SBV.Client.BaseIO 3231 0 0.0 0.0 0.0 0.0 + runSMTWith Data.SBV.Client.BaseIO Data/SBV/Client/BaseIO.hs:223:1-29 3609 1 0.0 0.0 0.0 0.0 + CAF Data.SBV.Core.Concrete 3230 0 0.0 0.0 0.0 0.0 + falseCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:263:1-31 3614 1 0.0 0.0 0.0 0.0 + trueCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:267:1-31 3626 1 0.0 0.0 0.0 0.0 + CAF Data.SBV.Core.Model 3227 0 0.0 0.0 0.0 0.0 + genLiteral Data.SBV.Core.Model Data/SBV/Core/Model.hs:99:1-48 4432 1 0.0 0.0 0.0 0.0 + CAF Data.SBV.Core.Operations 3226 0 0.0 0.0 0.0 0.0 + svFalse Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:77:1-35 4567 1 0.0 0.0 0.0 0.0 + svNot Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(417,1)-(423,34) 4590 1 0.0 0.0 0.0 0.0 + svShiftLeft Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:719:1-26 5944 1 0.0 0.0 0.0 0.0 + svShiftRight Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:726:1-28 4979 1 0.0 0.0 0.0 0.0 + svTrue Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:73:1-33 4571 1 0.0 0.0 0.0 0.0 + svUNeg Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:170:1-61 5030 1 0.0 0.0 0.0 0.0 + CAF Data.SBV.Core.Symbolic 3224 0 0.0 0.0 0.0 0.0 + falseSV Data.SBV.Core.Symbolic Data/SBV/Core/Symbolic.hs:142:1-32 3689 1 0.0 0.0 0.0 0.0 + trueSV Data.SBV.Core.Symbolic Data/SBV/Core/Symbolic.hs:146:1-32 3690 1 0.0 0.0 0.0 0.0 + CAF Data.SBV.Control.Types 3221 0 0.0 0.0 0.0 0.0 + setSMTOption Data.SBV.Control.Types Data/SBV/Control/Types.hs:(159,1)-(178,57) 3654 1 0.0 0.0 0.0 0.0 + CAF Data.SBV.SMT.SMT 3219 0 0.0 0.0 0.0 0.0 + standardEngine Data.SBV.SMT.SMT Data/SBV/SMT/SMT.hs:(628,1)-(635,44) 3702 0 0.0 0.0 0.0 0.0 + CAF Data.SBV.SMT.SMTLib2 3217 0 0.0 0.0 0.0 0.0 + cvt Data.SBV.SMT.SMTLib2 Data/SBV/SMT/SMTLib2.hs:(44,1)-(328,31) 3657 0 0.0 0.0 0.0 0.0 + dataBox Data.Generics.Uniplate.Internal.Data Data/Generics/Uniplate/Internal/Data.hs:228:1-33 3660 1 0.0 0.0 0.0 0.0 + typeKey Data.Generics.Uniplate.Internal.Data Data/Generics/Uniplate/Internal/Data.hs:65:1-16 3665 1 0.0 0.0 0.0 0.0 + readCacheFollower Data.Generics.Uniplate.Internal.Data Data/Generics/Uniplate/Internal/Data.hs:(144,1)-(162,22) 3661 1 0.0 0.0 0.0 0.0 + insertHitMap Data.Generics.Uniplate.Internal.Data Data/Generics/Uniplate/Internal/Data.hs:(262,1)-(282,56) 3667 1 0.0 0.0 0.0 0.0 + map_member Data.Generics.Uniplate.Internal.Data Data/Generics/Uniplate/Internal/Data.hs:93:1-42 3680 2 0.0 0.0 0.0 0.0 + hash Data.HashMap.Base Data/HashMap/Base.hs:166:1-28 3681 2 0.0 0.0 0.0 0.0 + sybChildren Data.Generics.Uniplate.Internal.Data Data/Generics/Uniplate/Internal/Data.hs:(233,1)-(244,27) 3682 1 0.0 0.0 0.0 0.0 + union Data.HashMap.Base Data/HashMap/Base.hs:1287:1-23 3669 0 0.0 0.0 0.0 0.0 + lookup2 Data.Generics.Uniplate.Internal.Data Data/Generics/Uniplate/Internal/Data.hs:186:1-49 3663 1 0.0 0.0 0.0 0.0 + hash Data.HashMap.Base Data/HashMap/Base.hs:166:1-28 3664 1 0.0 0.0 0.0 0.0 + typeKey Data.Generics.Uniplate.Internal.Data Data/Generics/Uniplate/Internal/Data.hs:65:1-16 3686 1 0.0 0.0 0.0 0.0 + CAF Data.SBV.Provers.Prover 3214 0 0.0 0.0 0.0 0.0 + cvc4 Data.SBV.Provers.Prover Data/SBV/Provers/Prover.hs:114:1-47 3634 1 0.0 0.0 0.0 0.0 + CAF Data.SBV.Provers.CVC4 3212 0 0.0 0.0 0.0 0.0 + cvc4 Data.SBV.Provers.CVC4 Data/SBV/Provers/CVC4.hs:(27,1)-(64,25) 3644 1 0.0 0.0 0.0 0.0 + CAF Data.SBV.Utils.Lib 3203 0 0.0 0.0 0.0 0.0 + splitArgs Data.SBV.Utils.Lib Data/SBV/Utils/Lib.hs:(88,1)-(108,40) 3696 1 0.0 0.0 0.0 0.0 + CAF Data.SBV.Utils.SExpr 3201 0 0.0 0.0 0.0 0.0 + parenDeficit Data.SBV.Utils.SExpr Data/SBV/Utils/SExpr.hs:(82,1)-(87,54) 3705 1 0.0 0.0 0.0 0.0 + CAF Data.Generics.Uniplate.Internal.Data 3197 0 0.0 0.0 0.0 0.0 + cache Data.Generics.Uniplate.Internal.Data Data/Generics/Uniplate/Internal/Data.hs:140:1-64 3662 1 0.0 0.0 0.0 0.0 + emptyHitMap Data.Generics.Uniplate.Internal.Data Data/Generics/Uniplate/Internal/Data.hs:(254,1)-(258,43) 3670 1 0.0 0.0 0.0 0.0 + typeKey Data.Generics.Uniplate.Internal.Data Data/Generics/Uniplate/Internal/Data.hs:65:1-16 3675 2 0.0 0.0 0.0 0.0 + fromList Data.HashMap.Strict.Base Data/HashMap/Strict/Base.hs:598:1-64 3671 1 0.0 0.0 0.0 0.0 + unsafeInsert Data.HashMap.Base Data/HashMap/Base.hs:(784,1)-(814,76) 3676 2 0.0 0.0 0.0 0.0 + hash Data.HashMap.Base Data/HashMap/Base.hs:166:1-28 3677 2 0.0 0.0 0.0 0.0 + singleton Data.HashSet.Base Data/HashSet/Base.hs:207:1-40 3672 1 0.0 0.0 0.0 0.0 + singleton Data.HashMap.Base Data/HashMap/Base.hs:468:1-37 3673 1 0.0 0.0 0.0 0.0 + hash Data.HashMap.Base Data/HashMap/Base.hs:166:1-28 3674 1 0.0 0.0 0.0 0.0 + union Data.HashMap.Base Data/HashMap/Base.hs:1287:1-23 3668 1 0.0 0.0 0.0 0.0 + uniplateVerbose Data.Generics.Uniplate.Internal.Data Data/Generics/Uniplate/Internal/Data.hs:(103,1)-(104,101) 3683 1 0.0 0.0 0.0 0.0 + CAF Text.Regex.TDFA.Common 3156 0 0.0 0.0 0.0 0.0 + noWin Text.Regex.TDFA.Common lib/Text/Regex/TDFA/Common.hs:69:1-12 4269 1 0.0 0.0 0.0 0.0 + CAF Text.Regex.TDFA.Pattern 3141 0 0.0 0.0 0.0 0.0 + starTrans Text.Regex.TDFA.Pattern lib/Text/Regex/TDFA/Pattern.hs:140:1-47 4250 1 0.0 0.0 0.0 0.0 + dfsPattern Text.Regex.TDFA.Pattern lib/Text/Regex/TDFA/Pattern.hs:(146,1)-(156,37) 4251 1 0.0 0.0 0.0 0.0 + CAF Text.Regex.TDFA.ReadRegex 3140 0 0.0 0.0 0.0 0.0 + CAF Options.Generic 3136 0 0.0 0.0 0.0 0.0 + metavar Options.Applicative.Builder src/Options/Applicative/Builder.hs:201:1-55 3595 2 0.0 0.0 0.0 0.0 + optionMod Options.Applicative.Builder.Internal src/Options/Applicative/Builder/Internal.hs:129:1-25 3596 0 0.0 0.0 0.0 0.0 + lispCaseModifiers Options.Generic src/Options/Generic.hs:(816,1)-(820,29) 3535 1 0.0 0.0 0.0 0.0 + multiSuffix Options.Applicative.Builder src/Options/Applicative/Builder.hs:467:1-58 3467 1 0.0 0.0 0.0 0.0 + str Options.Applicative.Builder src/Options/Applicative/Builder.hs:129:1-30 3586 1 0.0 0.0 0.0 0.0 + getRecord Options.Generic src/Options/Generic.hs:(1017,1)-(1019,51) 3464 0 0.0 0.0 0.0 0.0 + getRecordWith Options.Generic src/Options/Generic.hs:(1032,1)-(1035,46) 3465 0 0.0 0.0 0.0 0.0 + prefs Options.Applicative.Builder src/Options/Applicative/Builder.hs:(511,1)-(520,36) 3466 1 0.0 0.0 0.0 0.0 + multiSuffix Options.Applicative.Builder src/Options/Applicative/Builder.hs:467:1-58 3468 0 0.0 0.0 0.0 0.0 + CAF Options.Applicative.Builder 3132 0 0.0 0.0 0.0 0.0 + hidden Options.Applicative.Builder src/Options/Applicative/Builder.hs:(205,1)-(206,54) 3523 1 0.0 0.0 0.0 0.0 + optionMod Options.Applicative.Builder.Internal src/Options/Applicative/Builder/Internal.hs:129:1-25 3524 0 0.0 0.0 0.0 0.0 + switch Options.Applicative.Builder src/Options/Applicative/Builder.hs:333:1-24 3590 1 0.0 0.0 0.0 0.0 + abortOption Options.Applicative.Builder src/Options/Applicative/Builder.hs:(341,1)-(344,16) 3528 0 0.0 0.0 0.0 0.0 + metavar Options.Applicative.Builder src/Options/Applicative/Builder.hs:201:1-55 3530 1 0.0 0.0 0.0 0.0 + optionMod Options.Applicative.Builder.Internal src/Options/Applicative/Builder/Internal.hs:129:1-25 3531 0 0.0 0.0 0.0 0.0 + value Options.Applicative.Builder src/Options/Applicative/Builder.hs:173:1-50 3529 1 0.0 0.0 0.0 0.0 + option Options.Applicative.Builder src/Options/Applicative/Builder.hs:(367,1)-(372,65) 3496 0 0.0 0.0 0.0 0.0 + metavar Options.Applicative.Builder src/Options/Applicative/Builder.hs:201:1-55 3497 1 0.0 0.0 0.0 0.0 + optionMod Options.Applicative.Builder.Internal src/Options/Applicative/Builder/Internal.hs:129:1-25 3498 0 0.0 0.0 0.0 0.0 + subparser Options.Applicative.Builder src/Options/Applicative/Builder.hs:(270,1)-(274,39) 3541 0 0.0 0.0 0.0 0.0 + metavar Options.Applicative.Builder src/Options/Applicative/Builder.hs:201:1-55 3542 1 0.0 0.0 0.0 0.0 + optionMod Options.Applicative.Builder.Internal src/Options/Applicative/Builder/Internal.hs:129:1-25 3543 0 0.0 0.0 0.0 0.0 + CAF Options.Applicative.Builder.Internal 3130 0 0.0 0.0 0.0 0.0 + internal Options.Applicative.Builder.Internal src/Options/Applicative/Builder/Internal.hs:185:1-60 3482 1 0.0 0.0 0.0 0.0 + optionMod Options.Applicative.Builder.Internal src/Options/Applicative/Builder/Internal.hs:129:1-25 3484 0 0.0 0.0 0.0 0.0 + optionMod Options.Applicative.Builder.Internal src/Options/Applicative/Builder/Internal.hs:129:1-25 3483 1 0.0 0.0 0.0 0.0 + CAF Options.Applicative.Common 3129 0 0.0 0.0 0.0 0.0 + liftOpt Options.Applicative.Common src/Options/Applicative/Common.hs:80:1-14 3487 1 0.0 0.0 0.0 0.0 + CAF Options.Applicative.Extra 3128 0 0.0 0.0 0.0 0.0 + helper Options.Applicative.Extra src/Options/Applicative/Extra.hs:(49,1)-(53,12) 3516 1 0.0 0.0 0.0 0.0 + abortOption Options.Applicative.Builder src/Options/Applicative/Builder.hs:(341,1)-(344,16) 3525 1 0.0 0.0 0.0 0.0 + noArgError Options.Applicative.Builder src/Options/Applicative/Builder.hs:194:1-61 3526 1 0.0 0.0 0.0 0.0 + fieldMod Options.Applicative.Builder.Internal src/Options/Applicative/Builder/Internal.hs:132:1-28 3527 1 0.0 0.0 0.0 0.0 + option Options.Applicative.Builder src/Options/Applicative/Builder.hs:(367,1)-(372,65) 3532 1 0.0 0.0 0.0 0.0 + optNames Options.Applicative.Builder.Internal src/Options/Applicative/Builder/Internal.hs:35:5-12 3564 3 0.0 0.0 0.0 0.0 + mkParser Options.Applicative.Builder.Internal src/Options/Applicative/Builder/Internal.hs:(163,1)-(167,36) 3533 1 0.0 0.0 0.0 0.0 + mkOption Options.Applicative.Builder.Internal src/Options/Applicative/Builder/Internal.hs:173:1-43 3534 1 0.0 0.0 0.0 0.0 + noArgError Options.Applicative.Builder src/Options/Applicative/Builder.hs:194:1-61 3565 0 0.0 0.0 0.0 0.0 + fieldMod Options.Applicative.Builder.Internal src/Options/Applicative/Builder/Internal.hs:132:1-28 3566 0 0.0 0.0 0.0 0.0 + help Options.Applicative.Builder src/Options/Applicative/Builder.hs:185:1-55 3521 1 0.0 0.0 0.0 0.0 + optionMod Options.Applicative.Builder.Internal src/Options/Applicative/Builder/Internal.hs:129:1-25 3522 0 0.0 0.0 0.0 0.0 + long Options.Applicative.Builder src/Options/Applicative/Builder.hs:161:1-32 3517 1 0.0 0.0 0.0 0.0 + fieldMod Options.Applicative.Builder.Internal src/Options/Applicative/Builder/Internal.hs:132:1-28 3518 1 0.0 0.0 0.0 0.0 + short Options.Applicative.Builder src/Options/Applicative/Builder.hs:157:1-34 3519 1 0.0 0.0 0.0 0.0 + fieldMod Options.Applicative.Builder.Internal src/Options/Applicative/Builder/Internal.hs:132:1-28 3520 1 0.0 0.0 0.0 0.0 + CAF Options.Applicative.Types 3122 0 0.0 0.0 0.0 0.0 + readerAsk Options.Applicative.Types src/Options/Applicative/Types.hs:214:1-21 3588 1 0.0 0.0 0.0 0.0 + CAF Options.Applicative.BashCompletion 3120 0 0.0 0.0 0.0 0.0 + bashCompletionParser Options.Applicative.BashCompletion src/Options/Applicative/BashCompletion.hs:(35,1)-(65,7) 3479 0 0.0 0.0 0.0 0.0 + long Options.Applicative.Builder src/Options/Applicative/Builder.hs:161:1-32 3480 8 0.0 0.0 0.0 0.0 + fieldMod Options.Applicative.Builder.Internal src/Options/Applicative/Builder/Internal.hs:132:1-28 3481 8 0.0 0.0 0.0 0.0 + strOption Options.Applicative.Builder src/Options/Applicative/Builder.hs:352:1-22 3504 4 0.0 0.0 0.0 0.0 + option Options.Applicative.Builder src/Options/Applicative/Builder.hs:(367,1)-(372,65) 3505 4 0.0 0.0 0.0 0.0 + mkParser Options.Applicative.Builder.Internal src/Options/Applicative/Builder/Internal.hs:(163,1)-(167,36) 3506 4 0.0 0.0 0.0 0.0 + mkOption Options.Applicative.Builder.Internal src/Options/Applicative/Builder/Internal.hs:173:1-43 3507 4 0.0 0.0 0.0 0.0 + option Options.Applicative.Builder src/Options/Applicative/Builder.hs:(367,1)-(372,65) 3495 3 0.0 0.0 0.0 0.0 + mkParser Options.Applicative.Builder.Internal src/Options/Applicative/Builder/Internal.hs:(163,1)-(167,36) 3499 3 0.0 0.0 0.0 0.0 + mkOption Options.Applicative.Builder.Internal src/Options/Applicative/Builder/Internal.hs:173:1-43 3500 3 0.0 0.0 0.0 0.0 + value Options.Applicative.Builder src/Options/Applicative/Builder.hs:173:1-50 3494 2 0.0 0.0 0.0 0.0 + flag' Options.Applicative.Builder src/Options/Applicative/Builder.hs:(319,1)-(323,43) 3485 1 0.0 0.0 0.0 0.0 + flagActive Options.Applicative.Builder.Internal src/Options/Applicative/Builder/Internal.hs:41:5-14 3490 1 0.0 0.0 0.0 0.0 + mkParser Options.Applicative.Builder.Internal src/Options/Applicative/Builder/Internal.hs:(163,1)-(167,36) 3486 1 0.0 0.0 0.0 0.0 + mkOption Options.Applicative.Builder.Internal src/Options/Applicative/Builder/Internal.hs:173:1-43 3489 1 0.0 0.0 0.0 0.0 + long Options.Applicative.Builder src/Options/Applicative/Builder.hs:161:1-32 3492 0 0.0 0.0 0.0 0.0 + fieldMod Options.Applicative.Builder.Internal src/Options/Applicative/Builder/Internal.hs:132:1-28 3493 0 0.0 0.0 0.0 0.0 + fromM Options.Applicative.Types src/Options/Applicative/Types.hs:282:1-26 3501 1 0.0 0.0 0.0 0.0 + manyM Options.Applicative.Types src/Options/Applicative/Types.hs:(288,1)-(292,30) 3502 1 0.0 0.0 0.0 0.0 + oneM Options.Applicative.Types src/Options/Applicative/Types.hs:285:1-26 3503 1 0.0 0.0 0.0 0.0 + CAF Control.Monad.Operational 3119 0 0.0 0.0 0.0 0.0 + singleton Control.Monad.Operational src/Control/Monad/Operational.hs:221:1-17 4279 1 0.0 0.0 0.0 0.0 + view Control.Monad.Operational src/Control/Monad/Operational.hs:138:1-26 4273 1 0.0 0.0 0.0 0.0 + CAF System.Process.Posix 3069 0 0.0 0.0 0.0 0.0 + CAF Data.Serialize.Get 3058 0 0.0 0.0 0.0 0.0 + bytesRead Data.Serialize.Get src/Data/Serialize/Get.hs:838:1-45 4162 1 0.0 0.0 0.0 0.0 + CAF Data.DoubleWord 3015 0 0.0 0.0 0.0 0.0 + CAF Data.Memory.Internal.Compat 2930 0 0.0 0.0 0.0 0.0 + unsafeDoIO Data.Memory.Internal.Compat Data/Memory/Internal/Compat.hs:33:1-35 4143 1 0.0 0.0 0.0 0.0 + CAF System.Directory 2139 0 0.0 0.0 0.0 0.0 + CAF System.Directory.Internal.Posix 2137 0 0.0 0.0 0.0 0.0 + CAF Text.Megaparsec 2134 0 0.0 0.0 0.0 0.0 + parse Text.Megaparsec Text/Megaparsec.hs:178:1-17 5609 1 0.0 0.0 0.0 0.0 + CAF Data.Aeson.Parser.Internal 2098 0 0.0 0.0 0.0 0.0 + jstring Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:317:1-32 3728 1 0.0 0.0 0.0 0.0 + value Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:196:1-36 3720 1 0.0 0.0 0.0 0.0 + array_ Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:169:35-59 3732 1 0.0 0.0 0.0 0.0 + marray# Data.Primitive.Array Data/Primitive/Array.hs:92:5-11 3835 1 0.0 0.0 0.0 0.0 + sChunks Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:122:30-36 3833 1 0.0 0.0 0.0 0.0 + sSize Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:124:30-34 3832 1 0.0 0.0 0.0 0.0 + unId Data.Vector.Fusion.Util Data/Vector/Fusion/Util.hs:25:21-24 3834 1 0.0 0.0 0.0 0.0 + upperBound Data.Vector.Fusion.Bundle.Size Data/Vector/Fusion/Bundle/Size.hs:(126,1)-(128,30) 3831 1 0.0 0.0 0.0 0.0 + fromList Data.HashMap.Strict.Base Data/HashMap/Strict/Base.hs:598:1-64 3771 1 0.0 0.0 0.0 0.0 + object_ Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:132:46-89 3723 1 0.0 0.0 0.0 0.0 + CAF Data.Aeson.Parser.UnescapePure 2090 0 0.0 0.0 0.0 0.0 + unescapeText Data.Aeson.Parser.UnescapePure pure/Data/Aeson/Parser/UnescapePure.hs:254:1-70 3747 1 0.0 0.0 0.0 0.0 + CAF Data.HashMap.Base 2068 0 0.0 0.0 0.0 0.0 + bitsPerSubkey Data.HashMap.Base Data/HashMap/Base.hs:1858:1-17 3679 1 0.0 0.0 0.0 0.0 + empty Data.HashMap.Base Data/HashMap/Base.hs:464:1-13 3666 1 0.0 0.0 0.0 0.0 + CAF Data.HashSet.Base 2065 0 0.0 0.0 0.0 0.0 + empty Data.HashSet.Base Data/HashSet/Base.hs:203:1-23 3678 1 0.0 0.0 0.0 0.0 + CAF Data.Scientific 2033 0 0.0 0.0 0.0 0.0 + scientific Data.Scientific src/Data/Scientific.hs:174:1-23 3774 1 0.0 0.0 0.0 0.0 + CAF Data.Text 2021 0 0.0 0.0 0.0 0.0 + CAF Data.Text.Array 2020 0 0.0 0.0 0.0 0.0 + CAF Data.Text.Encoding 2019 0 0.0 0.0 0.0 0.0 + CAF Data.Text.IO 2017 0 0.0 0.0 0.0 0.0 + CAF Data.Text.Internal 2016 0 0.0 0.0 0.0 0.0 + CAF Data.ByteString.Builder.Prim.Internal.Base16 1972 0 0.0 0.0 0.0 0.0 + CAF Test.QuickCheck.Arbitrary 1971 0 0.0 0.0 0.0 0.0 + choose Test.QuickCheck.Gen Test/QuickCheck/Gen.hs:130:1-59 6326 1 0.0 0.0 0.0 0.0 + CAF Test.QuickCheck.Random 1962 0 0.0 0.0 0.0 0.0 + newQCGen Test.QuickCheck.Random Test/QuickCheck/Random.hs:42:1-30 5303 1 0.0 0.0 0.0 0.0 + CAF System.Random.SplitMix 1935 0 0.0 0.0 0.0 0.0 + initSMGen System.Random.SplitMix src/System/Random/SplitMix.hs:378:1-35 5307 1 0.0 0.0 0.0 0.0 + mkSMGen System.Random.SplitMix src/System/Random/SplitMix.hs:374:1-61 5308 1 0.0 0.0 0.0 0.0 + newSMGen System.Random.SplitMix src/System/Random/SplitMix.hs:382:1-48 5305 1 0.0 0.0 0.0 0.0 + CAF Data.Time.Clock.POSIX 1930 0 0.0 0.0 0.0 0.0 + CAF Data.Sequence.Internal 1899 0 0.0 0.0 0.0 0.0 + CAF Data.Data 1875 0 0.0 0.0 0.0 0.0 + CAF Data.Unique 1852 0 0.0 0.0 0.0 0.0 + CAF GHC.Conc.Signal 1836 0 0.0 0.0 0.0 0.0 + CAF GHC.IO.Encoding 1817 0 0.0 0.0 0.0 0.0 + CAF GHC.IO.Encoding.Iconv 1815 0 0.0 0.0 0.0 0.0 + CAF GHC.IO.Exception 1809 0 0.0 0.0 0.0 0.0 + CAF GHC.IO.FD 1808 0 0.0 0.0 0.0 0.0 + CAF GHC.IO.Handle.FD 1806 0 0.0 0.0 0.0 0.0 + CAF GHC.IO.Handle.Internals 1805 0 0.0 0.0 0.0 0.0 + CAF GHC.IO.Handle.Text 1804 0 0.0 0.0 0.0 0.0 + CAF GHC.Show 1786 0 0.0 0.0 0.0 0.0 + CAF System.CPUTime 1773 0 0.0 0.0 0.0 0.0 + CAF System.Exit 1771 0 0.0 0.0 0.0 0.0 + CAF Text.Read.Lex 1761 0 0.0 0.0 0.0 0.0 + CAF Data.Typeable.Internal 1755 0 0.0 0.0 0.0 0.0 + CAF GHC.Event.Thread 1753 0 0.0 0.0 0.0 0.0 + CAF GHC.Event.Manager 1745 0 0.0 0.0 0.0 0.0 + CAF GHC.Event.Poll 1743 0 0.0 0.0 0.0 0.0 + CAF GHC.Integer.Type 1737 0 0.0 0.0 0.0 0.0 + main Main hevm-cli/hevm-cli.hs:(307,1)-(354,100) 3451 0 0.0 0.0 99.9 100.0 + dappRoot Main hevm-cli/hevm-cli.hs:120:9-16 3602 1 0.0 0.0 0.0 0.0 + findJsonFile Main hevm-cli/hevm-cli.hs:(370,1)-(387,9) 3605 1 0.0 0.0 0.0 0.0 + jsonFile Main hevm-cli/hevm-cli.hs:119:9-16 3604 1 0.0 0.0 0.0 0.0 + runSMTWithTimeOut Main hevm-cli/hevm-cli.hs:(447,1)-(458,17) 3607 1 0.0 0.0 99.9 100.0 + runSMTWith Data.SBV.Client.BaseIO Data/SBV/Client/BaseIO.hs:223:1-29 3610 0 0.0 0.0 99.9 100.0 + runSMTWith Data.SBV.Provers.Prover Data/SBV/Provers/Prover.hs:755:1-80 3611 1 0.0 0.0 99.9 100.0 + runSymbolic Data.SBV.Core.Symbolic Data/SBV/Core/Symbolic.hs:(1472,1)-(1541,18) 3612 1 0.0 0.0 99.9 100.0 + incrementInternalCounter Data.SBV.Core.Symbolic Data/SBV/Core/Symbolic.hs:(1058,1)-(1060,43) 3615 2 0.0 0.0 0.0 0.0 + modifyState Data.SBV.Core.Symbolic Data/SBV/Core/Symbolic.hs:(1039,1)-(1044,41) 3617 2 0.0 0.0 0.0 0.0 + rctr Data.SBV.Core.Symbolic Data/SBV/Core/Symbolic.hs:935:23-26 3618 2 0.0 0.0 0.0 0.0 + rctr Data.SBV.Core.Symbolic Data/SBV/Core/Symbolic.hs:935:23-26 3616 2 0.0 0.0 0.0 0.0 + modifyState Data.SBV.Core.Symbolic Data/SBV/Core/Symbolic.hs:(1039,1)-(1044,41) 3624 2 0.0 0.0 0.0 0.0 + rconstMap Data.SBV.Core.Symbolic Data/SBV/Core/Symbolic.hs:945:23-31 3625 2 0.0 0.0 0.0 0.0 + rconstMap Data.SBV.Core.Symbolic Data/SBV/Core/Symbolic.hs:945:23-31 3613 2 0.0 0.0 0.0 0.0 + registerKind Data.SBV.Core.Symbolic Data/SBV/Core/Symbolic.hs:(1152,1)-(1193,60) 3619 2 0.0 0.0 0.0 0.0 + modifyState Data.SBV.Core.Symbolic Data/SBV/Core/Symbolic.hs:(1039,1)-(1044,41) 3622 2 0.0 0.0 0.0 0.0 + rUsedKinds Data.SBV.Core.Symbolic Data/SBV/Core/Symbolic.hs:936:23-32 3623 2 0.0 0.0 0.0 0.0 + rUsedKinds Data.SBV.Core.Symbolic Data/SBV/Core/Symbolic.hs:936:23-32 3621 2 0.0 0.0 0.0 0.0 + query Data.SBV.Control Data/SBV/Control.hs:105:1-40 3630 0 0.0 0.0 99.9 100.0 + extractSymbolicSimulationState Data.SBV.Core.Symbolic Data/SBV/Core/Symbolic.hs:(1545,1)-(1570,125) 3638 1 0.0 0.0 0.0 0.0 + executeQuery Data.SBV.Control.Utils Data/SBV/Control/Utils.hs:(1467,1)-(1619,43) 3631 0 0.0 0.0 99.9 100.0 + runMode Data.SBV.Core.Symbolic Data/SBV/Core/Symbolic.hs:931:23-29 3632 2 0.0 0.0 0.0 0.0 + allowQuantifiedQueries Data.SBV.Core.Symbolic Data/SBV/Core/Symbolic.hs:1842:10-31 3633 1 0.0 0.0 0.0 0.0 + cache Main hevm-cli/hevm-cli.hs:116:9-13 6502 1 0.0 0.0 0.0 0.0 + coverage Main hevm-cli/hevm-cli.hs:181:9-16 3940 1 0.0 0.0 0.0 0.0 + dappTest Main hevm-cli/hevm-cli.hs:(390,1)-(421,69) 3944 1 0.0 0.0 94.1 91.5 + _dappRoot EVM.Dapp src/EVM/Dapp.hs:33:5-13 4120 1 0.0 0.0 0.0 0.0 + corpus EVM.UnitTest src/EVM/UnitTest.hs:90:5-10 4122 1 0.0 0.0 0.0 0.0 + dapp EVM.UnitTest src/EVM/UnitTest.hs:87:5-8 4118 1 0.0 0.0 0.0 0.0 + findUnitTests EVM.Dapp src/EVM/Dapp.hs:(134,1)-(140,68) 4124 1 0.0 0.0 0.0 0.0 + unitTestMethodsFiltered EVM.Dapp src/EVM/Dapp.hs:(143,1)-(147,51) 4233 2 0.0 0.0 0.0 0.0 + regexMatches EVM.Dapp src/EVM/Dapp.hs:(123,1)-(131,49) 4239 0 0.0 0.0 0.0 0.0 + matchTest Text.Regex.TDFA.NewDFA.Tester lib/Text/Regex/TDFA/NewDFA/Tester.hs:(23,1)-(85,22) 4265 5 0.0 0.0 0.0 0.0 + d_dt Text.Regex.TDFA.Common lib/Text/Regex/TDFA/Common.hs:214:36-39 4267 5 0.0 0.0 0.0 0.0 + unitTestMethods EVM.Dapp src/EVM/Dapp.hs:(150,1)-(155,27) 4235 0 0.0 0.0 0.0 0.0 + mkTest EVM.Dapp src/EVM/Dapp.hs:(117,1)-(120,23) 4236 10 0.0 0.0 0.0 0.0 + regexMatches EVM.Dapp src/EVM/Dapp.hs:(123,1)-(131,49) 4238 1 0.0 0.0 0.0 0.0 + compile Text.Regex.TDFA.String lib/Text/Regex/TDFA/String.hs:(44,1)-(47,67) 4240 1 0.0 0.0 0.0 0.0 + parseRegex Text.Regex.TDFA.ReadRegex lib/Text/Regex/TDFA/ReadRegex.hs:(28,1)-(31,83) 4241 1 0.0 0.0 0.0 0.0 + patternToRegex Text.Regex.TDFA.TDFA lib/Text/Regex/TDFA/TDFA.hs:160:1-96 4245 1 0.0 0.0 0.0 0.0 + nfaToDFA Text.Regex.TDFA.TDFA lib/Text/Regex/TDFA/TDFA.hs:(53,1)-(157,65) 4247 1 0.0 0.0 0.0 0.0 + fromSinglesMerge Text.Regex.TDFA.IntArrTrieSet lib/Text/Regex/TDFA/IntArrTrieSet.hs:(45,1)-(52,33) 4260 1 0.0 0.0 0.0 0.0 + fromBounds Text.Regex.TDFA.IntArrTrieSet lib/Text/Regex/TDFA/IntArrTrieSet.hs:(32,1)-(35,86) 4261 1 0.0 0.0 0.0 0.0 + nfaToDFA.indexToDFA Text.Regex.TDFA.TDFA lib/Text/Regex/TDFA/TDFA.hs:85:52-96 4264 1 0.0 0.0 0.0 0.0 + multiline Text.Regex.TDFA.Common lib/Text/Regex/TDFA/Common.hs:86:5-13 4266 1 0.0 0.0 0.0 0.0 + nfaToDFA.indexesToDFA Text.Regex.TDFA.TDFA lib/Text/Regex/TDFA/TDFA.hs:59:54-72 4248 1 0.0 0.0 0.0 0.0 + lookupAsc Text.Regex.TDFA.IntArrTrieSet lib/Text/Regex/TDFA/IntArrTrieSet.hs:(23,1)-(25,64) 4262 2 0.0 0.0 0.0 0.0 + patternToNFA Text.Regex.TDFA.TNFA lib/Text/Regex/TDFA/TNFA.hs:(84,1)-(87,45) 4246 1 0.0 0.0 0.0 0.0 + lastStarGreedy Text.Regex.TDFA.Common lib/Text/Regex/TDFA/Common.hs:95:5-18 4268 3 0.0 0.0 0.0 0.0 + nullQ Text.Regex.TDFA.CorePattern lib/Text/Regex/TDFA/CorePattern.hs:75:13-17 4259 2 0.0 0.0 0.0 0.0 + cannotAccept Text.Regex.TDFA.CorePattern lib/Text/Regex/TDFA/CorePattern.hs:242:1-52 4257 1 0.0 0.0 0.0 0.0 + takes Text.Regex.TDFA.CorePattern lib/Text/Regex/TDFA/CorePattern.hs:76:13-17 4258 1 0.0 0.0 0.0 0.0 + multiline Text.Regex.TDFA.Common lib/Text/Regex/TDFA/Common.hs:86:5-13 4270 1 0.0 0.0 0.0 0.0 + patternToQ Text.Regex.TDFA.CorePattern lib/Text/Regex/TDFA/CorePattern.hs:(304,1)-(586,28) 4249 1 0.0 0.0 0.0 0.0 + starTrans Text.Regex.TDFA.Pattern lib/Text/Regex/TDFA/Pattern.hs:140:1-47 4252 0 0.0 0.0 0.0 0.0 + dfsPattern Text.Regex.TDFA.Pattern lib/Text/Regex/TDFA/Pattern.hs:(146,1)-(156,37) 4253 0 0.0 0.0 0.0 0.0 + simplify' Text.Regex.TDFA.Pattern lib/Text/Regex/TDFA/Pattern.hs:(326,1)-(343,23) 4255 4 0.0 0.0 0.0 0.0 + starTrans' Text.Regex.TDFA.Pattern lib/Text/Regex/TDFA/Pattern.hs:(169,1)-(320,14) 4254 4 0.0 0.0 0.0 0.0 + q_id Text.Regex.TDFA.Common lib/Text/Regex/TDFA/Common.hs:165:19-22 4263 1 0.0 0.0 0.0 0.0 + unQ Text.Regex.TDFA.CorePattern lib/Text/Regex/TDFA/CorePattern.hs:83:13-15 4256 1 0.0 0.0 0.0 0.0 + match EVM.UnitTest src/EVM/UnitTest.hs:83:5-9 4242 1 0.0 0.0 0.0 0.0 + readSolc EVM.Solidity src/EVM/Solidity.hs:(297,1)-(303,47) 3945 1 0.1 0.1 5.4 8.5 + readTextDevice Data.Text.Internal.IO libraries/text/Data/Text/Internal/IO.hs:133:39-64 3946 393 0.1 0.0 0.1 0.0 + readJSON EVM.Solidity src/EVM/Solidity.hs:(329,1)-(331,28) 3947 1 0.1 0.1 5.2 8.3 + lazy Control.Lens.Iso src/Control/Lens/Iso.hs:569:1-18 3948 1 0.0 0.0 1.5 2.4 + hash Data.HashMap.Base Data/HashMap/Base.hs:166:1-28 4027 1 0.0 0.0 0.0 0.0 + hashByteArrayWithSalt Data.Hashable.Class Data/Hashable/Class.hs:(770,1)-(772,20) 4028 1 0.0 0.0 0.0 0.0 + maybeResult Data.Attoparsec.ByteString.Lazy Data/Attoparsec/ByteString/Lazy.hs:(103,1)-(104,32) 3949 1 0.0 0.0 0.0 0.0 + parse Data.Attoparsec.ByteString.Lazy Data/Attoparsec/ByteString/Lazy.hs:(88,1)-(95,56) 3950 1 0.0 0.0 1.5 2.4 + runParser Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:111:7-15 3951 16 0.0 0.0 0.0 0.0 + fromPos Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:46:21-27 3953 3 0.0 0.0 0.0 0.0 + buffer Data.Attoparsec.ByteString.Buffer Data/Attoparsec/ByteString/Buffer.hs:85:1-45 3952 1 0.0 0.0 0.0 0.0 + value Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:196:1-36 3954 0 0.0 0.0 1.5 2.4 + array_ Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:169:35-59 3961 0 0.1 0.1 0.1 0.3 + runParser Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:111:7-15 3962 75877 0.0 0.0 0.0 0.0 + fromPos Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:46:21-27 3963 15377 0.0 0.0 0.0 0.0 + marray# Data.Primitive.Array Data/Primitive/Array.hs:92:5-11 4007 23 0.0 0.0 0.0 0.0 + unId Data.Vector.Fusion.Util Data/Vector/Fusion/Util.hs:25:21-24 4006 15 0.0 0.0 0.0 0.0 + sChunks Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:122:30-36 4005 6 0.0 0.0 0.0 0.0 + sSize Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:124:30-34 4004 6 0.0 0.0 0.0 0.0 + upperBound Data.Vector.Fusion.Bundle.Size Data/Vector/Fusion/Bundle/Size.hs:(126,1)-(128,30) 4003 6 0.0 0.0 0.0 0.0 + jstring Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:317:1-32 3978 0 0.0 0.1 0.0 0.1 + runParser Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:111:7-15 3979 123205 0.0 0.0 0.0 0.0 + fromPos Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:46:21-27 3980 20305 0.0 0.0 0.0 0.0 + jstringSlow Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:(333,44)-(337,31) 3992 0 0.0 0.0 0.0 0.0 + object_ Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:132:46-89 3981 0 0.0 0.0 0.0 0.0 + runParser Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:111:7-15 3982 335 0.0 0.0 0.0 0.0 + marray# Data.Primitive.Array Data/Primitive/Array.hs:92:5-11 4016 80 0.0 0.0 0.0 0.0 + fromPos Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:46:21-27 3983 65 0.0 0.0 0.0 0.0 + unId Data.Vector.Fusion.Util Data/Vector/Fusion/Util.hs:25:21-24 4015 28 0.0 0.0 0.0 0.0 + sChunks Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:122:30-36 4014 2 0.0 0.0 0.0 0.0 + sSize Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:124:30-34 4013 2 0.0 0.0 0.0 0.0 + upperBound Data.Vector.Fusion.Bundle.Size Data/Vector/Fusion/Bundle/Size.hs:(126,1)-(128,30) 4012 2 0.0 0.0 0.0 0.0 + scientific Data.Scientific src/Data/Scientific.hs:174:1-23 4011 0 0.0 0.0 0.0 0.0 + jstringSlow Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:(333,44)-(337,31) 3993 0 0.0 0.0 0.0 0.0 + runParser Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:111:7-15 3996 16 0.0 0.0 0.0 0.0 + fromPos Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:46:21-27 3997 3 0.0 0.0 0.0 0.0 + object_ Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:132:46-89 3994 0 0.0 0.0 0.0 0.0 + jstring Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:317:1-32 3995 0 0.0 0.0 0.0 0.0 + object_ Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:132:46-89 3967 0 0.0 0.0 0.1 0.2 + runParser Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:111:7-15 3976 2467 0.0 0.0 0.0 0.0 + fromPos Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:46:21-27 3977 481 0.0 0.0 0.0 0.0 + marray# Data.Primitive.Array Data/Primitive/Array.hs:92:5-11 4021 7 0.0 0.0 0.0 0.0 + unId Data.Vector.Fusion.Util Data/Vector/Fusion/Util.hs:25:21-24 4020 3 0.0 0.0 0.0 0.0 + sChunks Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:122:30-36 4019 1 0.0 0.0 0.0 0.0 + sSize Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:124:30-34 4018 1 0.0 0.0 0.0 0.0 + upperBound Data.Vector.Fusion.Bundle.Size Data/Vector/Fusion/Bundle/Size.hs:(126,1)-(128,30) 4017 1 0.0 0.0 0.0 0.0 + jstring Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:317:1-32 3968 0 0.1 0.2 0.1 0.2 + runParser Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:111:7-15 3969 184758 0.0 0.0 0.0 0.0 + fromPos Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:46:21-27 3970 31081 0.0 0.0 0.0 0.0 + jstringSlow Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:(333,44)-(337,31) 3991 0 0.0 0.0 0.0 0.0 + scientific Data.Scientific src/Data/Scientific.hs:174:1-23 3999 0 0.0 0.0 0.0 0.0 + fromList Data.HashMap.Strict.Base Data/HashMap/Strict/Base.hs:598:1-64 3998 0 0.0 0.0 0.0 0.0 + unsafeInsert Data.HashMap.Base Data/HashMap/Base.hs:(784,1)-(814,76) 4000 132 0.0 0.0 0.0 0.0 + hash Data.HashMap.Base Data/HashMap/Base.hs:166:1-28 4001 132 0.0 0.0 0.0 0.0 + hashByteArrayWithSalt Data.Hashable.Class Data/Hashable/Class.hs:(770,1)-(772,20) 4002 132 0.0 0.0 0.0 0.0 + copy Data.HashMap.Array Data/HashMap/Array.hs:(328,1)-(333,30) 4009 98 0.0 0.0 0.0 0.0 + sparseIndex Data.HashMap.Base Data/HashMap/Base.hs:1867:1-42 4010 58 0.0 0.0 0.0 0.0 + new_ Data.HashMap.Array Data/HashMap/Array.hs:256:1-28 4008 49 0.0 0.0 0.0 0.0 + object_ Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:132:46-89 3955 0 0.0 0.1 1.3 2.1 + runParser Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:111:7-15 3956 80825 0.0 0.0 0.0 0.0 + fromPos Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:46:21-27 3957 17308 0.0 0.0 0.0 0.0 + array_ Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:169:35-59 3971 0 0.0 0.0 0.0 0.0 + jstring Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:317:1-32 3958 0 1.1 1.5 1.3 2.0 + runParser Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:111:7-15 3959 1858836 0.0 0.0 0.0 0.0 + fromPos Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:46:21-27 3960 309351 0.0 0.0 0.0 0.0 + jstringSlow Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:(333,44)-(337,31) 3984 207 0.0 0.0 0.0 0.2 + runParser Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:111:7-15 3985 17077 0.0 0.0 0.0 0.0 + fromPos Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:46:21-27 3986 2739 0.0 0.0 0.0 0.0 + array_ Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:169:35-59 3988 0 0.0 0.1 0.0 0.1 + runParser Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:111:7-15 3989 105487 0.0 0.0 0.0 0.0 + fromPos Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:46:21-27 3990 17284 0.0 0.0 0.0 0.0 + unescapeText Data.Aeson.Parser.UnescapePure pure/Data/Aeson/Parser/UnescapePure.hs:254:1-70 3987 0 0.0 0.0 0.0 0.0 + array_ Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:169:35-59 3964 0 0.2 0.3 0.2 0.4 + runParser Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:111:7-15 3965 304197 0.0 0.0 0.0 0.0 + fromPos Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:46:21-27 3966 49863 0.0 0.0 0.0 0.0 + marray# Data.Primitive.Array Data/Primitive/Array.hs:92:5-11 4026 145 0.0 0.0 0.0 0.0 + unId Data.Vector.Fusion.Util Data/Vector/Fusion/Util.hs:25:21-24 4025 57 0.0 0.0 0.0 0.0 + sChunks Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:122:30-36 4024 8 0.0 0.0 0.0 0.0 + sSize Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:124:30-34 4023 8 0.0 0.0 0.0 0.0 + upperBound Data.Vector.Fusion.Bundle.Size Data/Vector/Fusion/Bundle/Size.hs:(126,1)-(128,30) 4022 8 0.0 0.0 0.0 0.0 + jstringSlow Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:(333,44)-(337,31) 3972 5 0.0 0.0 0.0 0.1 + runParser Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:111:7-15 3973 1383 0.0 0.0 0.0 0.0 + fromPos Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:46:21-27 3974 221 0.0 0.0 0.0 0.0 + unescapeText Data.Aeson.Parser.UnescapePure pure/Data/Aeson/Parser/UnescapePure.hs:254:1-70 3975 0 0.0 0.1 0.0 0.1 + readStdJSON EVM.Solidity src/EVM/Solidity.hs:(364,1)-(407,39) 4029 1 0.1 0.2 3.7 5.8 + hash Data.HashMap.Base Data/HashMap/Base.hs:166:1-28 4112 408 0.0 0.0 0.0 0.0 + hashByteArrayWithSalt Data.Hashable.Class Data/Hashable/Class.hs:(770,1)-(772,20) 4113 408 0.0 0.0 0.0 0.0 + sparseIndex Data.HashMap.Base Data/HashMap/Base.hs:1867:1-42 4115 406 0.0 0.0 0.0 0.0 + unId Data.Vector.Fusion.Util Data/Vector/Fusion/Util.hs:25:21-24 4164 159 0.0 0.0 0.0 0.0 + array# Data.Primitive.Array Data/Primitive/Array.hs:87:5-10 4165 131 0.0 0.0 0.0 0.0 + signature EVM.Solidity src/EVM/Solidity.hs:(468,1)-(478,7) 4173 83 0.0 0.0 0.0 0.0 + hash Data.HashMap.Base Data/HashMap/Base.hs:166:1-28 4175 364 0.0 0.0 0.0 0.0 + hashByteArrayWithSalt Data.Hashable.Class Data/Hashable/Class.hs:(770,1)-(772,20) 4176 364 0.0 0.0 0.0 0.0 + sparseIndex Data.HashMap.Base Data/HashMap/Base.hs:1867:1-42 4177 364 0.0 0.0 0.0 0.0 + unId Data.Vector.Fusion.Util Data/Vector/Fusion/Util.hs:25:21-24 4178 198 0.0 0.0 0.0 0.0 + array# Data.Primitive.Array Data/Primitive/Array.hs:87:5-10 4201 115 0.0 0.0 0.0 0.0 + parseMethodInput EVM.Solidity src/EVM/Solidity.hs:(490,1)-(493,3) 5605 11 0.0 0.0 0.0 0.0 + hash Data.HashMap.Base Data/HashMap/Base.hs:166:1-28 5615 11 0.0 0.0 0.0 0.0 + hashByteArrayWithSalt Data.Hashable.Class Data/Hashable/Class.hs:(770,1)-(772,20) 5616 11 0.0 0.0 0.0 0.0 + sparseIndex Data.HashMap.Base Data/HashMap/Base.hs:1867:1-42 5617 11 0.0 0.0 0.0 0.0 + parseTypeName EVM.ABI src/EVM/ABI.hs:375:1-50 5607 0 0.0 0.0 0.0 0.0 + unParser Text.Megaparsec.Internal Text/Megaparsec/Internal.hs:120:5-12 5618 233 0.0 0.0 0.0 0.0 + parseMaybe Text.Megaparsec Text/Megaparsec.hs:(191,1)-(194,21) 5608 11 0.0 0.0 0.0 0.0 + runParser Text.Megaparsec Text/Megaparsec.hs:223:1-61 5610 11 0.0 0.0 0.0 0.0 + runParser' Text.Megaparsec Text/Megaparsec.hs:236:1-42 5611 11 0.0 0.0 0.0 0.0 + runParserT' Text.Megaparsec Text/Megaparsec.hs:(261,1)-(274,54) 5612 11 0.0 0.0 0.0 0.0 + runParsecT Text.Megaparsec.Internal Text/Megaparsec/Internal.hs:(591,1)-(596,56) 5613 11 0.0 0.0 0.0 0.0 + unParser Text.Megaparsec.Internal Text/Megaparsec/Internal.hs:120:5-12 5614 180 0.0 0.0 0.0 0.0 + stateParseErrors Text.Megaparsec.State Text/Megaparsec/State.hs:48:5-20 5619 11 0.0 0.0 0.0 0.0 + decode Data.ByteString.Base16 Data/ByteString/Base16.hs:(100,1)-(136,75) 4136 6 0.1 0.0 0.1 0.0 + stripBytecodeMetadata EVM.Solidity src/EVM/Solidity.hs:(569,1)-(573,22) 4135 6 0.0 0.0 0.0 0.0 + lazy Control.Lens.Iso src/Control/Lens/Iso.hs:569:1-18 4030 5 0.0 0.0 3.2 4.9 + hash Data.HashMap.Base Data/HashMap/Base.hs:166:1-28 4109 5 0.0 0.0 0.0 0.0 + hashByteArrayWithSalt Data.Hashable.Class Data/Hashable/Class.hs:(770,1)-(772,20) 4110 5 0.0 0.0 0.0 0.0 + maybeResult Data.Attoparsec.ByteString.Lazy Data/Attoparsec/ByteString/Lazy.hs:(103,1)-(104,32) 4031 5 0.0 0.0 0.0 0.0 + parse Data.Attoparsec.ByteString.Lazy Data/Attoparsec/ByteString/Lazy.hs:(88,1)-(95,56) 4032 5 0.0 0.0 3.2 4.9 + runParser Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:111:7-15 4033 80 0.0 0.0 0.0 0.0 + fromPos Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:46:21-27 4035 15 0.0 0.0 0.0 0.0 + buffer Data.Attoparsec.ByteString.Buffer Data/Attoparsec/ByteString/Buffer.hs:85:1-45 4034 5 0.0 0.0 0.0 0.0 + value Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:196:1-36 4036 0 0.1 0.0 3.2 4.9 + array_ Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:169:35-59 4043 0 0.1 0.2 0.5 0.7 + runParser Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:111:7-15 4044 155263 0.0 0.0 0.0 0.0 + fromPos Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:46:21-27 4045 31458 0.0 0.0 0.0 0.0 + marray# Data.Primitive.Array Data/Primitive/Array.hs:92:5-11 4089 102 0.0 0.0 0.0 0.0 + unId Data.Vector.Fusion.Util Data/Vector/Fusion/Util.hs:25:21-24 4088 54 0.0 0.0 0.0 0.0 + sChunks Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:122:30-36 4087 20 0.0 0.0 0.0 0.0 + sSize Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:124:30-34 4086 20 0.0 0.0 0.0 0.0 + upperBound Data.Vector.Fusion.Bundle.Size Data/Vector/Fusion/Bundle/Size.hs:(126,1)-(128,30) 4085 20 0.0 0.0 0.0 0.0 + jstring Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:317:1-32 4060 0 0.3 0.2 0.3 0.2 + runParser Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:111:7-15 4061 248104 0.0 0.0 0.0 0.0 + fromPos Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:46:21-27 4062 40882 0.0 0.0 0.0 0.0 + jstringSlow Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:(333,44)-(337,31) 4074 0 0.0 0.0 0.0 0.0 + object_ Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:132:46-89 4063 0 0.0 0.0 0.0 0.0 + runParser Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:111:7-15 4064 891 0.0 0.0 0.0 0.0 + marray# Data.Primitive.Array Data/Primitive/Array.hs:92:5-11 4098 233 0.0 0.0 0.0 0.0 + fromPos Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:46:21-27 4065 173 0.0 0.0 0.0 0.0 + unId Data.Vector.Fusion.Util Data/Vector/Fusion/Util.hs:25:21-24 4097 81 0.0 0.0 0.0 0.0 + sChunks Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:122:30-36 4096 5 0.0 0.0 0.0 0.0 + sSize Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:124:30-34 4095 5 0.0 0.0 0.0 0.0 + upperBound Data.Vector.Fusion.Bundle.Size Data/Vector/Fusion/Bundle/Size.hs:(126,1)-(128,30) 4094 5 0.0 0.0 0.0 0.0 + scientific Data.Scientific src/Data/Scientific.hs:174:1-23 4093 0 0.0 0.0 0.0 0.0 + jstringSlow Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:(333,44)-(337,31) 4075 0 0.0 0.0 0.0 0.0 + runParser Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:111:7-15 4078 32 0.0 0.0 0.0 0.0 + fromPos Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:46:21-27 4079 6 0.0 0.0 0.0 0.0 + object_ Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:132:46-89 4076 0 0.0 0.0 0.0 0.0 + jstring Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:317:1-32 4077 0 0.0 0.0 0.0 0.0 + object_ Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:132:46-89 4049 0 0.0 0.0 0.1 0.3 + runParser Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:111:7-15 4058 4975 0.0 0.0 0.0 0.0 + fromPos Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:46:21-27 4059 970 0.0 0.0 0.0 0.0 + marray# Data.Primitive.Array Data/Primitive/Array.hs:92:5-11 4103 14 0.0 0.0 0.0 0.0 + unId Data.Vector.Fusion.Util Data/Vector/Fusion/Util.hs:25:21-24 4102 6 0.0 0.0 0.0 0.0 + sChunks Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:122:30-36 4101 2 0.0 0.0 0.0 0.0 + sSize Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:124:30-34 4100 2 0.0 0.0 0.0 0.0 + upperBound Data.Vector.Fusion.Bundle.Size Data/Vector/Fusion/Bundle/Size.hs:(126,1)-(128,30) 4099 2 0.0 0.0 0.0 0.0 + jstring Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:317:1-32 4050 0 0.1 0.3 0.1 0.3 + runParser Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:111:7-15 4051 372571 0.0 0.0 0.0 0.0 + fromPos Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:46:21-27 4052 62673 0.0 0.0 0.0 0.0 + jstringSlow Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:(333,44)-(337,31) 4073 0 0.0 0.0 0.0 0.0 + scientific Data.Scientific src/Data/Scientific.hs:174:1-23 4081 0 0.0 0.0 0.0 0.0 + fromList Data.HashMap.Strict.Base Data/HashMap/Strict/Base.hs:598:1-64 4080 0 0.0 0.0 0.0 0.0 + unsafeInsert Data.HashMap.Base Data/HashMap/Base.hs:(784,1)-(814,76) 4082 958 0.0 0.0 0.0 0.0 + hash Data.HashMap.Base Data/HashMap/Base.hs:166:1-28 4083 958 0.0 0.0 0.0 0.0 + hashByteArrayWithSalt Data.Hashable.Class Data/Hashable/Class.hs:(770,1)-(772,20) 4084 958 0.0 0.0 0.0 0.0 + copy Data.HashMap.Array Data/HashMap/Array.hs:(328,1)-(333,30) 4091 676 0.0 0.0 0.0 0.0 + sparseIndex Data.HashMap.Base Data/HashMap/Base.hs:1867:1-42 4092 514 0.0 0.0 0.0 0.0 + new_ Data.HashMap.Array Data/HashMap/Array.hs:256:1-28 4090 338 0.0 0.0 0.0 0.0 + object_ Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:132:46-89 4037 0 0.1 0.2 2.6 4.2 + runParser Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:111:7-15 4038 164662 0.0 0.0 0.0 0.0 + fromPos Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:46:21-27 4039 35256 0.0 0.0 0.0 0.0 + array_ Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:169:35-59 4053 0 0.0 0.0 0.0 0.0 + jstring Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:317:1-32 4040 0 2.1 3.0 2.6 4.0 + runParser Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:111:7-15 4041 3769052 0.0 0.0 0.0 0.0 + fromPos Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:46:21-27 4042 627227 0.0 0.0 0.0 0.0 + jstringSlow Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:(333,44)-(337,31) 4066 414 0.1 0.0 0.3 0.3 + runParser Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:111:7-15 4067 34154 0.0 0.0 0.0 0.0 + fromPos Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:46:21-27 4068 5478 0.0 0.0 0.0 0.0 + array_ Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:169:35-59 4070 0 0.1 0.2 0.1 0.2 + runParser Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:111:7-15 4071 210974 0.0 0.0 0.0 0.0 + fromPos Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:46:21-27 4072 34568 0.0 0.0 0.0 0.0 + unescapeText Data.Aeson.Parser.UnescapePure pure/Data/Aeson/Parser/UnescapePure.hs:254:1-70 4069 0 0.1 0.1 0.1 0.1 + array_ Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:169:35-59 4046 0 0.2 0.6 0.3 0.7 + runParser Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:111:7-15 4047 623248 0.0 0.0 0.0 0.0 + fromPos Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:46:21-27 4048 102190 0.0 0.0 0.0 0.0 + marray# Data.Primitive.Array Data/Primitive/Array.hs:92:5-11 4108 688 0.0 0.0 0.0 0.0 + unId Data.Vector.Fusion.Util Data/Vector/Fusion/Util.hs:25:21-24 4107 320 0.0 0.0 0.0 0.0 + sChunks Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:122:30-36 4106 82 0.0 0.0 0.0 0.0 + sSize Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:124:30-34 4105 82 0.0 0.0 0.0 0.0 + upperBound Data.Vector.Fusion.Bundle.Size Data/Vector/Fusion/Bundle/Size.hs:(126,1)-(128,30) 4104 82 0.0 0.0 0.0 0.0 + jstringSlow Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:(333,44)-(337,31) 4054 10 0.0 0.0 0.1 0.1 + runParser Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:111:7-15 4055 2766 0.0 0.0 0.0 0.0 + fromPos Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:46:21-27 4056 442 0.0 0.0 0.0 0.0 + unescapeText Data.Aeson.Parser.UnescapePure pure/Data/Aeson/Parser/UnescapePure.hs:254:1-70 4057 0 0.1 0.1 0.1 0.1 + scientific Data.Scientific src/Data/Scientific.hs:174:1-23 4116 0 0.0 0.0 0.0 0.0 + sparseIndex Data.HashMap.Base Data/HashMap/Base.hs:1867:1-42 4111 5 0.0 0.0 0.0 0.0 + new_ Data.HashMap.Array Data/HashMap/Array.hs:256:1-28 4117 2 0.0 0.0 0.0 0.0 + abiKeccak EVM.Types src/EVM/Types.hs:(586,1)-(590,14) 4167 0 0.0 0.0 0.1 0.0 + word32 EVM.Types src/EVM/Types.hs:(576,1)-(577,52) 4200 23 0.0 0.0 0.0 0.0 + keccakBytes EVM.Types src/EVM/Types.hs:(570,1)-(573,15) 4168 0 0.0 0.0 0.1 0.0 + hash Crypto.Hash Crypto/Hash.hs:58:1-47 4169 23 0.0 0.0 0.0 0.0 + hashFinalize Crypto.Hash Crypto/Hash.hs:(92,1)-(95,17) 4170 23 0.0 0.0 0.0 0.0 + allocAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:74:1-45 4184 23 0.0 0.0 0.0 0.0 + new Basement.Block.Base Basement/Block/Base.hs:304:1-76 4185 23 0.0 0.0 0.0 0.0 + unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 4186 23 0.0 0.0 0.0 0.0 + withMutablePtrHint Basement.Block.Base Basement/Block/Base.hs:(475,1)-(489,39) 4187 23 0.0 0.0 0.0 0.0 + copy Data.ByteArray.Methods Data/ByteArray/Methods.hs:(223,1)-(226,21) 4192 23 0.0 0.0 0.0 0.0 + isMutablePinned Basement.Block.Base Basement/Block/Base.hs:100:1-90 4188 23 0.0 0.0 0.0 0.0 + compatIsMutableByteArrayPinned# Basement.Compat.Primitive Basement/Compat/Primitive.hs:70:1-65 4189 23 0.0 0.0 0.0 0.0 + toPinnedStatus# Basement.Compat.Primitive Basement/Compat/Primitive.hs:(47,1)-(48,27) 4190 23 0.0 0.0 0.0 0.0 + unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 4191 23 0.0 0.0 0.0 0.0 + hashInit Crypto.Hash Crypto/Hash.hs:(66,1)-(67,24) 4182 23 0.0 0.0 0.0 0.0 + allocAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:74:1-45 4183 23 0.0 0.0 0.0 0.0 + hashUpdate Crypto.Hash Crypto/Hash.hs:(71,1)-(73,37) 4171 23 0.0 0.0 0.0 0.0 + hashUpdates Crypto.Hash Crypto/Hash.hs:(81,1)-(86,32) 4179 23 0.0 0.0 0.0 0.0 + copyAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:(237,1)-(240,21) 4181 23 0.0 0.0 0.0 0.0 + null Data.ByteArray.Methods Data/ByteArray/Methods.hs:92:1-22 4180 23 0.0 0.0 0.0 0.0 + null Data.ByteArray.Methods Data/ByteArray/Methods.hs:92:1-22 4172 23 0.0 0.0 0.0 0.0 + unpack Data.ByteArray.Methods Data/ByteArray/Methods.hs:(104,1)-(110,34) 4193 23 0.0 0.0 0.1 0.0 + unsafeCast Basement.Block Basement/Block.hs:421:1-32 4194 759 0.0 0.0 0.0 0.0 + withPtr Basement.Block.Base Basement/Block/Base.hs:(402,1)-(411,31) 4195 736 0.0 0.0 0.1 0.0 + isPinned Basement.Block.Base Basement/Block/Base.hs:97:1-67 4196 736 0.1 0.0 0.1 0.0 + compatIsByteArrayPinned# Basement.Compat.Primitive Basement/Compat/Primitive.hs:67:1-51 4197 736 0.0 0.0 0.0 0.0 + toPinnedStatus# Basement.Compat.Primitive Basement/Compat/Primitive.hs:(47,1)-(48,27) 4198 736 0.0 0.0 0.0 0.0 + unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 4199 736 0.0 0.0 0.0 0.0 + keccak EVM.Types src/EVM/Types.hs:(580,1)-(583,12) 4126 0 0.0 0.0 0.0 0.1 + keccakBytes EVM.Types src/EVM/Types.hs:(570,1)-(573,15) 4130 0 0.0 0.0 0.0 0.1 + hash Crypto.Hash Crypto/Hash.hs:58:1-47 4131 43 0.0 0.0 0.0 0.0 + hashFinalize Crypto.Hash Crypto/Hash.hs:(92,1)-(95,17) 4132 43 0.0 0.0 0.0 0.0 + allocAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:74:1-45 4144 43 0.0 0.0 0.0 0.0 + new Basement.Block.Base Basement/Block/Base.hs:304:1-76 4145 43 0.0 0.0 0.0 0.0 + unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 4146 43 0.0 0.0 0.0 0.0 + withMutablePtrHint Basement.Block.Base Basement/Block/Base.hs:(475,1)-(489,39) 4147 43 0.0 0.0 0.0 0.0 + copy Data.ByteArray.Methods Data/ByteArray/Methods.hs:(223,1)-(226,21) 4152 43 0.0 0.0 0.0 0.0 + isMutablePinned Basement.Block.Base Basement/Block/Base.hs:100:1-90 4148 43 0.0 0.0 0.0 0.0 + compatIsMutableByteArrayPinned# Basement.Compat.Primitive Basement/Compat/Primitive.hs:70:1-65 4149 43 0.0 0.0 0.0 0.0 + toPinnedStatus# Basement.Compat.Primitive Basement/Compat/Primitive.hs:(47,1)-(48,27) 4150 43 0.0 0.0 0.0 0.0 + unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 4151 43 0.0 0.0 0.0 0.0 + hashInit Crypto.Hash Crypto/Hash.hs:(66,1)-(67,24) 4141 43 0.0 0.0 0.0 0.0 + allocAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:74:1-45 4142 43 0.0 0.0 0.0 0.0 + hashUpdate Crypto.Hash Crypto/Hash.hs:(71,1)-(73,37) 4133 43 0.0 0.0 0.0 0.0 + hashUpdates Crypto.Hash Crypto/Hash.hs:(81,1)-(86,32) 4138 43 0.0 0.0 0.0 0.0 + copyAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:(237,1)-(240,21) 4140 43 0.0 0.0 0.0 0.0 + null Data.ByteArray.Methods Data/ByteArray/Methods.hs:92:1-22 4139 43 0.0 0.0 0.0 0.0 + null Data.ByteArray.Methods Data/ByteArray/Methods.hs:92:1-22 4134 43 0.0 0.0 0.0 0.0 + unpack Data.ByteArray.Methods Data/ByteArray/Methods.hs:(104,1)-(110,34) 4153 43 0.0 0.0 0.0 0.0 + unsafeCast Basement.Block Basement/Block.hs:421:1-32 4154 1419 0.0 0.0 0.0 0.0 + withPtr Basement.Block.Base Basement/Block/Base.hs:(402,1)-(411,31) 4155 1376 0.0 0.0 0.0 0.0 + isPinned Basement.Block.Base Basement/Block/Base.hs:97:1-67 4156 1376 0.0 0.0 0.0 0.0 + compatIsByteArrayPinned# Basement.Compat.Primitive Basement/Compat/Primitive.hs:67:1-51 4157 1376 0.0 0.0 0.0 0.0 + toPinnedStatus# Basement.Compat.Primitive Basement/Compat/Primitive.hs:(47,1)-(48,27) 4158 1376 0.0 0.0 0.0 0.0 + unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 4159 1376 0.0 0.0 0.0 0.0 + word EVM.Types src/EVM/Types.hs:521:1-21 4128 0 0.0 0.0 0.0 0.0 + word256 EVM.Types src/EVM/Types.hs:(510,1)-(518,67) 4160 43 0.0 0.0 0.0 0.0 + padLeft EVM.Types src/EVM/Types.hs:495:1-54 4161 43 0.0 0.0 0.0 0.0 + bytesRead Data.Serialize.Get src/Data/Serialize/Get.hs:838:1-45 4163 0 0.0 0.0 0.0 0.0 + makeSrcMaps EVM.Solidity src/EVM/Solidity.hs:(227,1)-(271,126) 4203 0 0.4 0.5 0.4 0.5 + union Data.HashMap.Base Data/HashMap/Base.hs:1287:1-23 4114 0 0.0 0.0 0.0 0.0 + runUnitTestContract EVM.UnitTest src/EVM/UnitTest.hs:(477,1)-(528,68) 4271 1 0.0 0.0 88.6 83.0 + interpret EVM.Stepper src/EVM/Stepper.hs:(117,1)-(141,33) 4272 7 0.0 0.0 0.1 0.2 + enter EVM.Stepper src/EVM/Stepper.hs:114:1-48 4281 0 0.0 0.0 0.0 0.0 + pushTrace EVM src/EVM.hs:(2438,1)-(2441,59) 4282 0 0.0 0.0 0.0 0.0 + children Data.Tree.Zipper Data/Tree/Zipper.hs:(166,1)-(172,7) 4425 1 0.0 0.0 0.0 0.0 + exec EVM.Exec src/EVM/Exec.hs:(48,1)-(51,23) 4295 0 0.0 0.0 0.1 0.2 + exec1 EVM src/EVM.hs:(547,1)-(1323,42) 4429 0 0.0 0.0 0.1 0.2 + genFromCV Data.SBV.Core.Model Data/SBV/Core/Model.hs:(103,1)-(104,95) 4435 166 0.0 0.0 0.0 0.0 + index EVM.Symbolic src/EVM/Symbolic.hs:(207,1)-(208,47) 4431 166 0.0 0.0 0.0 0.0 + genLiteral Data.SBV.Core.Model Data/SBV/Core/Model.hs:99:1-48 4433 0 0.0 0.0 0.0 0.0 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 4434 166 0.0 0.0 0.0 0.0 + len EVM.Symbolic src/EVM/Symbolic.hs:(161,1)-(162,38) 4430 166 0.0 0.0 0.0 0.0 + num EVM.Types src/EVM/Types.hs:492:1-18 4436 81 0.0 0.0 0.0 0.0 + limitStack EVM src/EVM.hs:(1809,1)-(1813,17) 4438 76 0.0 0.0 0.0 0.0 + burn EVM src/EVM.hs:(1826,1)-(1838,38) 4440 76 0.0 0.0 0.0 0.0 + num EVM.Types src/EVM/Types.hs:492:1-18 4442 76 0.0 0.0 0.0 0.0 + next EVM src/EVM.hs:543:1-46 4445 0 0.0 0.0 0.0 0.0 + pushSym EVM src/EVM.hs:2477:1-34 4447 0 0.0 0.0 0.0 0.0 + pushSym EVM src/EVM.hs:2477:1-34 4446 76 0.0 0.0 0.0 0.0 + next EVM src/EVM.hs:543:1-46 4444 71 0.0 0.0 0.0 0.0 + opSize EVM src/EVM.hs:(2542,1)-(2543,37) 4448 71 0.0 0.0 0.0 0.0 + num EVM.Types src/EVM/Types.hs:492:1-18 4449 49 0.0 0.0 0.0 0.0 + genFromCV Data.SBV.Core.Model Data/SBV/Core/Model.hs:(103,1)-(104,95) 5186 1 0.0 0.0 0.0 0.0 + svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 5187 1 0.0 0.0 0.0 0.0 + svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 5188 1 0.0 0.0 0.0 0.0 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 5189 1 0.0 0.0 0.0 0.0 + litWord EVM.Symbolic src/EVM/Symbolic.hs:24:1-52 5175 1 0.0 0.0 0.0 0.0 + genLiteral Data.SBV.Core.Model Data/SBV/Core/Model.hs:99:1-48 5177 1 0.0 0.0 0.0 0.0 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 5178 1 0.0 0.0 0.0 0.0 + svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 5179 1 0.0 0.0 0.0 0.0 + svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 5180 1 0.0 0.0 0.0 0.0 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 5181 1 0.0 0.0 0.0 0.0 + num EVM.Types src/EVM/Types.hs:492:1-18 5174 1 0.0 0.0 0.0 0.0 + w256lit EVM.Types src/EVM/Types.hs:346:1-48 4437 49 0.0 0.0 0.0 0.0 + genLiteral Data.SBV.Core.Model Data/SBV/Core/Model.hs:99:1-48 4452 47 0.0 0.0 0.0 0.0 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 4460 46 0.0 0.0 0.0 0.0 + svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 4461 46 0.0 0.0 0.0 0.0 + svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 4462 46 0.0 0.0 0.0 0.0 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 4463 46 0.0 0.0 0.0 0.0 + padRight EVM.Types src/EVM/Types.hs:498:1-55 4465 46 0.0 0.0 0.0 0.0 + burn EVM src/EVM.hs:(1826,1)-(1838,38) 4507 34 0.0 0.0 0.0 0.0 + num EVM.Types src/EVM/Types.hs:492:1-18 4508 34 0.0 0.0 0.0 0.0 + accessStorage EVM src/EVM.hs:(1674,1)-(1702,35) 4510 0 0.0 0.0 0.0 0.0 + readStorage EVM src/EVM.hs:(1662,1)-(1663,58) 4511 3 0.0 0.0 0.0 0.0 + forceLit EVM.Symbolic src/EVM/Symbolic.hs:(40,1)-(42,49) 4512 3 0.0 0.0 0.0 0.0 + genFromCV Data.SBV.Core.Model Data/SBV/Core/Model.hs:(103,1)-(104,95) 5219 1 0.0 0.0 0.0 0.0 + svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 5220 1 0.0 0.0 0.0 0.0 + svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 5221 1 0.0 0.0 0.0 0.0 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 5222 1 0.0 0.0 0.0 0.0 + writeStorage EVM src/EVM.hs:(1666,1)-(1667,78) 4529 2 0.0 0.0 0.0 0.0 + forceLit EVM.Symbolic src/EVM/Symbolic.hs:(40,1)-(42,49) 4531 2 0.0 0.0 0.0 0.0 + genFromCV Data.SBV.Core.Model Data/SBV/Core/Model.hs:(103,1)-(104,95) 4538 2 0.0 0.0 0.0 0.0 + svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 4539 2 0.0 0.0 0.0 0.0 + svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 4540 2 0.0 0.0 0.0 0.0 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 4541 2 0.0 0.0 0.0 0.0 + forceConcrete EVM src/EVM.hs:(1846,1)-(1848,22) 5000 0 0.0 0.0 0.0 0.0 + checkJump EVM src/EVM.hs:(2526,1)-(2539,35) 5001 0 0.0 0.0 0.0 0.0 + unId Data.Vector.Fusion.Util Data/Vector/Fusion/Util.hs:25:21-24 5008 16 0.0 0.0 0.0 0.0 + num EVM.Types src/EVM/Types.hs:492:1-18 5002 8 0.0 0.0 0.0 0.0 + array# Data.Primitive.Array Data/Primitive/Array.hs:87:5-10 5009 4 0.0 0.0 0.0 0.0 + genFromCV Data.SBV.Core.Model Data/SBV/Core/Model.hs:(103,1)-(104,95) 5007 4 0.0 0.0 0.0 0.0 + index EVM.Symbolic src/EVM/Symbolic.hs:(207,1)-(208,47) 5004 4 0.0 0.0 0.0 0.0 + genLiteral Data.SBV.Core.Model Data/SBV/Core/Model.hs:99:1-48 5005 0 0.0 0.0 0.0 0.0 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 5006 4 0.0 0.0 0.0 0.0 + len EVM.Symbolic src/EVM/Symbolic.hs:(161,1)-(162,38) 5003 4 0.0 0.0 0.0 0.0 + next EVM src/EVM.hs:543:1-46 4523 0 0.0 0.0 0.0 0.0 + stackOp2 EVM src/EVM.hs:(2500,1)-(2507,14) 4492 23 0.0 0.0 0.0 0.0 + burn EVM src/EVM.hs:(1826,1)-(1838,38) 4499 23 0.0 0.0 0.0 0.0 + num EVM.Types src/EVM/Types.hs:492:1-18 4500 23 0.0 0.0 0.0 0.0 + next EVM src/EVM.hs:543:1-46 4502 0 0.0 0.0 0.0 0.0 + next EVM src/EVM.hs:543:1-46 4501 23 0.0 0.0 0.0 0.0 + opSize EVM src/EVM.hs:(2542,1)-(2543,37) 4503 23 0.0 0.0 0.0 0.0 + svTimes Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(155,1)-(160,81) 4572 6 0.0 0.0 0.0 0.0 + cvVal Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:155:16-20 5228 2 0.0 0.0 0.0 0.0 + mapCV2 Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(359,1)-(371,141) 5229 2 0.0 0.0 0.0 0.0 + cvVal Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:155:16-20 5231 4 0.0 0.0 0.0 0.0 + cvSameType Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:231:1-37 5230 2 0.0 0.0 0.0 0.0 + svAnd Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(373,1)-(383,50) 4594 5 0.0 0.0 0.0 0.0 + mapCV2 Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(359,1)-(371,141) 5190 3 0.0 0.0 0.0 0.0 + cvVal Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:155:16-20 5192 6 0.0 0.0 0.0 0.0 + cvSameType Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:231:1-37 5191 3 0.0 0.0 0.0 0.0 + .^ Data.SBV.Core.Model Data/SBV/Core/Model.hs:(1262,1)-(1280,49) 4574 3 0.0 0.0 0.0 0.0 + genFromCV Data.SBV.Core.Model Data/SBV/Core/Model.hs:(103,1)-(104,95) 4578 3 0.0 0.0 0.0 0.0 + sFromIntegral Data.SBV.Core.Model Data/SBV/Core/Model.hs:(1428,1)-(1441,70) 4576 3 0.0 0.0 0.0 0.0 + genFromCV Data.SBV.Core.Model Data/SBV/Core/Model.hs:(103,1)-(104,95) 4580 3 0.0 0.0 0.0 0.0 + svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 4581 3 0.0 0.0 0.0 0.0 + svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 4582 3 0.0 0.0 0.0 0.0 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 4583 3 0.0 0.0 0.0 0.0 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 4579 3 0.0 0.0 0.0 0.0 + svTimes Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(155,1)-(160,81) 5223 2 0.0 0.0 0.0 0.0 + cvVal Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:155:16-20 5224 1 0.0 0.0 0.0 0.0 + mapCV2 Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(359,1)-(371,141) 5225 1 0.0 0.0 0.0 0.0 + cvVal Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:155:16-20 5227 2 0.0 0.0 0.0 0.0 + cvSameType Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:231:1-37 5226 1 0.0 0.0 0.0 0.0 + forceLit EVM.Symbolic src/EVM/Symbolic.hs:(40,1)-(42,49) 4494 3 0.0 0.0 0.0 0.0 + genFromCV Data.SBV.Core.Model Data/SBV/Core/Model.hs:(103,1)-(104,95) 4495 3 0.0 0.0 0.0 0.0 + svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 4496 3 0.0 0.0 0.0 0.0 + svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 4497 3 0.0 0.0 0.0 0.0 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 4498 3 0.0 0.0 0.0 0.0 + iteWhiff EVM.Types src/EVM/Types.hs:211:1-34 4913 3 0.0 0.0 0.0 0.0 + ite Data.SBV.Core.Model Data/SBV/Core/Model.hs:(1817,1)-(1819,52) 4965 3 0.0 0.0 0.0 0.0 + cvToBool Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:235:1-34 4966 3 0.0 0.0 0.0 0.0 + cvVal Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:155:16-20 4967 3 0.0 0.0 0.0 0.0 + svOr Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(387,1)-(398,48) 4589 3 0.0 0.0 0.0 0.0 + mapCV2 Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(359,1)-(371,141) 5232 1 0.0 0.0 0.0 0.0 + cvVal Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:155:16-20 5234 2 0.0 0.0 0.0 0.0 + cvSameType Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:231:1-37 5233 1 0.0 0.0 0.0 0.0 + svPlus Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(148,1)-(151,80) 5025 2 0.0 0.0 0.0 0.0 + cvVal Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:155:16-20 5026 2 0.0 0.0 0.0 0.0 + mapCV2 Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(359,1)-(371,141) 5027 2 0.0 0.0 0.0 0.0 + cvVal Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:155:16-20 5029 4 0.0 0.0 0.0 0.0 + cvSameType Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:231:1-37 5028 2 0.0 0.0 0.0 0.0 + ceilDiv EVM src/EVM.hs:2835:1-31 5218 1 0.0 0.0 0.0 0.0 + log2 EVM src/EVM.hs:2841:1-50 5217 1 0.0 0.0 0.0 0.0 + num EVM.Types src/EVM/Types.hs:492:1-18 5216 1 0.0 0.0 0.0 0.0 + sShiftRight Data.SBV.Core.Model Data/SBV/Core/Model.hs:1464:1-38 4978 1 0.0 0.0 0.0 0.0 + svShiftRight Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:726:1-28 4980 0 0.0 0.0 0.0 0.0 + svEqual Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(288,1)-(292,129) 4995 1 0.0 0.0 0.0 0.0 + cvVal Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:155:16-20 4996 1 0.0 0.0 0.0 0.0 + liftCV2 Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(310,1)-(322,148) 4997 1 0.0 0.0 0.0 0.0 + cvVal Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:155:16-20 4998 2 0.0 0.0 0.0 0.0 + svBool Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:81:1-40 4999 1 0.0 0.0 0.0 0.0 + svGreaterThan Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(352,1)-(355,147) 4990 1 0.0 0.0 0.0 0.0 + cvVal Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:155:16-20 4991 1 0.0 0.0 0.0 0.0 + liftCV2 Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(310,1)-(322,148) 4992 1 0.0 0.0 0.0 0.0 + cvVal Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:155:16-20 4993 2 0.0 0.0 0.0 0.0 + svBool Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:81:1-40 4994 1 0.0 0.0 0.0 0.0 + svLessThan Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(345,1)-(348,143) 4917 1 0.0 0.0 0.0 0.0 + cvVal Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:155:16-20 4961 1 0.0 0.0 0.0 0.0 + liftCV2 Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(310,1)-(322,148) 4962 1 0.0 0.0 0.0 0.0 + cvVal Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:155:16-20 4963 2 0.0 0.0 0.0 0.0 + svBool Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:81:1-40 4964 1 0.0 0.0 0.0 0.0 + svUNeg Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:170:1-61 5031 0 0.0 0.0 0.0 0.0 + mapCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(334,1)-(346,133) 5032 1 0.0 0.0 0.0 0.0 + cvVal Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:155:16-20 5033 1 0.0 0.0 0.0 0.0 + next EVM src/EVM.hs:543:1-46 4514 20 0.0 0.0 0.0 0.0 + opSize EVM src/EVM.hs:(2542,1)-(2543,37) 4524 20 0.0 0.0 0.0 0.0 + forceConcrete EVM src/EVM.hs:(1846,1)-(1848,22) 4450 16 0.0 0.0 0.0 0.0 + maybeLitWord EVM.Types src/EVM/Types.hs:324:1-68 4453 23 0.0 0.0 0.0 0.0 + genFromCV Data.SBV.Core.Model Data/SBV/Core/Model.hs:(103,1)-(104,95) 4469 22 0.0 0.0 0.0 0.0 + svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 4470 22 0.0 0.0 0.0 0.0 + svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 4471 22 0.0 0.0 0.0 0.0 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 4472 22 0.0 0.0 0.0 0.0 + burn EVM src/EVM.hs:(1826,1)-(1838,38) 4454 17 0.0 0.0 0.0 0.0 + num EVM.Types src/EVM/Types.hs:492:1-18 4455 17 0.0 0.0 0.0 0.0 + accessMemoryWord EVM src/EVM.hs:2391:1-53 4475 0 0.0 0.0 0.0 0.0 + accessMemoryRange EVM src/EVM.hs:(2383,1)-(2387,53) 4476 0 0.0 0.0 0.0 0.0 + accessUnboundedMemoryRange EVM src/EVM.hs:(2368,1)-(2375,14) 4477 0 0.0 0.0 0.0 0.0 + memoryCost EVM src/EVM.hs:(2824,1)-(2830,30) 4482 10 0.0 0.0 0.0 0.0 + ceilDiv EVM src/EVM.hs:2835:1-31 4483 10 0.0 0.0 0.0 0.0 + ceilDiv EVM src/EVM.hs:2835:1-31 4481 5 0.0 0.0 0.0 0.0 + num EVM.Types src/EVM/Types.hs:492:1-18 4479 5 0.0 0.0 0.0 0.0 + word256At EVM src/EVM.hs:(2418,1)-(2420,34) 4489 0 0.0 0.0 0.0 0.0 + setMemoryWord EVM.Symbolic src/EVM/Symbolic.hs:(191,1)-(194,61) 4490 3 0.0 0.0 0.0 0.0 + maybeLitWord EVM.Types src/EVM/Types.hs:324:1-68 4491 3 0.0 0.0 0.0 0.0 + genFromCV Data.SBV.Core.Model Data/SBV/Core/Model.hs:(103,1)-(104,95) 4696 3 0.0 0.0 0.0 0.0 + svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 4697 3 0.0 0.0 0.0 0.0 + svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 4698 3 0.0 0.0 0.0 0.0 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 4699 3 0.0 0.0 0.0 0.0 + setMemoryWord EVM.Concrete src/EVM/Concrete.hs:(82,1)-(83,43) 4688 3 0.0 0.0 0.0 0.0 + num EVM.Types src/EVM/Types.hs:492:1-18 4690 3 0.0 0.0 0.0 0.0 + word256Bytes EVM.Types src/EVM/Types.hs:537:1-59 4693 3 0.0 0.0 0.0 0.0 + byteAt EVM.Types src/EVM/Types.hs:524:1-46 4694 96 0.0 0.0 0.0 0.0 + num EVM.Types src/EVM/Types.hs:492:1-18 4695 96 0.0 0.0 0.0 0.0 + writeMemory EVM.Concrete src/EVM/Concrete.hs:(46,1)-(59,22) 4689 3 0.0 0.0 0.0 0.0 + num EVM.Types src/EVM/Types.hs:492:1-18 4691 12 0.0 0.0 0.0 0.0 + sliceMemory EVM.Concrete src/EVM/Concrete.hs:(42,1)-(43,50) 4700 3 0.0 0.0 0.0 0.0 + num EVM.Types src/EVM/Types.hs:492:1-18 4701 6 0.0 0.0 0.0 0.0 + byteStringSliceWithDefaultZeroes EVM.Concrete src/EVM/Concrete.hs:(27,1)-(35,51) 4702 3 0.0 0.0 0.0 0.0 + checkJump EVM src/EVM.hs:(2526,1)-(2539,35) 4624 0 0.0 0.0 0.0 0.0 + unId Data.Vector.Fusion.Util Data/Vector/Fusion/Util.hs:25:21-24 4640 24 0.0 0.0 0.0 0.0 + num EVM.Types src/EVM/Types.hs:492:1-18 4625 12 0.0 0.0 0.0 0.0 + array# Data.Primitive.Array Data/Primitive/Array.hs:87:5-10 4641 6 0.0 0.0 0.0 0.0 + genFromCV Data.SBV.Core.Model Data/SBV/Core/Model.hs:(103,1)-(104,95) 4632 6 0.0 0.0 0.0 0.0 + index EVM.Symbolic src/EVM/Symbolic.hs:(207,1)-(208,47) 4628 6 0.0 0.0 0.0 0.0 + genLiteral Data.SBV.Core.Model Data/SBV/Core/Model.hs:99:1-48 4629 0 0.0 0.0 0.0 0.0 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 4630 6 0.0 0.0 0.0 0.0 + len EVM.Symbolic src/EVM/Symbolic.hs:(161,1)-(162,38) 4626 6 0.0 0.0 0.0 0.0 + checkJump EVM src/EVM.hs:(2526,1)-(2539,35) 4623 10 0.0 0.0 0.0 0.0 + num EVM.Types src/EVM/Types.hs:492:1-18 4631 10 0.0 0.0 0.0 0.0 + accessMemoryWord EVM src/EVM.hs:2391:1-53 4456 5 0.0 0.0 0.0 0.0 + accessMemoryRange EVM src/EVM.hs:(2383,1)-(2387,53) 4458 5 0.0 0.0 0.0 0.0 + accessUnboundedMemoryRange EVM src/EVM.hs:(2368,1)-(2375,14) 4473 5 0.0 0.0 0.0 0.0 + num EVM.Types src/EVM/Types.hs:492:1-18 4480 10 0.0 0.0 0.0 0.0 + num EVM.Types src/EVM/Types.hs:492:1-18 4687 5 0.0 0.0 0.0 0.0 + word256At EVM src/EVM.hs:(2418,1)-(2420,34) 4488 5 0.0 0.0 0.0 0.0 + readMemoryWord EVM.Symbolic src/EVM/Symbolic.hs:(183,1)-(184,75) 5010 2 0.0 0.0 0.0 0.0 + litWord EVM.Symbolic src/EVM/Symbolic.hs:24:1-52 5014 2 0.0 0.0 0.0 0.0 + genLiteral Data.SBV.Core.Model Data/SBV/Core/Model.hs:99:1-48 5017 2 0.0 0.0 0.0 0.0 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 5018 2 0.0 0.0 0.0 0.0 + svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 5019 2 0.0 0.0 0.0 0.0 + svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 5020 2 0.0 0.0 0.0 0.0 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 5021 2 0.0 0.0 0.0 0.0 + readMemoryWord EVM.Concrete src/EVM/Concrete.hs:(62,1)-(70,19) 5011 2 0.0 0.0 0.0 0.0 + num EVM.Types src/EVM/Types.hs:492:1-18 5012 68 0.0 0.0 0.0 0.0 + readByteOrZero EVM.Concrete src/EVM/Concrete.hs:24:1-46 5022 64 0.0 0.0 0.0 0.0 + readMemoryWord EVM.Concrete src/EVM/Concrete.hs:70:5-19 5013 2 0.0 0.0 0.0 0.0 + next EVM src/EVM.hs:543:1-46 4486 0 0.0 0.0 0.0 0.0 + stackOp1 EVM src/EVM.hs:(2485,1)-(2493,14) 4516 11 0.0 0.0 0.0 0.0 + burn EVM src/EVM.hs:(1826,1)-(1838,38) 4518 11 0.0 0.0 0.0 0.0 + num EVM.Types src/EVM/Types.hs:492:1-18 4519 11 0.0 0.0 0.0 0.0 + next EVM src/EVM.hs:543:1-46 4521 0 0.0 0.0 0.0 0.0 + next EVM src/EVM.hs:543:1-46 4520 11 0.0 0.0 0.0 0.0 + opSize EVM src/EVM.hs:(2542,1)-(2543,37) 4522 11 0.0 0.0 0.0 0.0 + iteWhiff EVM.Types src/EVM/Types.hs:211:1-34 4525 7 0.0 0.0 0.0 0.0 + ite Data.SBV.Core.Model Data/SBV/Core/Model.hs:(1817,1)-(1819,52) 4568 7 0.0 0.0 0.0 0.0 + cvToBool Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:235:1-34 4569 7 0.0 0.0 0.0 0.0 + cvVal Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:155:16-20 4570 7 0.0 0.0 0.0 0.0 + svEqual Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(288,1)-(292,129) 4557 7 0.0 0.0 0.0 0.0 + cvVal Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:155:16-20 4559 7 0.0 0.0 0.0 0.0 + liftCV2 Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(310,1)-(322,148) 4560 7 0.0 0.0 0.0 0.0 + cvVal Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:155:16-20 4561 14 0.0 0.0 0.0 0.0 + svBool Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:81:1-40 4566 7 0.0 0.0 0.0 0.0 + readSWordWithBound EVM.Symbolic src/EVM/Symbolic.hs:(136,1)-(157,48) 4968 1 0.0 0.0 0.0 0.0 + litWord EVM.Symbolic src/EVM/Symbolic.hs:24:1-52 4977 1 0.0 0.0 0.0 0.0 + genLiteral Data.SBV.Core.Model Data/SBV/Core/Model.hs:99:1-48 4983 1 0.0 0.0 0.0 0.0 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 4984 1 0.0 0.0 0.0 0.0 + svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 4985 1 0.0 0.0 0.0 0.0 + svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 4986 1 0.0 0.0 0.0 0.0 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 4987 1 0.0 0.0 0.0 0.0 + maybeLitWord EVM.Types src/EVM/Types.hs:324:1-68 4969 1 0.0 0.0 0.0 0.0 + genFromCV Data.SBV.Core.Model Data/SBV/Core/Model.hs:(103,1)-(104,95) 4970 1 0.0 0.0 0.0 0.0 + svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 4971 1 0.0 0.0 0.0 0.0 + svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 4972 1 0.0 0.0 0.0 0.0 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 4973 1 0.0 0.0 0.0 0.0 + readMemoryWord EVM.Concrete src/EVM/Concrete.hs:(62,1)-(70,19) 4974 1 0.0 0.0 0.0 0.0 + num EVM.Types src/EVM/Types.hs:492:1-18 4975 34 0.0 0.0 0.0 0.0 + readByteOrZero EVM.Concrete src/EVM/Concrete.hs:24:1-46 4989 32 0.0 0.0 0.0 0.0 + readMemoryWord EVM.Concrete src/EVM/Concrete.hs:70:5-19 4976 1 0.0 0.0 0.0 0.0 + svNot Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(417,1)-(423,34) 4591 0 0.0 0.0 0.0 0.0 + mapCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(334,1)-(346,133) 4592 3 0.0 0.0 0.0 0.0 + cvVal Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:155:16-20 4593 3 0.0 0.0 0.0 0.0 + notStatic EVM src/EVM.hs:(1816,1)-(1820,17) 4526 4 0.0 0.0 0.1 0.0 + accessStorage EVM src/EVM.hs:(1674,1)-(1702,35) 4528 3 0.0 0.0 0.0 0.0 + maybeLitWord EVM.Types src/EVM/Types.hs:324:1-68 4556 6 0.0 0.0 0.0 0.0 + genFromCV Data.SBV.Core.Model Data/SBV/Core/Model.hs:(103,1)-(104,95) 4600 6 0.0 0.0 0.0 0.0 + svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 4601 6 0.0 0.0 0.0 0.0 + svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 4602 6 0.0 0.0 0.0 0.0 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 4603 6 0.0 0.0 0.0 0.0 + accessStorageForGas EVM src/EVM.hs:(1919,1)-(1927,21) 4543 3 0.0 0.0 0.0 0.0 + maybeLitWord EVM.Types src/EVM/Types.hs:324:1-68 4544 3 0.0 0.0 0.0 0.0 + genFromCV Data.SBV.Core.Model Data/SBV/Core/Model.hs:(103,1)-(104,95) 4547 3 0.0 0.0 0.0 0.0 + svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 4548 3 0.0 0.0 0.0 0.0 + svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 4549 3 0.0 0.0 0.0 0.0 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 4550 3 0.0 0.0 0.0 0.0 + wordValue EVM.Concrete src/EVM/Concrete.hs:39:1-21 4546 3 0.0 0.0 0.0 0.0 + burn EVM src/EVM.hs:(1826,1)-(1838,38) 4609 3 0.0 0.0 0.0 0.0 + num EVM.Types src/EVM/Types.hs:492:1-18 4610 3 0.0 0.0 0.0 0.0 + writeStorage EVM src/EVM.hs:(1666,1)-(1667,78) 4633 3 0.0 0.0 0.0 0.0 + num EVM.Types src/EVM/Types.hs:492:1-18 4542 3 0.0 0.0 0.0 0.0 + readStorage EVM src/EVM.hs:(1662,1)-(1663,58) 4532 3 0.0 0.0 0.0 0.0 + forceLit EVM.Symbolic src/EVM/Symbolic.hs:(40,1)-(42,49) 4533 3 0.0 0.0 0.0 0.0 + genFromCV Data.SBV.Core.Model Data/SBV/Core/Model.hs:(103,1)-(104,95) 4534 3 0.0 0.0 0.0 0.0 + svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 4535 3 0.0 0.0 0.0 0.0 + svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 4536 3 0.0 0.0 0.0 0.0 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 4537 3 0.0 0.0 0.0 0.0 + forceLit EVM.Symbolic src/EVM/Symbolic.hs:(40,1)-(42,49) 4608 3 0.0 0.0 0.0 0.0 + maybeLitWord EVM.Types src/EVM/Types.hs:324:1-68 4599 3 0.0 0.0 0.0 0.0 + genFromCV Data.SBV.Core.Model Data/SBV/Core/Model.hs:(103,1)-(104,95) 4604 3 0.0 0.0 0.0 0.0 + svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 4605 3 0.0 0.0 0.0 0.0 + svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 4606 3 0.0 0.0 0.0 0.0 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 4607 3 0.0 0.0 0.0 0.0 + forceConcrete3 EVM src/EVM.hs:(1856,1)-(1858,36) 5023 1 0.0 0.0 0.1 0.0 + maybeLitWord EVM.Types src/EVM/Types.hs:324:1-68 5024 3 0.0 0.0 0.0 0.0 + genFromCV Data.SBV.Core.Model Data/SBV/Core/Model.hs:(103,1)-(104,95) 5034 3 0.0 0.0 0.0 0.0 + svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 5035 3 0.0 0.0 0.0 0.0 + svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 5036 3 0.0 0.0 0.0 0.0 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 5037 3 0.0 0.0 0.0 0.0 + num EVM.Types src/EVM/Types.hs:492:1-18 5121 2 0.0 0.0 0.0 0.0 + accessAccountForGas EVM src/EVM.hs:(1910,1)-(1914,17) 5046 1 0.0 0.0 0.0 0.0 + accessMemoryRange EVM src/EVM.hs:(2383,1)-(2387,53) 5038 1 0.0 0.0 0.1 0.0 + accessUnboundedMemoryRange EVM src/EVM.hs:(2368,1)-(2375,14) 5039 1 0.0 0.0 0.1 0.0 + burn EVM src/EVM.hs:(1826,1)-(1838,38) 5044 3 0.0 0.0 0.1 0.0 + num EVM.Types src/EVM/Types.hs:492:1-18 5045 4 0.0 0.0 0.0 0.0 + costOfCreate EVM src/EVM.hs:(2768,1)-(2774,58) 5048 1 0.0 0.0 0.0 0.0 + num EVM.Types src/EVM/Types.hs:492:1-18 5049 2 0.0 0.0 0.0 0.0 + allButOne64th EVM src/EVM.hs:2838:1-30 5051 1 0.0 0.0 0.0 0.0 + ceilDiv EVM src/EVM.hs:2835:1-31 5050 1 0.0 0.0 0.0 0.0 + create EVM src/EVM.hs:(2123,1)-(2184,30) 5096 1 0.0 0.0 0.1 0.0 + collision EVM src/EVM.hs:(2114,1)-(2118,18) 5102 1 0.0 0.0 0.0 0.0 + initialContract EVM src/EVM.hs:(516,1)-(533,39) 5130 1 0.0 0.0 0.1 0.0 + mkCodeOps EVM src/EVM.hs:(2721,1)-(2739,79) 5165 1 0.1 0.0 0.1 0.0 + marray# Data.Primitive.Array Data/Primitive/Array.hs:92:5-11 5172 1866 0.0 0.0 0.0 0.0 + unId Data.Vector.Fusion.Util Data/Vector/Fusion/Util.hs:25:21-24 5171 1866 0.0 0.0 0.0 0.0 + opSize EVM src/EVM.hs:(2542,1)-(2543,37) 5169 1865 0.0 0.0 0.0 0.0 + num EVM.Types src/EVM/Types.hs:492:1-18 5170 494 0.0 0.0 0.0 0.0 + readOp EVM src/EVM.hs:(2636,1)-(2718,21) 5173 1 0.0 0.0 0.0 0.0 + sChunks Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:122:30-36 5168 1 0.0 0.0 0.0 0.0 + sSize Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:124:30-34 5167 1 0.0 0.0 0.0 0.0 + upperBound Data.Vector.Fusion.Bundle.Size Data/Vector/Fusion/Bundle/Size.hs:(126,1)-(128,30) 5166 1 0.0 0.0 0.0 0.0 + mkOpIxMap EVM src/EVM.hs:(2549,1)-(2586,83) 5163 1 0.0 0.0 0.0 0.0 + len EVM.Symbolic src/EVM/Symbolic.hs:(161,1)-(162,38) 5164 1 0.0 0.0 0.0 0.0 + stripBytecodeMetadata EVM.Solidity src/EVM/Solidity.hs:(569,1)-(573,22) 5138 1 0.0 0.0 0.0 0.0 + keccak EVM.Types src/EVM/Types.hs:(580,1)-(583,12) 5131 0 0.0 0.0 0.0 0.0 + keccakBytes EVM.Types src/EVM/Types.hs:(570,1)-(573,15) 5133 0 0.0 0.0 0.0 0.0 + hash Crypto.Hash Crypto/Hash.hs:58:1-47 5134 1 0.0 0.0 0.0 0.0 + hashFinalize Crypto.Hash Crypto/Hash.hs:(92,1)-(95,17) 5135 1 0.0 0.0 0.0 0.0 + allocAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:74:1-45 5144 1 0.0 0.0 0.0 0.0 + new Basement.Block.Base Basement/Block/Base.hs:304:1-76 5145 1 0.0 0.0 0.0 0.0 + unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 5146 1 0.0 0.0 0.0 0.0 + withMutablePtrHint Basement.Block.Base Basement/Block/Base.hs:(475,1)-(489,39) 5147 1 0.0 0.0 0.0 0.0 + copy Data.ByteArray.Methods Data/ByteArray/Methods.hs:(223,1)-(226,21) 5152 1 0.0 0.0 0.0 0.0 + isMutablePinned Basement.Block.Base Basement/Block/Base.hs:100:1-90 5148 1 0.0 0.0 0.0 0.0 + compatIsMutableByteArrayPinned# Basement.Compat.Primitive Basement/Compat/Primitive.hs:70:1-65 5149 1 0.0 0.0 0.0 0.0 + toPinnedStatus# Basement.Compat.Primitive Basement/Compat/Primitive.hs:(47,1)-(48,27) 5150 1 0.0 0.0 0.0 0.0 + unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 5151 1 0.0 0.0 0.0 0.0 + hashInit Crypto.Hash Crypto/Hash.hs:(66,1)-(67,24) 5142 1 0.0 0.0 0.0 0.0 + allocAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:74:1-45 5143 1 0.0 0.0 0.0 0.0 + hashUpdate Crypto.Hash Crypto/Hash.hs:(71,1)-(73,37) 5136 1 0.0 0.0 0.0 0.0 + hashUpdates Crypto.Hash Crypto/Hash.hs:(81,1)-(86,32) 5139 1 0.0 0.0 0.0 0.0 + copyAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:(237,1)-(240,21) 5141 1 0.0 0.0 0.0 0.0 + null Data.ByteArray.Methods Data/ByteArray/Methods.hs:92:1-22 5140 1 0.0 0.0 0.0 0.0 + null Data.ByteArray.Methods Data/ByteArray/Methods.hs:92:1-22 5137 1 0.0 0.0 0.0 0.0 + unpack Data.ByteArray.Methods Data/ByteArray/Methods.hs:(104,1)-(110,34) 5153 1 0.0 0.0 0.0 0.0 + unsafeCast Basement.Block Basement/Block.hs:421:1-32 5154 33 0.0 0.0 0.0 0.0 + withPtr Basement.Block.Base Basement/Block/Base.hs:(402,1)-(411,31) 5155 32 0.0 0.0 0.0 0.0 + isPinned Basement.Block.Base Basement/Block/Base.hs:97:1-67 5156 32 0.0 0.0 0.0 0.0 + compatIsByteArrayPinned# Basement.Compat.Primitive Basement/Compat/Primitive.hs:67:1-51 5157 32 0.0 0.0 0.0 0.0 + toPinnedStatus# Basement.Compat.Primitive Basement/Compat/Primitive.hs:(47,1)-(48,27) 5158 32 0.0 0.0 0.0 0.0 + unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 5159 32 0.0 0.0 0.0 0.0 + word EVM.Types src/EVM/Types.hs:521:1-21 5132 0 0.0 0.0 0.0 0.0 + word256 EVM.Types src/EVM/Types.hs:(510,1)-(518,67) 5160 1 0.0 0.0 0.0 0.0 + padLeft EVM.Types src/EVM/Types.hs:495:1-54 5161 1 0.0 0.0 0.0 0.0 + bytesRead Data.Serialize.Get src/Data/Serialize/Get.hs:838:1-45 5162 0 0.0 0.0 0.0 0.0 + litWord EVM.Symbolic src/EVM/Symbolic.hs:24:1-52 5117 1 0.0 0.0 0.0 0.0 + genLiteral Data.SBV.Core.Model Data/SBV/Core/Model.hs:99:1-48 5125 1 0.0 0.0 0.0 0.0 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 5126 1 0.0 0.0 0.0 0.0 + svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 5127 1 0.0 0.0 0.0 0.0 + svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 5128 1 0.0 0.0 0.0 0.0 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 5129 1 0.0 0.0 0.0 0.0 + num EVM.Types src/EVM/Types.hs:492:1-18 5103 1 0.0 0.0 0.0 0.0 + pushTo EVM src/EVM.hs:1582:1-23 5112 1 0.0 0.0 0.0 0.0 + pushTrace EVM src/EVM.hs:(2438,1)-(2441,59) 5107 1 0.0 0.0 0.0 0.0 + children Data.Tree.Zipper Data/Tree/Zipper.hs:(166,1)-(172,7) 5113 1 0.0 0.0 0.0 0.0 + parents Data.Tree.Zipper Data/Tree/Zipper.hs:71:1-26 5294 1 0.0 0.0 0.0 0.0 + insert Data.Tree.Zipper Data/Tree/Zipper.hs:275:1-37 5295 1 0.0 0.0 0.0 0.0 + withTraceLocation EVM src/EVM.hs:(2426,1)-(2435,5) 5108 1 0.0 0.0 0.0 0.0 + transfer EVM src/EVM.hs:(1326,1)-(1329,31) 5106 1 0.0 0.0 0.0 0.0 + w256 EVM.Types src/EVM/Types.hs:90:1-24 5215 1 0.0 0.0 0.0 0.0 + litAddr EVM.Symbolic src/EVM/Symbolic.hs:27:1-36 5118 0 0.0 0.0 0.0 0.0 + genLiteral Data.SBV.Core.Model Data/SBV/Core/Model.hs:99:1-48 5119 1 0.0 0.0 0.0 0.0 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 5182 1 0.0 0.0 0.0 0.0 + svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 5183 1 0.0 0.0 0.0 0.0 + svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 5184 1 0.0 0.0 0.0 0.0 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 5185 1 0.0 0.0 0.0 0.0 + next EVM src/EVM.hs:543:1-46 5111 0 0.0 0.0 0.0 0.0 + touchAccount EVM src/EVM.hs:1895:1-57 5104 0 0.0 0.0 0.0 0.0 + pushTo EVM src/EVM.hs:1582:1-23 5105 2 0.0 0.0 0.0 0.0 + accessAccountForGas EVM src/EVM.hs:(1910,1)-(1914,17) 5047 0 0.0 0.0 0.0 0.0 + num EVM.Types src/EVM/Types.hs:492:1-18 5040 3 0.0 0.0 0.0 0.0 + memoryCost EVM src/EVM.hs:(2824,1)-(2830,30) 5042 2 0.0 0.0 0.0 0.0 + ceilDiv EVM src/EVM.hs:2835:1-31 5043 2 0.0 0.0 0.0 0.0 + ceilDiv EVM src/EVM.hs:2835:1-31 5041 1 0.0 0.0 0.0 0.0 + createAddress EVM.Concrete src/EVM/Concrete.hs:108:1-72 5052 1 0.0 0.0 0.0 0.0 + num EVM.Types src/EVM/Types.hs:492:1-18 5053 1 0.0 0.0 0.0 0.0 + rlpList EVM.RLP src/EVM/RLP.hs:63:1-30 5061 1 0.0 0.0 0.0 0.0 + rlpencode EVM.RLP src/EVM/RLP.hs:(50,1)-(52,70) 5062 3 0.0 0.0 0.0 0.0 + encodeLen EVM.RLP src/EVM/RLP.hs:(55,1)-(60,44) 5066 2 0.0 0.0 0.0 0.0 + num EVM.Types src/EVM/Types.hs:492:1-18 5067 2 0.0 0.0 0.0 0.0 + rlpWord256 EVM.RLP src/EVM/RLP.hs:(78,1)-(79,28) 5069 1 0.0 0.0 0.0 0.0 + octets EVM.RLP src/EVM/RLP.hs:(66,1)-(67,85) 5070 1 0.0 0.0 0.0 0.0 + keccak EVM.Types src/EVM/Types.hs:(580,1)-(583,12) 5054 0 0.0 0.0 0.0 0.0 + keccakBytes EVM.Types src/EVM/Types.hs:(570,1)-(573,15) 5056 0 0.0 0.0 0.0 0.0 + hash Crypto.Hash Crypto/Hash.hs:58:1-47 5057 1 0.0 0.0 0.0 0.0 + hashFinalize Crypto.Hash Crypto/Hash.hs:(92,1)-(95,17) 5058 1 0.0 0.0 0.0 0.0 + allocAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:74:1-45 5076 1 0.0 0.0 0.0 0.0 + new Basement.Block.Base Basement/Block/Base.hs:304:1-76 5077 1 0.0 0.0 0.0 0.0 + unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 5078 1 0.0 0.0 0.0 0.0 + withMutablePtrHint Basement.Block.Base Basement/Block/Base.hs:(475,1)-(489,39) 5079 1 0.0 0.0 0.0 0.0 + copy Data.ByteArray.Methods Data/ByteArray/Methods.hs:(223,1)-(226,21) 5084 1 0.0 0.0 0.0 0.0 + isMutablePinned Basement.Block.Base Basement/Block/Base.hs:100:1-90 5080 1 0.0 0.0 0.0 0.0 + compatIsMutableByteArrayPinned# Basement.Compat.Primitive Basement/Compat/Primitive.hs:70:1-65 5081 1 0.0 0.0 0.0 0.0 + toPinnedStatus# Basement.Compat.Primitive Basement/Compat/Primitive.hs:(47,1)-(48,27) 5082 1 0.0 0.0 0.0 0.0 + unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 5083 1 0.0 0.0 0.0 0.0 + hashInit Crypto.Hash Crypto/Hash.hs:(66,1)-(67,24) 5074 1 0.0 0.0 0.0 0.0 + allocAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:74:1-45 5075 1 0.0 0.0 0.0 0.0 + hashUpdate Crypto.Hash Crypto/Hash.hs:(71,1)-(73,37) 5059 1 0.0 0.0 0.0 0.0 + hashUpdates Crypto.Hash Crypto/Hash.hs:(81,1)-(86,32) 5071 1 0.0 0.0 0.0 0.0 + copyAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:(237,1)-(240,21) 5073 1 0.0 0.0 0.0 0.0 + null Data.ByteArray.Methods Data/ByteArray/Methods.hs:92:1-22 5072 1 0.0 0.0 0.0 0.0 + null Data.ByteArray.Methods Data/ByteArray/Methods.hs:92:1-22 5060 1 0.0 0.0 0.0 0.0 + unpack Data.ByteArray.Methods Data/ByteArray/Methods.hs:(104,1)-(110,34) 5085 1 0.0 0.0 0.0 0.0 + unsafeCast Basement.Block Basement/Block.hs:421:1-32 5086 33 0.0 0.0 0.0 0.0 + withPtr Basement.Block.Base Basement/Block/Base.hs:(402,1)-(411,31) 5087 32 0.0 0.0 0.0 0.0 + isPinned Basement.Block.Base Basement/Block/Base.hs:97:1-67 5088 32 0.0 0.0 0.0 0.0 + compatIsByteArrayPinned# Basement.Compat.Primitive Basement/Compat/Primitive.hs:67:1-51 5089 32 0.0 0.0 0.0 0.0 + toPinnedStatus# Basement.Compat.Primitive Basement/Compat/Primitive.hs:(47,1)-(48,27) 5090 32 0.0 0.0 0.0 0.0 + unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 5091 32 0.0 0.0 0.0 0.0 + word EVM.Types src/EVM/Types.hs:521:1-21 5055 0 0.0 0.0 0.0 0.0 + word256 EVM.Types src/EVM/Types.hs:(510,1)-(518,67) 5092 1 0.0 0.0 0.0 0.0 + padLeft EVM.Types src/EVM/Types.hs:495:1-54 5093 1 0.0 0.0 0.0 0.0 + bytesRead Data.Serialize.Get src/Data/Serialize/Get.hs:838:1-45 5094 0 0.0 0.0 0.0 0.0 + rlpAddrFull EVM.RLP src/EVM/RLP.hs:85:1-38 5063 0 0.0 0.0 0.0 0.0 + octetsFull EVM.RLP src/EVM/RLP.hs:(70,1)-(71,67) 5064 1 0.0 0.0 0.0 0.0 + num EVM.Types src/EVM/Types.hs:492:1-18 5065 0 0.0 0.0 0.0 0.0 + readMemory EVM src/EVM.hs:2412:1-92 5115 1 0.0 0.0 0.0 0.0 + num EVM.Types src/EVM/Types.hs:492:1-18 5120 2 0.0 0.0 0.0 0.0 + sliceWithZero EVM.Symbolic src/EVM/Symbolic.hs:(169,1)-(170,103) 5116 1 0.0 0.0 0.0 0.0 + byteStringSliceWithDefaultZeroes EVM.Concrete src/EVM/Concrete.hs:(27,1)-(35,51) 5122 1 0.0 0.0 0.0 0.0 + wordValue EVM.Concrete src/EVM/Concrete.hs:39:1-21 5068 1 0.0 0.0 0.0 0.0 + create EVM src/EVM.hs:(2123,1)-(2184,30) 5109 0 0.0 0.0 0.0 0.0 + next EVM src/EVM.hs:543:1-46 5110 1 0.0 0.0 0.0 0.0 + opSize EVM src/EVM.hs:(2542,1)-(2543,37) 5114 1 0.0 0.0 0.0 0.0 + next EVM src/EVM.hs:543:1-46 4613 0 0.0 0.0 0.0 0.0 + writeStorage EVM src/EVM.hs:(1666,1)-(1667,78) 4634 0 0.0 0.0 0.0 0.0 + forceLit EVM.Symbolic src/EVM/Symbolic.hs:(40,1)-(42,49) 4635 3 0.0 0.0 0.0 0.0 + genFromCV Data.SBV.Core.Model Data/SBV/Core/Model.hs:(103,1)-(104,95) 4636 3 0.0 0.0 0.0 0.0 + svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 4637 3 0.0 0.0 0.0 0.0 + svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 4638 3 0.0 0.0 0.0 0.0 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 4639 3 0.0 0.0 0.0 0.0 + accessStorage EVM src/EVM.hs:(1674,1)-(1702,35) 4509 3 0.0 0.0 0.0 0.0 + accessStorageForGas EVM src/EVM.hs:(1919,1)-(1927,21) 4504 3 0.0 0.0 0.0 0.0 + maybeLitWord EVM.Types src/EVM/Types.hs:324:1-68 4505 3 0.0 0.0 0.0 0.0 + genFromCV Data.SBV.Core.Model Data/SBV/Core/Model.hs:(103,1)-(104,95) 4552 3 0.0 0.0 0.0 0.0 + svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 4553 3 0.0 0.0 0.0 0.0 + svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 4554 3 0.0 0.0 0.0 0.0 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 4555 3 0.0 0.0 0.0 0.0 + wordValue EVM.Concrete src/EVM/Concrete.hs:39:1-21 4551 3 0.0 0.0 0.0 0.0 + forceConcrete3 EVM src/EVM.hs:(1856,1)-(1858,36) 4643 3 0.0 0.0 0.0 0.0 + maybeLitWord EVM.Types src/EVM/Types.hs:324:1-68 4644 9 0.0 0.0 0.0 0.0 + genFromCV Data.SBV.Core.Model Data/SBV/Core/Model.hs:(103,1)-(104,95) 4646 9 0.0 0.0 0.0 0.0 + svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 4647 9 0.0 0.0 0.0 0.0 + svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 4648 9 0.0 0.0 0.0 0.0 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 4649 9 0.0 0.0 0.0 0.0 + burn EVM src/EVM.hs:(1826,1)-(1838,38) 4651 6 0.0 0.0 0.0 0.0 + num EVM.Types src/EVM/Types.hs:492:1-18 4652 6 0.0 0.0 0.0 0.0 + accessUnboundedMemoryRange EVM src/EVM.hs:(2368,1)-(2375,14) 4654 0 0.0 0.0 0.0 0.0 + memoryCost EVM src/EVM.hs:(2824,1)-(2830,30) 4658 6 0.0 0.0 0.0 0.0 + ceilDiv EVM src/EVM.hs:2835:1-31 4659 6 0.0 0.0 0.0 0.0 + ceilDiv EVM src/EVM.hs:2835:1-31 4657 3 0.0 0.0 0.0 0.0 + num EVM.Types src/EVM/Types.hs:492:1-18 4655 3 0.0 0.0 0.0 0.0 + copyBytesToMemory EVM src/EVM.hs:(2395,1)-(2400,45) 4662 0 0.0 0.0 0.0 0.0 + writeMemory EVM.Symbolic src/EVM/Symbolic.hs:(173,1)-(180,49) 4663 3 0.0 0.0 0.0 0.0 + writeMemory EVM.Concrete src/EVM/Concrete.hs:(46,1)-(59,22) 4686 3 0.0 0.0 0.0 0.0 + num EVM.Types src/EVM/Types.hs:492:1-18 4703 12 0.0 0.0 0.0 0.0 + sliceMemory EVM.Concrete src/EVM/Concrete.hs:(42,1)-(43,50) 4704 3 0.0 0.0 0.0 0.0 + num EVM.Types src/EVM/Types.hs:492:1-18 4705 6 0.0 0.0 0.0 0.0 + byteStringSliceWithDefaultZeroes EVM.Concrete src/EVM/Concrete.hs:(27,1)-(35,51) 4706 3 0.0 0.0 0.0 0.0 + accessUnboundedMemoryRange EVM src/EVM.hs:(2368,1)-(2375,14) 4653 3 0.0 0.0 0.0 0.0 + num EVM.Types src/EVM/Types.hs:492:1-18 4656 6 0.0 0.0 0.0 0.0 + ceilDiv EVM src/EVM.hs:2835:1-31 4650 3 0.0 0.0 0.0 0.0 + copyBytesToMemory EVM src/EVM.hs:(2395,1)-(2400,45) 4660 3 0.0 0.0 0.0 0.0 + num EVM.Types src/EVM/Types.hs:492:1-18 4645 3 0.0 0.0 0.0 0.0 + forceConcrete2 EVM src/EVM.hs:(1851,1)-(1853,36) 4664 2 0.0 0.0 0.1 0.1 + maybeLitWord EVM.Types src/EVM/Types.hs:324:1-68 4665 4 0.0 0.0 0.0 0.0 + genFromCV Data.SBV.Core.Model Data/SBV/Core/Model.hs:(103,1)-(104,95) 4666 4 0.0 0.0 0.0 0.0 + svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 4667 4 0.0 0.0 0.0 0.0 + svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 4668 4 0.0 0.0 0.0 0.0 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 4669 4 0.0 0.0 0.0 0.0 + num EVM.Types src/EVM/Types.hs:492:1-18 4679 4 0.0 0.0 0.0 0.0 + accessMemoryRange EVM src/EVM.hs:(2383,1)-(2387,53) 4670 2 0.0 0.0 0.1 0.1 + accessUnboundedMemoryRange EVM src/EVM.hs:(2368,1)-(2375,14) 4671 2 0.0 0.0 0.1 0.1 + num EVM.Types src/EVM/Types.hs:492:1-18 4672 6 0.0 0.0 0.0 0.0 + memoryCost EVM src/EVM.hs:(2824,1)-(2830,30) 4674 4 0.0 0.0 0.0 0.0 + ceilDiv EVM src/EVM.hs:2835:1-31 4675 4 0.0 0.0 0.0 0.0 + burn EVM src/EVM.hs:(1826,1)-(1838,38) 4676 2 0.0 0.0 0.1 0.1 + num EVM.Types src/EVM/Types.hs:492:1-18 4677 2 0.0 0.0 0.0 0.0 + finishFrame EVM src/EVM.hs:(2237,1)-(2357,20) 4711 0 0.0 0.0 0.1 0.1 + insertTrace EVM src/EVM.hs:(2444,1)-(2447,60) 5193 1 0.0 0.0 0.0 0.0 + insert Data.Tree.Zipper Data/Tree/Zipper.hs:275:1-37 5198 1 0.0 0.0 0.0 0.0 + nextSpace Data.Tree.Zipper Data/Tree/Zipper.hs:153:1-69 5197 1 0.0 0.0 0.0 0.0 + withTraceLocation EVM src/EVM.hs:(2426,1)-(2435,5) 5194 1 0.0 0.0 0.0 0.0 + num EVM.Types src/EVM/Types.hs:492:1-18 5214 1 0.0 0.0 0.0 0.0 + replaceCode EVM src/EVM.hs:(2189,1)-(2202,74) 5195 1 0.0 0.0 0.0 0.0 + initialContract EVM src/EVM.hs:(516,1)-(533,39) 5243 1 0.0 0.0 0.0 0.0 + mkCodeOps EVM src/EVM.hs:(2721,1)-(2739,79) 5278 1 0.0 0.0 0.0 0.0 + marray# Data.Primitive.Array Data/Primitive/Array.hs:92:5-11 5285 1824 0.0 0.0 0.0 0.0 + unId Data.Vector.Fusion.Util Data/Vector/Fusion/Util.hs:25:21-24 5284 1824 0.0 0.0 0.0 0.0 + opSize EVM src/EVM.hs:(2542,1)-(2543,37) 5282 1823 0.0 0.0 0.0 0.0 + num EVM.Types src/EVM/Types.hs:492:1-18 5283 481 0.0 0.0 0.0 0.0 + readOp EVM src/EVM.hs:(2636,1)-(2718,21) 6106 66 0.0 0.0 0.0 0.0 + sChunks Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:122:30-36 5281 1 0.0 0.0 0.0 0.0 + sSize Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:124:30-34 5280 1 0.0 0.0 0.0 0.0 + upperBound Data.Vector.Fusion.Bundle.Size Data/Vector/Fusion/Bundle/Size.hs:(126,1)-(128,30) 5279 1 0.0 0.0 0.0 0.0 + mkOpIxMap EVM src/EVM.hs:(2549,1)-(2586,83) 5276 1 0.0 0.0 0.0 0.0 + len EVM.Symbolic src/EVM/Symbolic.hs:(161,1)-(162,38) 5277 1 0.0 0.0 0.0 0.0 + stripBytecodeMetadata EVM.Solidity src/EVM/Solidity.hs:(569,1)-(573,22) 5251 1 0.0 0.0 0.0 0.0 + keccak EVM.Types src/EVM/Types.hs:(580,1)-(583,12) 5244 0 0.0 0.0 0.0 0.0 + keccakBytes EVM.Types src/EVM/Types.hs:(570,1)-(573,15) 5246 0 0.0 0.0 0.0 0.0 + hash Crypto.Hash Crypto/Hash.hs:58:1-47 5247 1 0.0 0.0 0.0 0.0 + hashFinalize Crypto.Hash Crypto/Hash.hs:(92,1)-(95,17) 5248 1 0.0 0.0 0.0 0.0 + allocAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:74:1-45 5257 1 0.0 0.0 0.0 0.0 + new Basement.Block.Base Basement/Block/Base.hs:304:1-76 5258 1 0.0 0.0 0.0 0.0 + unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 5259 1 0.0 0.0 0.0 0.0 + withMutablePtrHint Basement.Block.Base Basement/Block/Base.hs:(475,1)-(489,39) 5260 1 0.0 0.0 0.0 0.0 + copy Data.ByteArray.Methods Data/ByteArray/Methods.hs:(223,1)-(226,21) 5265 1 0.0 0.0 0.0 0.0 + isMutablePinned Basement.Block.Base Basement/Block/Base.hs:100:1-90 5261 1 0.0 0.0 0.0 0.0 + compatIsMutableByteArrayPinned# Basement.Compat.Primitive Basement/Compat/Primitive.hs:70:1-65 5262 1 0.0 0.0 0.0 0.0 + toPinnedStatus# Basement.Compat.Primitive Basement/Compat/Primitive.hs:(47,1)-(48,27) 5263 1 0.0 0.0 0.0 0.0 + unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 5264 1 0.0 0.0 0.0 0.0 + hashInit Crypto.Hash Crypto/Hash.hs:(66,1)-(67,24) 5255 1 0.0 0.0 0.0 0.0 + allocAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:74:1-45 5256 1 0.0 0.0 0.0 0.0 + hashUpdate Crypto.Hash Crypto/Hash.hs:(71,1)-(73,37) 5249 1 0.0 0.0 0.0 0.0 + hashUpdates Crypto.Hash Crypto/Hash.hs:(81,1)-(86,32) 5252 1 0.0 0.0 0.0 0.0 + copyAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:(237,1)-(240,21) 5254 1 0.0 0.0 0.0 0.0 + null Data.ByteArray.Methods Data/ByteArray/Methods.hs:92:1-22 5253 1 0.0 0.0 0.0 0.0 + null Data.ByteArray.Methods Data/ByteArray/Methods.hs:92:1-22 5250 1 0.0 0.0 0.0 0.0 + unpack Data.ByteArray.Methods Data/ByteArray/Methods.hs:(104,1)-(110,34) 5266 1 0.0 0.0 0.0 0.0 + unsafeCast Basement.Block Basement/Block.hs:421:1-32 5267 33 0.0 0.0 0.0 0.0 + withPtr Basement.Block.Base Basement/Block/Base.hs:(402,1)-(411,31) 5268 32 0.0 0.0 0.0 0.0 + isPinned Basement.Block.Base Basement/Block/Base.hs:97:1-67 5269 32 0.0 0.0 0.0 0.0 + compatIsByteArrayPinned# Basement.Compat.Primitive Basement/Compat/Primitive.hs:67:1-51 5270 32 0.0 0.0 0.0 0.0 + toPinnedStatus# Basement.Compat.Primitive Basement/Compat/Primitive.hs:(47,1)-(48,27) 5271 32 0.0 0.0 0.0 0.0 + unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 5272 32 0.0 0.0 0.0 0.0 + word EVM.Types src/EVM/Types.hs:521:1-21 5245 0 0.0 0.0 0.0 0.0 + word256 EVM.Types src/EVM/Types.hs:(510,1)-(518,67) 5273 1 0.0 0.0 0.0 0.0 + padLeft EVM.Types src/EVM/Types.hs:495:1-54 5274 1 0.0 0.0 0.0 0.0 + bytesRead Data.Serialize.Get src/Data/Serialize/Get.hs:838:1-45 5275 0 0.0 0.0 0.0 0.0 + finalize EVM src/EVM.hs:(1721,1)-(1790,66) 4713 0 0.0 0.0 0.1 0.1 + accountEmpty EVM src/EVM.hs:(1712,1)-(1717,26) 4797 2 0.0 0.0 0.0 0.0 + len EVM.Symbolic src/EVM/Symbolic.hs:(161,1)-(162,38) 4798 2 0.0 0.0 0.0 0.0 + num EVM.Types src/EVM/Types.hs:492:1-18 4758 2 0.0 0.0 0.0 0.0 + r_block EVM.FeeSchedule src/EVM/FeeSchedule.hs:47:5-11 4801 1 0.0 0.0 0.0 0.0 + replaceCode EVM src/EVM.hs:(2189,1)-(2202,74) 4714 1 0.0 0.0 0.1 0.1 + initialContract EVM src/EVM.hs:(516,1)-(533,39) 4844 1 0.0 0.0 0.1 0.1 + mkCodeOps EVM src/EVM.hs:(2721,1)-(2739,79) 4879 1 0.0 0.1 0.0 0.1 + marray# Data.Primitive.Array Data/Primitive/Array.hs:92:5-11 4886 4303 0.0 0.0 0.0 0.0 + unId Data.Vector.Fusion.Util Data/Vector/Fusion/Util.hs:25:21-24 4885 4303 0.0 0.0 0.0 0.0 + opSize EVM src/EVM.hs:(2542,1)-(2543,37) 4883 4302 0.0 0.0 0.0 0.0 + num EVM.Types src/EVM/Types.hs:492:1-18 4884 1124 0.0 0.0 0.0 0.0 + readOp EVM src/EVM.hs:(2636,1)-(2718,21) 4911 138 0.0 0.0 0.0 0.0 + sChunks Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:122:30-36 4882 1 0.0 0.0 0.0 0.0 + sSize Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:124:30-34 4881 1 0.0 0.0 0.0 0.0 + upperBound Data.Vector.Fusion.Bundle.Size Data/Vector/Fusion/Bundle/Size.hs:(126,1)-(128,30) 4880 1 0.0 0.0 0.0 0.0 + mkOpIxMap EVM src/EVM.hs:(2549,1)-(2586,83) 4877 1 0.1 0.0 0.1 0.0 + len EVM.Symbolic src/EVM/Symbolic.hs:(161,1)-(162,38) 4878 1 0.0 0.0 0.0 0.0 + stripBytecodeMetadata EVM.Solidity src/EVM/Solidity.hs:(569,1)-(573,22) 4852 1 0.0 0.0 0.0 0.0 + keccak EVM.Types src/EVM/Types.hs:(580,1)-(583,12) 4845 0 0.0 0.0 0.0 0.0 + keccakBytes EVM.Types src/EVM/Types.hs:(570,1)-(573,15) 4847 0 0.0 0.0 0.0 0.0 + hash Crypto.Hash Crypto/Hash.hs:58:1-47 4848 1 0.0 0.0 0.0 0.0 + hashFinalize Crypto.Hash Crypto/Hash.hs:(92,1)-(95,17) 4849 1 0.0 0.0 0.0 0.0 + allocAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:74:1-45 4858 1 0.0 0.0 0.0 0.0 + new Basement.Block.Base Basement/Block/Base.hs:304:1-76 4859 1 0.0 0.0 0.0 0.0 + unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 4860 1 0.0 0.0 0.0 0.0 + withMutablePtrHint Basement.Block.Base Basement/Block/Base.hs:(475,1)-(489,39) 4861 1 0.0 0.0 0.0 0.0 + copy Data.ByteArray.Methods Data/ByteArray/Methods.hs:(223,1)-(226,21) 4866 1 0.0 0.0 0.0 0.0 + isMutablePinned Basement.Block.Base Basement/Block/Base.hs:100:1-90 4862 1 0.0 0.0 0.0 0.0 + compatIsMutableByteArrayPinned# Basement.Compat.Primitive Basement/Compat/Primitive.hs:70:1-65 4863 1 0.0 0.0 0.0 0.0 + toPinnedStatus# Basement.Compat.Primitive Basement/Compat/Primitive.hs:(47,1)-(48,27) 4864 1 0.0 0.0 0.0 0.0 + unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 4865 1 0.0 0.0 0.0 0.0 + hashInit Crypto.Hash Crypto/Hash.hs:(66,1)-(67,24) 4856 1 0.0 0.0 0.0 0.0 + allocAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:74:1-45 4857 1 0.0 0.0 0.0 0.0 + hashUpdate Crypto.Hash Crypto/Hash.hs:(71,1)-(73,37) 4850 1 0.0 0.0 0.0 0.0 + hashUpdates Crypto.Hash Crypto/Hash.hs:(81,1)-(86,32) 4853 1 0.0 0.0 0.0 0.0 + copyAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:(237,1)-(240,21) 4855 1 0.0 0.0 0.0 0.0 + null Data.ByteArray.Methods Data/ByteArray/Methods.hs:92:1-22 4854 1 0.0 0.0 0.0 0.0 + null Data.ByteArray.Methods Data/ByteArray/Methods.hs:92:1-22 4851 1 0.0 0.0 0.0 0.0 + unpack Data.ByteArray.Methods Data/ByteArray/Methods.hs:(104,1)-(110,34) 4867 1 0.0 0.0 0.0 0.0 + unsafeCast Basement.Block Basement/Block.hs:421:1-32 4868 33 0.0 0.0 0.0 0.0 + withPtr Basement.Block.Base Basement/Block/Base.hs:(402,1)-(411,31) 4869 32 0.0 0.0 0.0 0.0 + isPinned Basement.Block.Base Basement/Block/Base.hs:97:1-67 4870 32 0.0 0.0 0.0 0.0 + compatIsByteArrayPinned# Basement.Compat.Primitive Basement/Compat/Primitive.hs:67:1-51 4871 32 0.0 0.0 0.0 0.0 + toPinnedStatus# Basement.Compat.Primitive Basement/Compat/Primitive.hs:(47,1)-(48,27) 4872 32 0.0 0.0 0.0 0.0 + unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 4873 32 0.0 0.0 0.0 0.0 + word EVM.Types src/EVM/Types.hs:521:1-21 4846 0 0.0 0.0 0.0 0.0 + word256 EVM.Types src/EVM/Types.hs:(510,1)-(518,67) 4874 1 0.0 0.0 0.0 0.0 + padLeft EVM.Types src/EVM/Types.hs:495:1-54 4875 1 0.0 0.0 0.0 0.0 + bytesRead Data.Serialize.Get src/Data/Serialize/Get.hs:838:1-45 4876 0 0.0 0.0 0.0 0.0 + w256 EVM.Types src/EVM/Types.hs:90:1-24 4756 1 0.0 0.0 0.0 0.0 + touchAccount EVM src/EVM.hs:1895:1-57 4716 0 0.0 0.0 0.0 0.0 + pushTo EVM src/EVM.hs:1582:1-23 4717 1 0.0 0.0 0.0 0.0 + popTrace EVM src/EVM.hs:(2450,1)-(2454,42) 5196 0 0.0 0.0 0.0 0.0 + nextSpace Data.Tree.Zipper Data/Tree/Zipper.hs:153:1-69 5201 1 0.0 0.0 0.0 0.0 + parent Data.Tree.Zipper Data/Tree/Zipper.hs:(124,1)-(132,17) 5199 1 0.0 0.0 0.0 0.0 + parents Data.Tree.Zipper Data/Tree/Zipper.hs:71:1-26 5200 1 0.0 0.0 0.0 0.0 + push EVM src/EVM.hs:2474:1-30 5204 0 0.0 0.0 0.0 0.0 + pushSym EVM src/EVM.hs:2477:1-34 5205 1 0.0 0.0 0.0 0.0 + w256lit EVM.Types src/EVM/Types.hs:346:1-48 5206 1 0.0 0.0 0.0 0.0 + genLiteral Data.SBV.Core.Model Data/SBV/Core/Model.hs:99:1-48 5207 1 0.0 0.0 0.0 0.0 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 5208 1 0.0 0.0 0.0 0.0 + svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 5209 1 0.0 0.0 0.0 0.0 + svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 5210 1 0.0 0.0 0.0 0.0 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 5211 1 0.0 0.0 0.0 0.0 + num EVM.Types src/EVM/Types.hs:492:1-18 5213 0 0.0 0.0 0.0 0.0 + ceilDiv EVM src/EVM.hs:2835:1-31 4673 2 0.0 0.0 0.0 0.0 + burn EVM src/EVM.hs:(1826,1)-(1838,38) 4708 2 0.0 0.0 0.0 0.0 + num EVM.Types src/EVM/Types.hs:492:1-18 4709 2 0.0 0.0 0.0 0.0 + finishFrame EVM src/EVM.hs:(2237,1)-(2357,20) 4710 2 0.0 0.0 0.0 0.0 + len EVM.Symbolic src/EVM/Symbolic.hs:(161,1)-(162,38) 4680 2 0.0 0.0 0.0 0.0 + readMemory EVM src/EVM.hs:2412:1-92 4681 2 0.0 0.0 0.0 0.0 + num EVM.Types src/EVM/Types.hs:492:1-18 4684 4 0.0 0.0 0.0 0.0 + sliceWithZero EVM.Symbolic src/EVM/Symbolic.hs:(169,1)-(170,103) 4683 2 0.0 0.0 0.0 0.0 + byteStringSliceWithDefaultZeroes EVM.Concrete src/EVM/Concrete.hs:(27,1)-(35,51) 4685 2 0.0 0.0 0.0 0.0 + finishFrame EVM src/EVM.hs:(2237,1)-(2357,20) 5236 0 0.0 0.0 0.0 0.0 + finalize EVM src/EVM.hs:(1721,1)-(1790,66) 5237 0 0.0 0.0 0.0 0.0 + accountEmpty EVM src/EVM.hs:(1712,1)-(1717,26) 5286 4 0.0 0.0 0.0 0.0 + len EVM.Symbolic src/EVM/Symbolic.hs:(161,1)-(162,38) 5287 4 0.0 0.0 0.0 0.0 + num EVM.Types src/EVM/Types.hs:492:1-18 5241 2 0.0 0.0 0.0 0.0 + noop EVM src/EVM.hs:1579:1-14 5242 1 0.0 0.0 0.0 0.0 + r_block EVM.FeeSchedule src/EVM/FeeSchedule.hs:47:5-11 5288 1 0.0 0.0 0.0 0.0 + w256 EVM.Types src/EVM/Types.hs:90:1-24 5240 1 0.0 0.0 0.0 0.0 + touchAccount EVM src/EVM.hs:1895:1-57 5238 0 0.0 0.0 0.0 0.0 + pushTo EVM src/EVM.hs:1582:1-23 5239 1 0.0 0.0 0.0 0.0 + word EVM.Types src/EVM/Types.hs:521:1-21 4464 0 0.0 0.0 0.0 0.0 + word256 EVM.Types src/EVM/Types.hs:(510,1)-(518,67) 4466 46 0.0 0.0 0.0 0.0 + padLeft EVM.Types src/EVM/Types.hs:495:1-54 4467 46 0.0 0.0 0.0 0.0 + bytesRead Data.Serialize.Get src/Data/Serialize/Get.hs:838:1-45 4468 0 0.0 0.0 0.0 0.0 + initializeUnitTest EVM.UnitTest src/EVM/UnitTest.hs:(142,1)-(172,17) 4286 0 0.0 0.0 0.0 0.0 + abiCall EVM.UnitTest src/EVM/UnitTest.hs:(842,1)-(845,53) 4835 0 0.0 0.0 0.0 0.0 + makeTxCall EVM.UnitTest src/EVM/UnitTest.hs:(848,1)-(859,17) 4836 0 0.0 0.0 0.0 0.0 + w256 EVM.Types src/EVM/Types.hs:90:1-24 4893 2 0.0 0.0 0.0 0.0 + initTx EVM.Transaction src/EVM/Transaction.hs:(182,1)-(205,47) 4897 1 0.0 0.0 0.0 0.0 + forceLit EVM.Symbolic src/EVM/Symbolic.hs:(40,1)-(42,49) 4910 2 0.0 0.0 0.0 0.0 + genFromCV Data.SBV.Core.Model Data/SBV/Core/Model.hs:(103,1)-(104,95) 5098 2 0.0 0.0 0.0 0.0 + svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 5099 2 0.0 0.0 0.0 0.0 + svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 5100 2 0.0 0.0 0.0 0.0 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 5101 2 0.0 0.0 0.0 0.0 + maybeLitWord EVM.Types src/EVM/Types.hs:324:1-68 4902 1 0.0 0.0 0.0 0.0 + setupTx EVM.Transaction src/EVM/Transaction.hs:(171,1)-(176,38) 4899 1 0.0 0.0 0.0 0.0 + touchAccount EVM.Transaction src/EVM/Transaction.hs:164:1-57 4900 2 0.0 0.0 0.0 0.0 + touchAccount EVM.Transaction src/EVM/Transaction.hs:164:1-57 4901 1 0.0 0.0 0.0 0.0 + loadContract EVM src/EVM.hs:(1794,1)-(1806,44) 4839 0 0.0 0.0 0.0 0.0 + resetState EVM src/EVM.hs:(2210,1)-(2213,26) 4840 0 0.0 0.0 0.0 0.0 + popTrace EVM src/EVM.hs:(2450,1)-(2454,42) 4896 0 0.0 0.0 0.0 0.0 + nextSpace Data.Tree.Zipper Data/Tree/Zipper.hs:153:1-69 4905 1 0.0 0.0 0.0 0.0 + parent Data.Tree.Zipper Data/Tree/Zipper.hs:(124,1)-(132,17) 4903 1 0.0 0.0 0.0 0.0 + parents Data.Tree.Zipper Data/Tree/Zipper.hs:71:1-26 4904 1 0.0 0.0 0.0 0.0 + pushTrace EVM src/EVM.hs:(2438,1)-(2441,59) 4289 0 0.0 0.0 0.0 0.0 + children Data.Tree.Zipper Data/Tree/Zipper.hs:(166,1)-(172,7) 4426 2 0.0 0.0 0.0 0.0 + view Control.Monad.Operational src/Control/Monad/Operational.hs:138:1-26 4274 0 0.0 0.0 0.0 0.0 + viewT Control.Monad.Operational src/Control/Monad/Operational.hs:(239,1)-(243,54) 4275 13 0.0 0.0 0.0 0.0 + execFully EVM.Stepper src/EVM/Stepper.hs:(82,1)-(91,20) 4802 0 0.0 0.0 0.0 0.0 + initializeUnitTest EVM.UnitTest src/EVM/UnitTest.hs:(142,1)-(172,17) 4803 0 0.0 0.0 0.0 0.0 + evm EVM.Stepper src/EVM/Stepper.hs:78:1-21 5290 0 0.0 0.0 0.0 0.0 + popTrace EVM src/EVM.hs:(2450,1)-(2454,42) 5291 0 0.0 0.0 0.0 0.0 + nextSpace Data.Tree.Zipper Data/Tree/Zipper.hs:153:1-69 5296 1 0.0 0.0 0.0 0.0 + parent Data.Tree.Zipper Data/Tree/Zipper.hs:(124,1)-(132,17) 5292 1 0.0 0.0 0.0 0.0 + parents Data.Tree.Zipper Data/Tree/Zipper.hs:71:1-26 5293 1 0.0 0.0 0.0 0.0 + runTest EVM.UnitTest src/EVM/UnitTest.hs:(532,1)-(545,41) 5297 5 0.0 0.0 88.5 82.7 + fuzzRun EVM.UnitTest src/EVM/UnitTest.hs:(586,1)-(615,40) 5299 5 0.0 0.0 88.5 82.7 + fuzzTest EVM.UnitTest src/EVM/UnitTest.hs:(228,1)-(241,53) 5301 405 2.6 0.0 88.4 82.7 + interpretWithTraceId EVM.UnitTest src/EVM/UnitTest.hs:(256,1)-(279,78) 5310 2024 0.1 0.0 77.8 72.7 + execWithTraceId EVM.UnitTest src/EVM/UnitTest.hs:(282,1)-(283,51) 5336 0 0.0 0.0 76.4 71.8 + runWithTraceId EVM.UnitTest src/EVM/UnitTest.hs:(286,1)-(301,90) 5338 0 5.9 7.5 76.4 71.8 + currentContract EVM src/EVM.hs:(443,1)-(444,65) 5935 414891 1.8 0.6 1.8 0.6 + vmOpIx EVM src/EVM.hs:(2603,1)-(2605,57) 5936 414891 3.1 2.1 4.0 2.7 + unId Data.Vector.Fusion.Util Data/Vector/Fusion/Util.hs:25:21-24 5939 829782 0.0 0.0 0.0 0.0 + currentContract EVM src/EVM.hs:(443,1)-(444,65) 5937 414891 1.0 0.6 1.0 0.6 + exec1 EVM src/EVM.hs:(547,1)-(1323,42) 5345 0 18.8 14.4 64.7 61.1 + len EVM.Symbolic src/EVM/Symbolic.hs:(161,1)-(162,38) 5346 428143 0.1 0.3 0.1 0.3 + genFromCV Data.SBV.Core.Model Data/SBV/Core/Model.hs:(103,1)-(104,95) 5350 428142 0.1 0.0 0.1 0.0 + index EVM.Symbolic src/EVM/Symbolic.hs:(207,1)-(208,47) 5347 428142 0.6 2.0 3.5 3.9 + genLiteral Data.SBV.Core.Model Data/SBV/Core/Model.hs:99:1-48 5348 0 0.9 0.7 2.9 1.9 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 5349 428142 2.0 1.2 2.0 1.2 + num EVM.Types src/EVM/Types.hs:492:1-18 5351 218370 0.0 0.0 0.0 0.0 + burn EVM src/EVM.hs:(1826,1)-(1838,38) 5423 184668 3.6 6.7 8.2 10.7 + num EVM.Types src/EVM/Types.hs:492:1-18 5424 184668 1.1 1.1 1.1 1.1 + accessStorage EVM src/EVM.hs:(1674,1)-(1702,35) 5799 0 0.2 0.0 0.3 0.1 + readStorage EVM src/EVM.hs:(1662,1)-(1663,58) 5800 2266 0.0 0.0 0.1 0.1 + forceLit EVM.Symbolic src/EVM/Symbolic.hs:(40,1)-(42,49) 5801 2266 0.1 0.0 0.1 0.1 + genFromCV Data.SBV.Core.Model Data/SBV/Core/Model.hs:(103,1)-(104,95) 5802 2266 0.1 0.0 0.1 0.0 + svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 5803 2266 0.0 0.0 0.0 0.0 + svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 5804 2266 0.0 0.0 0.0 0.0 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 5805 2266 0.0 0.0 0.0 0.0 + writeStorage EVM src/EVM.hs:(1666,1)-(1667,78) 6187 496 0.0 0.0 0.0 0.0 + forceLit EVM.Symbolic src/EVM/Symbolic.hs:(40,1)-(42,49) 6188 496 0.0 0.0 0.0 0.0 + genFromCV Data.SBV.Core.Model Data/SBV/Core/Model.hs:(103,1)-(104,95) 6189 496 0.0 0.0 0.0 0.0 + svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 6190 496 0.0 0.0 0.0 0.0 + svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 6191 496 0.0 0.0 0.0 0.0 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 6192 496 0.0 0.0 0.0 0.0 + forceConcrete EVM src/EVM.hs:(1846,1)-(1848,22) 5666 0 0.0 0.0 3.1 1.7 + checkJump EVM src/EVM.hs:(2526,1)-(2539,35) 5667 0 1.9 0.9 3.1 1.7 + unId Data.Vector.Fusion.Util Data/Vector/Fusion/Util.hs:25:21-24 5674 139936 0.0 0.0 0.0 0.0 + num EVM.Types src/EVM/Types.hs:492:1-18 5668 69968 0.7 0.5 0.7 0.5 + array# Data.Primitive.Array Data/Primitive/Array.hs:87:5-10 5675 34984 0.0 0.0 0.0 0.0 + genFromCV Data.SBV.Core.Model Data/SBV/Core/Model.hs:(103,1)-(104,95) 5673 34984 0.1 0.0 0.1 0.0 + index EVM.Symbolic src/EVM/Symbolic.hs:(207,1)-(208,47) 5670 34984 0.1 0.2 0.5 0.3 + genLiteral Data.SBV.Core.Model Data/SBV/Core/Model.hs:99:1-48 5671 0 0.1 0.1 0.4 0.2 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 5672 34984 0.3 0.1 0.3 0.1 + len EVM.Symbolic src/EVM/Symbolic.hs:(161,1)-(162,38) 5669 34984 0.0 0.0 0.0 0.0 + next EVM src/EVM.hs:543:1-46 5426 0 0.2 1.1 0.2 1.1 + limitStack EVM src/EVM.hs:(1809,1)-(1813,17) 5353 169111 3.4 0.8 8.7 10.5 + burn EVM src/EVM.hs:(1826,1)-(1838,38) 5354 169111 2.6 4.7 5.0 9.3 + num EVM.Types src/EVM/Types.hs:492:1-18 5355 169111 1.6 1.0 1.6 1.0 + next EVM src/EVM.hs:543:1-46 5357 0 0.3 1.9 0.3 1.9 + push EVM src/EVM.hs:2474:1-30 6012 0 0.0 0.0 0.0 0.0 + pushSym EVM src/EVM.hs:2477:1-34 6013 0 0.0 0.0 0.0 0.0 + pushSym EVM src/EVM.hs:2477:1-34 5359 0 0.5 1.7 0.5 1.7 + pushSym EVM src/EVM.hs:2477:1-34 5358 168120 0.0 0.0 0.0 0.0 + next EVM src/EVM.hs:543:1-46 5356 164029 0.0 0.3 0.1 0.4 + opSize EVM src/EVM.hs:(2542,1)-(2543,37) 5360 164029 0.1 0.1 0.1 0.1 + num EVM.Types src/EVM/Types.hs:492:1-18 5361 103603 0.0 0.0 0.0 0.0 + num EVM.Types src/EVM/Types.hs:492:1-18 6081 1284 0.1 0.0 0.1 0.0 + len EVM.Symbolic src/EVM/Symbolic.hs:(161,1)-(162,38) 6315 350 0.0 0.0 0.0 0.0 + genFromCV Data.SBV.Core.Model Data/SBV/Core/Model.hs:(103,1)-(104,95) 6128 293 0.0 0.0 0.0 0.0 + svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 6129 293 0.0 0.0 0.0 0.0 + svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 6130 293 0.0 0.0 0.0 0.0 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 6131 293 0.0 0.0 0.0 0.0 + litWord EVM.Symbolic src/EVM/Symbolic.hs:24:1-52 6118 293 0.0 0.0 0.1 0.0 + genLiteral Data.SBV.Core.Model Data/SBV/Core/Model.hs:99:1-48 6119 293 0.0 0.0 0.1 0.0 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 6120 293 0.1 0.0 0.1 0.0 + svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 6121 293 0.0 0.0 0.0 0.0 + svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 6122 293 0.0 0.0 0.0 0.0 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 6123 293 0.0 0.0 0.0 0.0 + push EVM src/EVM.hs:2474:1-30 6010 0 0.0 0.0 0.1 0.0 + pushSym EVM src/EVM.hs:2477:1-34 6011 991 0.0 0.0 0.0 0.0 + w256lit EVM.Types src/EVM/Types.hs:346:1-48 6014 991 0.0 0.0 0.1 0.0 + genLiteral Data.SBV.Core.Model Data/SBV/Core/Model.hs:99:1-48 6015 991 0.0 0.0 0.0 0.0 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 6076 991 0.0 0.0 0.0 0.0 + svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 6077 991 0.0 0.0 0.0 0.0 + svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 6078 991 0.0 0.0 0.1 0.0 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 6079 991 0.1 0.0 0.1 0.0 + num EVM.Types src/EVM/Types.hs:492:1-18 6080 0 0.0 0.0 0.0 0.0 + w256lit EVM.Types src/EVM/Types.hs:346:1-48 5352 103603 1.0 0.5 4.1 3.0 + genLiteral Data.SBV.Core.Model Data/SBV/Core/Model.hs:99:1-48 5363 90338 0.4 0.4 1.6 1.4 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 5369 85334 1.2 1.0 1.2 1.0 + svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 5370 85334 0.0 0.0 0.0 0.0 + svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 5371 85334 0.2 0.1 1.6 1.1 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 5372 85334 1.3 1.0 1.3 1.0 + next EVM src/EVM.hs:543:1-46 5425 99148 0.1 0.7 0.1 0.7 + opSize EVM src/EVM.hs:(2542,1)-(2543,37) 5427 99148 0.0 0.0 0.0 0.0 + padRight EVM.Types src/EVM/Types.hs:498:1-55 5374 85334 0.1 0.1 0.1 0.1 + forceConcrete EVM src/EVM.hs:(1846,1)-(1848,22) 5362 59931 0.5 0.4 10.2 8.5 + maybeLitWord EVM.Types src/EVM/Types.hs:324:1-68 5364 74557 0.5 0.5 1.9 1.5 + genFromCV Data.SBV.Core.Model Data/SBV/Core/Model.hs:(103,1)-(104,95) 5378 69711 0.2 0.1 1.3 1.0 + svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 5379 69711 0.0 0.0 0.0 0.0 + svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 5380 69711 0.3 0.0 1.2 0.9 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 5381 69711 0.9 0.8 0.9 0.8 + checkJump EVM src/EVM.hs:(2526,1)-(2539,35) 5411 44764 0.0 0.0 0.2 0.2 + num EVM.Types src/EVM/Types.hs:492:1-18 5418 44764 0.2 0.2 0.2 0.2 + burn EVM src/EVM.hs:(1826,1)-(1838,38) 5365 34276 0.6 0.7 4.1 3.9 + num EVM.Types src/EVM/Types.hs:492:1-18 5366 34276 0.3 0.2 0.3 0.2 + accessMemoryRange EVM src/EVM.hs:(2383,1)-(2387,53) 6135 0 0.0 0.0 0.0 0.0 + accessUnboundedMemoryRange EVM src/EVM.hs:(2368,1)-(2375,14) 6136 0 0.0 0.0 0.0 0.0 + memoryCost EVM src/EVM.hs:(2824,1)-(2830,30) 6140 992 0.0 0.0 0.0 0.0 + ceilDiv EVM src/EVM.hs:2835:1-31 6141 992 0.0 0.0 0.0 0.0 + ceilDiv EVM src/EVM.hs:2835:1-31 6139 496 0.0 0.0 0.0 0.0 + next EVM src/EVM.hs:543:1-46 6146 496 0.0 0.0 0.0 0.0 + opSize EVM src/EVM.hs:(2542,1)-(2543,37) 6147 496 0.0 0.0 0.0 0.0 + num EVM.Types src/EVM/Types.hs:492:1-18 6137 496 0.0 0.0 0.0 0.0 + accessMemoryWord EVM src/EVM.hs:2391:1-53 5383 0 0.0 0.0 2.4 2.5 + accessMemoryRange EVM src/EVM.hs:(2383,1)-(2387,53) 5384 0 0.0 0.0 2.4 2.5 + accessUnboundedMemoryRange EVM src/EVM.hs:(2368,1)-(2375,14) 5385 0 0.3 0.4 2.4 2.5 + memoryCost EVM src/EVM.hs:(2824,1)-(2830,30) 5389 18658 0.1 0.0 0.1 0.1 + ceilDiv EVM src/EVM.hs:2835:1-31 5390 18658 0.0 0.0 0.0 0.0 + ceilDiv EVM src/EVM.hs:2835:1-31 5388 9329 0.2 0.0 0.2 0.0 + num EVM.Types src/EVM/Types.hs:492:1-18 5386 9329 0.0 0.0 0.0 0.0 + word256At EVM src/EVM.hs:(2418,1)-(2420,34) 5393 0 0.2 0.0 1.8 1.9 + setMemoryWord EVM.Symbolic src/EVM/Symbolic.hs:(191,1)-(194,61) 5394 5265 0.2 0.0 1.7 1.9 + maybeLitWord EVM.Types src/EVM/Types.hs:324:1-68 5395 5265 0.1 0.1 0.1 0.1 + genFromCV Data.SBV.Core.Model Data/SBV/Core/Model.hs:(103,1)-(104,95) 5825 5107 0.0 0.0 0.1 0.1 + svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 5826 5107 0.0 0.0 0.0 0.0 + svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 5827 5107 0.0 0.0 0.1 0.1 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 5828 5107 0.1 0.1 0.1 0.1 + setMemoryWord EVM.Concrete src/EVM/Concrete.hs:(82,1)-(83,43) 5818 5107 0.0 0.0 1.4 1.7 + num EVM.Types src/EVM/Types.hs:492:1-18 5820 5107 0.0 0.1 0.0 0.1 + word256Bytes EVM.Types src/EVM/Types.hs:537:1-59 5822 5107 0.1 0.6 1.0 1.5 + byteAt EVM.Types src/EVM/Types.hs:524:1-46 5823 163424 0.4 0.1 0.9 0.8 + num EVM.Types src/EVM/Types.hs:492:1-18 5824 163424 0.5 0.7 0.5 0.7 + writeMemory EVM.Concrete src/EVM/Concrete.hs:(46,1)-(59,22) 5819 5107 0.1 0.1 0.4 0.2 + num EVM.Types src/EVM/Types.hs:492:1-18 5821 20428 0.2 0.1 0.2 0.1 + sliceMemory EVM.Concrete src/EVM/Concrete.hs:(42,1)-(43,50) 5829 5107 0.1 0.0 0.1 0.1 + num EVM.Types src/EVM/Types.hs:492:1-18 5830 10214 0.1 0.0 0.1 0.0 + byteStringSliceWithDefaultZeroes EVM.Concrete src/EVM/Concrete.hs:(27,1)-(35,51) 5831 5107 0.0 0.0 0.0 0.0 + checkJump EVM src/EVM.hs:(2526,1)-(2539,35) 5412 0 0.5 0.2 0.8 0.5 + unId Data.Vector.Fusion.Util Data/Vector/Fusion/Util.hs:25:21-24 5421 39120 0.0 0.0 0.0 0.0 + num EVM.Types src/EVM/Types.hs:492:1-18 5413 19560 0.2 0.1 0.2 0.1 + array# Data.Primitive.Array Data/Primitive/Array.hs:87:5-10 5422 9780 0.0 0.0 0.0 0.0 + genFromCV Data.SBV.Core.Model Data/SBV/Core/Model.hs:(103,1)-(104,95) 5419 9780 0.0 0.0 0.0 0.0 + index EVM.Symbolic src/EVM/Symbolic.hs:(207,1)-(208,47) 5415 9780 0.1 0.0 0.1 0.1 + genLiteral Data.SBV.Core.Model Data/SBV/Core/Model.hs:99:1-48 5416 0 0.0 0.0 0.0 0.0 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 5417 9780 0.0 0.0 0.0 0.0 + len EVM.Symbolic src/EVM/Symbolic.hs:(161,1)-(162,38) 5414 9780 0.0 0.0 0.0 0.0 + num EVM.Types src/EVM/Types.hs:492:1-18 5814 9667 0.3 0.1 0.3 0.1 + accessMemoryWord EVM src/EVM.hs:2391:1-53 5367 9329 0.1 0.0 0.3 0.1 + accessMemoryRange EVM src/EVM.hs:(2383,1)-(2387,53) 5368 9329 0.0 0.0 0.3 0.1 + accessUnboundedMemoryRange EVM src/EVM.hs:(2368,1)-(2375,14) 5382 9329 0.2 0.0 0.3 0.1 + num EVM.Types src/EVM/Types.hs:492:1-18 5387 18658 0.1 0.1 0.1 0.1 + word256At EVM src/EVM.hs:(2418,1)-(2420,34) 5392 9329 0.3 0.1 1.9 1.0 + readMemoryWord EVM.Symbolic src/EVM/Symbolic.hs:(183,1)-(184,75) 5815 4064 0.0 0.0 1.6 1.0 + litWord EVM.Symbolic src/EVM/Symbolic.hs:24:1-52 5833 4064 0.2 0.0 0.3 0.1 + genLiteral Data.SBV.Core.Model Data/SBV/Core/Model.hs:99:1-48 5834 4064 0.1 0.0 0.1 0.1 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 5835 4064 0.1 0.0 0.1 0.0 + svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 5836 4064 0.0 0.0 0.0 0.0 + svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 5837 4064 0.0 0.0 0.0 0.1 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 5838 4064 0.0 0.0 0.0 0.0 + readMemoryWord EVM.Concrete src/EVM/Concrete.hs:(62,1)-(70,19) 5816 4064 0.6 0.0 1.3 0.8 + num EVM.Types src/EVM/Types.hs:492:1-18 5817 138176 0.7 0.8 0.7 0.8 + readByteOrZero EVM.Concrete src/EVM/Concrete.hs:24:1-46 5839 130048 0.0 0.0 0.0 0.0 + readMemoryWord EVM.Concrete src/EVM/Concrete.hs:70:5-19 5832 4064 0.0 0.0 0.0 0.0 + keccakBlob EVM.Concrete src/EVM/Concrete.hs:90:1-59 6144 992 0.0 0.0 0.9 1.1 + keccak EVM.Types src/EVM/Types.hs:(580,1)-(583,12) 6156 0 0.0 0.0 0.9 1.1 + keccakBytes EVM.Types src/EVM/Types.hs:(570,1)-(573,15) 6158 0 0.0 0.0 0.9 1.1 + hash Crypto.Hash Crypto/Hash.hs:58:1-47 6159 891 0.1 0.0 0.2 0.1 + hashFinalize Crypto.Hash Crypto/Hash.hs:(92,1)-(95,17) 6160 891 0.0 0.0 0.2 0.0 + allocAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:74:1-45 6168 891 0.0 0.0 0.2 0.0 + new Basement.Block.Base Basement/Block/Base.hs:304:1-76 6169 891 0.0 0.0 0.0 0.0 + unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 6170 891 0.0 0.0 0.0 0.0 + withMutablePtrHint Basement.Block.Base Basement/Block/Base.hs:(475,1)-(489,39) 6171 891 0.0 0.0 0.2 0.0 + copy Data.ByteArray.Methods Data/ByteArray/Methods.hs:(223,1)-(226,21) 6176 891 0.2 0.0 0.2 0.0 + isMutablePinned Basement.Block.Base Basement/Block/Base.hs:100:1-90 6172 891 0.0 0.0 0.0 0.0 + compatIsMutableByteArrayPinned# Basement.Compat.Primitive Basement/Compat/Primitive.hs:70:1-65 6173 891 0.0 0.0 0.0 0.0 + toPinnedStatus# Basement.Compat.Primitive Basement/Compat/Primitive.hs:(47,1)-(48,27) 6174 891 0.0 0.0 0.0 0.0 + unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 6175 891 0.0 0.0 0.0 0.0 + hashInit Crypto.Hash Crypto/Hash.hs:(66,1)-(67,24) 6166 891 0.0 0.0 0.0 0.0 + allocAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:74:1-45 6167 891 0.0 0.0 0.0 0.0 + hashUpdate Crypto.Hash Crypto/Hash.hs:(71,1)-(73,37) 6161 891 0.0 0.0 0.0 0.0 + hashUpdates Crypto.Hash Crypto/Hash.hs:(81,1)-(86,32) 6163 891 0.0 0.0 0.0 0.0 + copyAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:(237,1)-(240,21) 6165 891 0.0 0.0 0.0 0.0 + null Data.ByteArray.Methods Data/ByteArray/Methods.hs:92:1-22 6164 891 0.0 0.0 0.0 0.0 + null Data.ByteArray.Methods Data/ByteArray/Methods.hs:92:1-22 6162 891 0.0 0.0 0.0 0.0 + unpack Data.ByteArray.Methods Data/ByteArray/Methods.hs:(104,1)-(110,34) 6177 891 0.0 0.2 0.7 1.0 + unsafeCast Basement.Block Basement/Block.hs:421:1-32 6178 29403 0.0 0.0 0.0 0.0 + withPtr Basement.Block.Base Basement/Block/Base.hs:(402,1)-(411,31) 6179 28512 0.6 0.8 0.7 0.8 + isPinned Basement.Block.Base Basement/Block/Base.hs:97:1-67 6180 28512 0.1 0.0 0.1 0.0 + compatIsByteArrayPinned# Basement.Compat.Primitive Basement/Compat/Primitive.hs:67:1-51 6181 28512 0.0 0.0 0.0 0.0 + toPinnedStatus# Basement.Compat.Primitive Basement/Compat/Primitive.hs:(47,1)-(48,27) 6182 28512 0.0 0.0 0.0 0.0 + unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 6183 28512 0.1 0.1 0.1 0.1 + word EVM.Types src/EVM/Types.hs:521:1-21 6157 0 0.0 0.0 0.0 0.0 + word256 EVM.Types src/EVM/Types.hs:(510,1)-(518,67) 6184 891 0.0 0.0 0.0 0.0 + padLeft EVM.Types src/EVM/Types.hs:495:1-54 6185 891 0.0 0.0 0.0 0.0 + bytesRead Data.Serialize.Get src/Data/Serialize/Get.hs:838:1-45 6186 0 0.0 0.0 0.0 0.0 + accessMemoryRange EVM src/EVM.hs:(2383,1)-(2387,53) 6133 496 0.0 0.0 0.0 0.0 + accessUnboundedMemoryRange EVM src/EVM.hs:(2368,1)-(2375,14) 6134 496 0.0 0.0 0.0 0.0 + num EVM.Types src/EVM/Types.hs:492:1-18 6138 992 0.0 0.0 0.0 0.0 + ceilDiv EVM src/EVM.hs:2835:1-31 6132 496 0.0 0.0 0.0 0.0 + litWord EVM.Symbolic src/EVM/Symbolic.hs:24:1-52 6145 496 0.0 0.0 0.1 0.0 + genLiteral Data.SBV.Core.Model Data/SBV/Core/Model.hs:99:1-48 6151 496 0.1 0.0 0.1 0.0 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 6152 496 0.0 0.0 0.0 0.0 + svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 6153 496 0.0 0.0 0.0 0.0 + svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 6154 496 0.0 0.0 0.0 0.0 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 6155 496 0.0 0.0 0.0 0.0 + readMemory EVM src/EVM.hs:2412:1-92 6142 496 0.0 0.0 0.0 0.0 + num EVM.Types src/EVM/Types.hs:492:1-18 6148 992 0.0 0.0 0.0 0.0 + sliceWithZero EVM.Symbolic src/EVM/Symbolic.hs:(169,1)-(170,103) 6143 496 0.0 0.0 0.0 0.0 + byteStringSliceWithDefaultZeroes EVM.Concrete src/EVM/Concrete.hs:(27,1)-(35,51) 6149 496 0.0 0.0 0.0 0.0 + next EVM src/EVM.hs:543:1-46 5391 0 0.1 0.1 0.1 0.1 + stackOp2 EVM src/EVM.hs:(2500,1)-(2507,14) 5428 36018 1.0 0.3 3.9 3.2 + burn EVM src/EVM.hs:(1826,1)-(1838,38) 5429 36018 0.8 1.3 1.1 1.9 + num EVM.Types src/EVM/Types.hs:492:1-18 5430 36018 0.2 0.2 0.2 0.2 + next EVM src/EVM.hs:543:1-46 5432 0 0.1 0.4 0.1 0.4 + next EVM src/EVM.hs:543:1-46 5431 36018 0.1 0.1 0.1 0.1 + opSize EVM src/EVM.hs:(2542,1)-(2543,37) 5433 36018 0.1 0.0 0.1 0.0 + svPlus Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(148,1)-(151,80) 5684 13443 0.1 0.0 0.2 0.2 + cvVal Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:155:16-20 5685 9868 0.0 0.0 0.0 0.0 + mapCV2 Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(359,1)-(371,141) 5686 9868 0.2 0.2 0.2 0.2 + cvVal Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:155:16-20 5688 19736 0.0 0.0 0.0 0.0 + cvSameType Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:231:1-37 5687 9868 0.0 0.0 0.0 0.0 + iteWhiff EVM.Types src/EVM/Types.hs:211:1-34 5435 10548 0.1 0.0 0.1 0.0 + ite Data.SBV.Core.Model Data/SBV/Core/Model.hs:(1817,1)-(1819,52) 5635 10548 0.0 0.0 0.0 0.0 + cvToBool Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:235:1-34 5636 10548 0.0 0.0 0.0 0.0 + cvVal Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:155:16-20 5637 10548 0.0 0.0 0.0 0.0 + svEqual Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(288,1)-(292,129) 5661 6673 0.0 0.0 0.1 0.0 + cvVal Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:155:16-20 5662 6673 0.0 0.0 0.0 0.0 + liftCV2 Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(310,1)-(322,148) 5663 6673 0.1 0.0 0.1 0.0 + cvVal Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:155:16-20 5664 13346 0.0 0.0 0.0 0.0 + svBool Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:81:1-40 5665 6673 0.0 0.0 0.0 0.0 + svAnd Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(373,1)-(383,50) 5711 5729 0.3 0.1 0.3 0.2 + mapCV2 Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(359,1)-(371,141) 5712 5729 0.0 0.1 0.0 0.1 + cvVal Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:155:16-20 5714 11458 0.0 0.0 0.0 0.0 + cvSameType Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:231:1-37 5713 5729 0.0 0.0 0.0 0.0 + svGreaterThan Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(352,1)-(355,147) 5656 2293 0.0 0.0 0.1 0.0 + cvVal Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:155:16-20 5657 1799 0.0 0.0 0.0 0.0 + liftCV2 Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(310,1)-(322,148) 5658 1799 0.1 0.0 0.1 0.0 + cvVal Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:155:16-20 5659 3598 0.0 0.0 0.0 0.0 + svBool Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:81:1-40 5660 1799 0.0 0.0 0.0 0.0 + svLessThan Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(345,1)-(348,143) 5437 1582 0.0 0.0 0.0 0.0 + cvVal Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:155:16-20 5631 1582 0.0 0.0 0.0 0.0 + liftCV2 Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(310,1)-(322,148) 5632 1582 0.0 0.0 0.0 0.0 + cvVal Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:155:16-20 5633 3164 0.0 0.0 0.0 0.0 + svBool Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:81:1-40 5634 1582 0.0 0.0 0.0 0.0 + sShiftRight Data.SBV.Core.Model Data/SBV/Core/Model.hs:1464:1-38 5648 1449 0.1 0.0 0.1 0.0 + svShiftRight Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:726:1-28 5649 0 0.1 0.0 0.1 0.0 + .^ Data.SBV.Core.Model Data/SBV/Core/Model.hs:(1262,1)-(1280,49) 5841 1335 0.1 0.0 0.2 0.0 + svTimes Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(155,1)-(160,81) 5849 1684 0.1 0.0 0.1 0.0 + cvVal Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:155:16-20 5946 640 0.0 0.0 0.0 0.0 + mapCV2 Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(359,1)-(371,141) 5947 640 0.0 0.0 0.0 0.0 + cvVal Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:155:16-20 5949 1280 0.0 0.0 0.0 0.0 + cvSameType Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:231:1-37 5948 640 0.0 0.0 0.0 0.0 + genFromCV Data.SBV.Core.Model Data/SBV/Core/Model.hs:(103,1)-(104,95) 5843 1335 0.0 0.0 0.0 0.0 + sFromIntegral Data.SBV.Core.Model Data/SBV/Core/Model.hs:(1428,1)-(1441,70) 5842 1335 0.0 0.0 0.0 0.0 + genFromCV Data.SBV.Core.Model Data/SBV/Core/Model.hs:(103,1)-(104,95) 5845 1335 0.0 0.0 0.0 0.0 + svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 5846 1335 0.0 0.0 0.0 0.0 + svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 5847 1335 0.0 0.0 0.0 0.0 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 5848 1335 0.0 0.0 0.0 0.0 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 5844 1335 0.0 0.0 0.0 0.0 + forceLit EVM.Symbolic src/EVM/Symbolic.hs:(40,1)-(42,49) 5806 1335 0.0 0.0 0.1 0.0 + genFromCV Data.SBV.Core.Model Data/SBV/Core/Model.hs:(103,1)-(104,95) 5807 1335 0.0 0.0 0.1 0.0 + svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 5808 1335 0.0 0.0 0.0 0.0 + svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 5809 1335 0.0 0.0 0.1 0.0 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 5810 1335 0.1 0.0 0.1 0.0 + liftQRem Data.SBV.Core.Model Data/SBV/Core/Model.hs:(1702,1)-(1720,46) 5840 1335 0.1 0.0 0.3 0.1 + cvVal Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:155:16-20 5860 2088 0.0 0.0 0.0 0.0 + genLiteral Data.SBV.Core.Model Data/SBV/Core/Model.hs:99:1-48 5851 1044 0.1 0.0 0.1 0.0 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 5855 1044 0.1 0.0 0.1 0.0 + ite Data.SBV.Core.Model Data/SBV/Core/Model.hs:(1817,1)-(1819,52) 5857 1044 0.0 0.0 0.0 0.0 + cvToBool Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:235:1-34 5858 1044 0.0 0.0 0.0 0.0 + cvVal Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:155:16-20 5859 1044 0.0 0.0 0.0 0.0 + svEqual Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(288,1)-(292,129) 5850 1044 0.1 0.0 0.1 0.0 + cvVal Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:155:16-20 5852 1044 0.0 0.0 0.0 0.0 + liftCV2 Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(310,1)-(322,148) 5853 1044 0.0 0.0 0.0 0.0 + cvVal Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:155:16-20 5854 2088 0.0 0.0 0.0 0.0 + svBool Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:81:1-40 5856 1044 0.0 0.0 0.0 0.0 + slt EVM.Symbolic src/EVM/Symbolic.hs:(75,1)-(76,79) 5676 1248 0.1 0.0 0.3 0.2 + sFromIntegral Data.SBV.Core.Model Data/SBV/Core/Model.hs:(1428,1)-(1441,70) 5679 2496 0.1 0.0 0.2 0.2 + genFromCV Data.SBV.Core.Model Data/SBV/Core/Model.hs:(103,1)-(104,95) 5695 2496 0.0 0.0 0.1 0.0 + svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 5696 2496 0.0 0.0 0.0 0.0 + svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 5697 2496 0.0 0.0 0.1 0.0 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 5698 2496 0.1 0.0 0.1 0.0 + genLiteral Data.SBV.Core.Model Data/SBV/Core/Model.hs:99:1-48 5689 2496 0.0 0.0 0.1 0.1 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 5691 2496 0.1 0.1 0.1 0.1 + svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 5692 2496 0.0 0.0 0.0 0.0 + svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 5693 2496 0.0 0.0 0.0 0.1 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 5694 2496 0.0 0.1 0.0 0.1 + iteWhiff EVM.Types src/EVM/Types.hs:211:1-34 5677 1248 0.0 0.0 0.1 0.0 + ite Data.SBV.Core.Model Data/SBV/Core/Model.hs:(1817,1)-(1819,52) 5703 1248 0.0 0.0 0.1 0.0 + cvToBool Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:235:1-34 5704 1248 0.0 0.0 0.1 0.0 + cvVal Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:155:16-20 5705 1248 0.1 0.0 0.1 0.0 + svLessThan Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(345,1)-(348,143) 5690 1248 0.0 0.0 0.0 0.0 + cvVal Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:155:16-20 5699 1248 0.0 0.0 0.0 0.0 + liftCV2 Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(310,1)-(322,148) 5700 1248 0.0 0.0 0.0 0.0 + cvVal Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:155:16-20 5701 2496 0.0 0.0 0.0 0.0 + svBool Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:81:1-40 5702 1248 0.0 0.0 0.0 0.0 + ceilDiv EVM src/EVM.hs:2835:1-31 5813 1044 0.0 0.0 0.0 0.0 + log2 EVM src/EVM.hs:2841:1-50 5812 1044 0.0 0.0 0.0 0.0 + num EVM.Types src/EVM/Types.hs:492:1-18 5811 1044 0.0 0.0 0.0 0.0 + sShiftLeft Data.SBV.Core.Model Data/SBV/Core/Model.hs:1454:1-36 5943 640 0.0 0.0 0.0 0.0 + svShiftLeft Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:719:1-26 5945 0 0.0 0.0 0.0 0.0 + svUNeg Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:170:1-61 5681 0 0.1 0.0 0.2 0.1 + mapCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(334,1)-(346,133) 5682 4459 0.1 0.1 0.1 0.1 + cvVal Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:155:16-20 5683 4459 0.0 0.0 0.0 0.0 + stackOp1 EVM src/EVM.hs:(2485,1)-(2493,14) 5396 10290 0.4 0.1 2.9 1.5 + burn EVM src/EVM.hs:(1826,1)-(1838,38) 5397 10290 0.5 0.4 0.6 0.6 + num EVM.Types src/EVM/Types.hs:492:1-18 5398 10290 0.1 0.1 0.1 0.1 + next EVM src/EVM.hs:543:1-46 5400 0 0.0 0.1 0.0 0.1 + next EVM src/EVM.hs:543:1-46 5399 10290 0.0 0.0 0.0 0.0 + opSize EVM src/EVM.hs:(2542,1)-(2543,37) 5402 10290 0.0 0.0 0.0 0.0 + iteWhiff EVM.Types src/EVM/Types.hs:211:1-34 5401 6895 0.0 0.0 0.2 0.0 + ite Data.SBV.Core.Model Data/SBV/Core/Model.hs:(1817,1)-(1819,52) 5408 6895 0.1 0.0 0.2 0.0 + cvToBool Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:235:1-34 5409 6895 0.0 0.0 0.1 0.0 + cvVal Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:155:16-20 5410 6895 0.1 0.0 0.1 0.0 + svEqual Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(288,1)-(292,129) 5403 6895 0.0 0.0 0.1 0.0 + cvVal Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:155:16-20 5404 6895 0.0 0.0 0.0 0.0 + liftCV2 Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(310,1)-(322,148) 5405 6895 0.1 0.0 0.1 0.0 + cvVal Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:155:16-20 5406 13790 0.0 0.0 0.0 0.0 + svBool Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:81:1-40 5407 6895 0.0 0.0 0.0 0.0 + readSWordWithBound EVM.Symbolic src/EVM/Symbolic.hs:(136,1)-(157,48) 5638 3047 0.1 0.0 1.7 0.8 + litWord EVM.Symbolic src/EVM/Symbolic.hs:24:1-52 5647 3047 0.2 0.0 0.3 0.1 + genLiteral Data.SBV.Core.Model Data/SBV/Core/Model.hs:99:1-48 5650 3047 0.0 0.0 0.0 0.0 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 5651 3047 0.0 0.0 0.0 0.0 + svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 5652 3047 0.0 0.0 0.0 0.0 + svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 5653 3047 0.0 0.0 0.1 0.0 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 5654 3047 0.1 0.0 0.1 0.0 + maybeLitWord EVM.Types src/EVM/Types.hs:324:1-68 5639 3047 0.0 0.0 0.0 0.1 + genFromCV Data.SBV.Core.Model Data/SBV/Core/Model.hs:(103,1)-(104,95) 5640 3047 0.0 0.0 0.0 0.0 + svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 5641 3047 0.0 0.0 0.0 0.0 + svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 5642 3047 0.0 0.0 0.0 0.0 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 5643 3047 0.0 0.0 0.0 0.0 + readMemoryWord EVM.Concrete src/EVM/Concrete.hs:(62,1)-(70,19) 5644 3047 0.3 0.0 1.3 0.6 + num EVM.Types src/EVM/Types.hs:492:1-18 5645 103598 1.0 0.6 1.0 0.6 + readByteOrZero EVM.Concrete src/EVM/Concrete.hs:24:1-46 5655 97504 0.0 0.0 0.0 0.0 + readMemoryWord EVM.Concrete src/EVM/Concrete.hs:70:5-19 5646 3047 0.0 0.0 0.0 0.0 + svNot Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(417,1)-(423,34) 6316 0 0.0 0.0 0.0 0.0 + mapCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(334,1)-(346,133) 6317 348 0.0 0.0 0.0 0.0 + cvVal Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:155:16-20 6318 348 0.0 0.0 0.0 0.0 + accessStorage EVM src/EVM.hs:(1674,1)-(1702,35) 5798 2266 0.0 0.0 0.0 0.0 + accessStorageForGas EVM src/EVM.hs:(1919,1)-(1927,21) 5791 2266 0.1 0.0 0.2 0.1 + maybeLitWord EVM.Types src/EVM/Types.hs:324:1-68 5792 2266 0.1 0.0 0.1 0.1 + genFromCV Data.SBV.Core.Model Data/SBV/Core/Model.hs:(103,1)-(104,95) 5794 2266 0.0 0.0 0.1 0.0 + svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 5795 2266 0.0 0.0 0.0 0.0 + svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 5796 2266 0.0 0.0 0.1 0.0 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 5797 2266 0.1 0.0 0.1 0.0 + wordValue EVM.Concrete src/EVM/Concrete.hs:39:1-21 5793 2266 0.0 0.0 0.0 0.0 + notStatic EVM src/EVM.hs:(1816,1)-(1820,17) 6193 874 0.0 0.0 0.4 0.3 + accessStorage EVM src/EVM.hs:(1674,1)-(1702,35) 6194 582 0.1 0.0 0.3 0.1 + maybeLitWord EVM.Types src/EVM/Types.hs:324:1-68 6209 1164 0.0 0.0 0.0 0.0 + genFromCV Data.SBV.Core.Model Data/SBV/Core/Model.hs:(103,1)-(104,95) 6211 1164 0.0 0.0 0.0 0.0 + svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 6212 1164 0.0 0.0 0.0 0.0 + svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 6213 1164 0.0 0.0 0.0 0.0 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 6214 1164 0.0 0.0 0.0 0.0 + accessStorageForGas EVM src/EVM.hs:(1919,1)-(1927,21) 6202 582 0.1 0.0 0.1 0.0 + maybeLitWord EVM.Types src/EVM/Types.hs:324:1-68 6203 582 0.0 0.0 0.0 0.0 + genFromCV Data.SBV.Core.Model Data/SBV/Core/Model.hs:(103,1)-(104,95) 6205 582 0.0 0.0 0.0 0.0 + svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 6206 582 0.0 0.0 0.0 0.0 + svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 6207 582 0.0 0.0 0.0 0.0 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 6208 582 0.0 0.0 0.0 0.0 + wordValue EVM.Concrete src/EVM/Concrete.hs:39:1-21 6204 582 0.0 0.0 0.0 0.0 + burn EVM src/EVM.hs:(1826,1)-(1838,38) 6220 582 0.0 0.0 0.0 0.0 + num EVM.Types src/EVM/Types.hs:492:1-18 6221 582 0.0 0.0 0.0 0.0 + writeStorage EVM src/EVM.hs:(1666,1)-(1667,78) 6223 582 0.0 0.0 0.0 0.0 + num EVM.Types src/EVM/Types.hs:492:1-18 6201 582 0.0 0.0 0.0 0.0 + readStorage EVM src/EVM.hs:(1662,1)-(1663,58) 6195 582 0.0 0.0 0.2 0.0 + forceLit EVM.Symbolic src/EVM/Symbolic.hs:(40,1)-(42,49) 6196 582 0.1 0.0 0.2 0.0 + genFromCV Data.SBV.Core.Model Data/SBV/Core/Model.hs:(103,1)-(104,95) 6197 582 0.1 0.0 0.1 0.0 + svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 6198 582 0.0 0.0 0.0 0.0 + svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 6199 582 0.0 0.0 0.0 0.0 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 6200 582 0.0 0.0 0.0 0.0 + forceLit EVM.Symbolic src/EVM/Symbolic.hs:(40,1)-(42,49) 6219 582 0.0 0.0 0.0 0.0 + maybeLitWord EVM.Types src/EVM/Types.hs:324:1-68 6210 582 0.1 0.0 0.1 0.0 + genFromCV Data.SBV.Core.Model Data/SBV/Core/Model.hs:(103,1)-(104,95) 6215 582 0.0 0.0 0.0 0.0 + svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 6216 582 0.0 0.0 0.0 0.0 + svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 6217 582 0.0 0.0 0.0 0.0 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 6218 582 0.0 0.0 0.0 0.0 + forceConcrete2 EVM src/EVM.hs:(1851,1)-(1853,36) 6231 292 0.1 0.0 0.1 0.1 + num EVM.Types src/EVM/Types.hs:492:1-18 6237 586 0.0 0.0 0.0 0.0 + burn EVM src/EVM.hs:(1826,1)-(1838,38) 6238 584 0.0 0.0 0.0 0.0 + num EVM.Types src/EVM/Types.hs:492:1-18 6239 584 0.0 0.0 0.0 0.0 + accessMemoryRange EVM src/EVM.hs:(2383,1)-(2387,53) 6242 0 0.0 0.0 0.0 0.0 + accessUnboundedMemoryRange EVM src/EVM.hs:(2368,1)-(2375,14) 6243 0 0.0 0.0 0.0 0.0 + memoryCost EVM src/EVM.hs:(2824,1)-(2830,30) 6247 584 0.0 0.0 0.0 0.0 + ceilDiv EVM src/EVM.hs:2835:1-31 6248 584 0.0 0.0 0.0 0.0 + ceilDiv EVM src/EVM.hs:2835:1-31 6246 292 0.0 0.0 0.0 0.0 + num EVM.Types src/EVM/Types.hs:492:1-18 6244 292 0.0 0.0 0.0 0.0 + next EVM src/EVM.hs:543:1-46 6253 0 0.0 0.0 0.0 0.0 + pushToSequence EVM src/EVM.hs:1585:1-36 6255 0 0.0 0.0 0.0 0.0 + traceLog EVM src/EVM.hs:(2466,1)-(2469,60) 6250 0 0.0 0.0 0.0 0.0 + insert Data.Tree.Zipper Data/Tree/Zipper.hs:275:1-37 6257 292 0.0 0.0 0.0 0.0 + nextSpace Data.Tree.Zipper Data/Tree/Zipper.hs:153:1-69 6256 292 0.0 0.0 0.0 0.0 + maybeLitWord EVM.Types src/EVM/Types.hs:324:1-68 6232 584 0.0 0.0 0.0 0.0 + genFromCV Data.SBV.Core.Model Data/SBV/Core/Model.hs:(103,1)-(104,95) 6233 584 0.0 0.0 0.0 0.0 + svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 6234 584 0.0 0.0 0.0 0.0 + svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 6235 584 0.0 0.0 0.0 0.0 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 6236 584 0.0 0.0 0.0 0.0 + accessMemoryRange EVM src/EVM.hs:(2383,1)-(2387,53) 6240 292 0.0 0.0 0.0 0.0 + accessUnboundedMemoryRange EVM src/EVM.hs:(2368,1)-(2375,14) 6241 292 0.0 0.0 0.0 0.0 + num EVM.Types src/EVM/Types.hs:492:1-18 6245 584 0.0 0.0 0.0 0.0 + next EVM src/EVM.hs:543:1-46 6252 292 0.0 0.0 0.0 0.0 + opSize EVM src/EVM.hs:(2542,1)-(2543,37) 6258 292 0.0 0.0 0.0 0.0 + pushToSequence EVM src/EVM.hs:1585:1-36 6254 292 0.0 0.0 0.0 0.0 + traceLog EVM src/EVM.hs:(2466,1)-(2469,60) 6249 292 0.0 0.0 0.0 0.0 + withTraceLocation EVM src/EVM.hs:(2426,1)-(2435,5) 6251 292 0.0 0.0 0.0 0.0 + readMemory EVM src/EVM.hs:2412:1-92 6426 2 0.0 0.0 0.0 0.0 + num EVM.Types src/EVM/Types.hs:492:1-18 6455 2 0.0 0.0 0.0 0.0 + sliceWithZero EVM.Symbolic src/EVM/Symbolic.hs:(169,1)-(170,103) 6427 2 0.0 0.0 0.0 0.0 + byteStringSliceWithDefaultZeroes EVM.Concrete src/EVM/Concrete.hs:(27,1)-(35,51) 6456 1 0.0 0.0 0.0 0.0 + num EVM.Types src/EVM/Types.hs:492:1-18 6230 292 0.0 0.0 0.0 0.0 + next EVM src/EVM.hs:543:1-46 6222 0 0.0 0.0 0.0 0.0 + writeStorage EVM src/EVM.hs:(1666,1)-(1667,78) 6224 0 0.0 0.0 0.1 0.0 + forceLit EVM.Symbolic src/EVM/Symbolic.hs:(40,1)-(42,49) 6225 582 0.1 0.0 0.1 0.0 + genFromCV Data.SBV.Core.Model Data/SBV/Core/Model.hs:(103,1)-(104,95) 6226 582 0.0 0.0 0.0 0.0 + svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 6227 582 0.0 0.0 0.0 0.0 + svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 6228 582 0.0 0.0 0.0 0.0 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 6229 582 0.0 0.0 0.0 0.0 + forceConcrete2 EVM src/EVM.hs:(1851,1)-(1853,36) 5861 754 0.2 0.0 0.5 0.3 + maybeLitWord EVM.Types src/EVM/Types.hs:324:1-68 5862 1508 0.0 0.0 0.1 0.0 + genFromCV Data.SBV.Core.Model Data/SBV/Core/Model.hs:(103,1)-(104,95) 5863 1508 0.1 0.0 0.1 0.0 + svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 5864 1508 0.0 0.0 0.0 0.0 + svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 5865 1508 0.0 0.0 0.1 0.0 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 5866 1508 0.1 0.0 0.1 0.0 + accessMemoryRange EVM src/EVM.hs:(2383,1)-(2387,53) 5867 754 0.0 0.0 0.3 0.2 + accessUnboundedMemoryRange EVM src/EVM.hs:(2368,1)-(2375,14) 5868 754 0.0 0.0 0.3 0.2 + num EVM.Types src/EVM/Types.hs:492:1-18 5869 2262 0.0 0.0 0.0 0.0 + memoryCost EVM src/EVM.hs:(2824,1)-(2830,30) 5871 1508 0.0 0.0 0.0 0.0 + ceilDiv EVM src/EVM.hs:2835:1-31 5872 1508 0.0 0.0 0.0 0.0 + burn EVM src/EVM.hs:(1826,1)-(1838,38) 5873 754 0.0 0.0 0.3 0.2 + num EVM.Types src/EVM/Types.hs:492:1-18 5874 754 0.0 0.0 0.0 0.0 + finishFrame EVM src/EVM.hs:(2237,1)-(2357,20) 5876 0 0.1 0.0 0.3 0.2 + num EVM.Types src/EVM/Types.hs:492:1-18 6290 698 0.0 0.0 0.0 0.0 + copyCallBytesToMemory EVM src/EVM.hs:(2404,1)-(2409,66) 6291 349 0.1 0.0 0.1 0.0 + len EVM.Symbolic src/EVM/Symbolic.hs:(161,1)-(162,38) 6310 349 0.0 0.0 0.0 0.0 + num EVM.Types src/EVM/Types.hs:492:1-18 6309 349 0.0 0.0 0.0 0.0 + writeMemory EVM.Symbolic src/EVM/Symbolic.hs:(173,1)-(180,49) 6300 349 0.0 0.0 0.0 0.0 + writeMemory EVM.Concrete src/EVM/Concrete.hs:(46,1)-(59,22) 6308 349 0.0 0.0 0.0 0.0 + num EVM.Types src/EVM/Types.hs:492:1-18 6311 1396 0.0 0.0 0.0 0.0 + sliceMemory EVM.Concrete src/EVM/Concrete.hs:(42,1)-(43,50) 6312 349 0.0 0.0 0.0 0.0 + num EVM.Types src/EVM/Types.hs:492:1-18 6313 698 0.0 0.0 0.0 0.0 + byteStringSliceWithDefaultZeroes EVM.Concrete src/EVM/Concrete.hs:(27,1)-(35,51) 6314 349 0.0 0.0 0.0 0.0 + insertTrace EVM src/EVM.hs:(2444,1)-(2447,60) 6288 349 0.0 0.0 0.0 0.0 + insert Data.Tree.Zipper Data/Tree/Zipper.hs:275:1-37 6296 349 0.0 0.0 0.0 0.0 + nextSpace Data.Tree.Zipper Data/Tree/Zipper.hs:153:1-69 6295 349 0.0 0.0 0.0 0.0 + withTraceLocation EVM src/EVM.hs:(2426,1)-(2435,5) 6289 349 0.0 0.0 0.0 0.0 + forceConcreteBuffer EVM src/EVM.hs:(1876,1)-(1879,60) 6352 1 0.0 0.0 0.0 0.0 + finalize EVM src/EVM.hs:(1721,1)-(1790,66) 5879 0 0.0 0.1 0.1 0.1 + accountEmpty EVM src/EVM.hs:(1712,1)-(1717,26) 5885 1617 0.0 0.0 0.0 0.0 + len EVM.Symbolic src/EVM/Symbolic.hs:(161,1)-(162,38) 5886 1617 0.0 0.0 0.0 0.0 + num EVM.Types src/EVM/Types.hs:492:1-18 5883 810 0.1 0.0 0.1 0.0 + noop EVM src/EVM.hs:1579:1-14 5884 405 0.0 0.0 0.0 0.0 + r_block EVM.FeeSchedule src/EVM/FeeSchedule.hs:47:5-11 5887 405 0.0 0.0 0.0 0.0 + w256 EVM.Types src/EVM/Types.hs:90:1-24 5882 405 0.0 0.0 0.0 0.0 + touchAccount EVM src/EVM.hs:1895:1-57 5880 0 0.0 0.0 0.0 0.0 + pushTo EVM src/EVM.hs:1582:1-23 5881 405 0.0 0.0 0.0 0.0 + popTrace EVM src/EVM.hs:(2450,1)-(2454,42) 6294 0 0.0 0.0 0.0 0.0 + nextSpace Data.Tree.Zipper Data/Tree/Zipper.hs:153:1-69 6299 349 0.0 0.0 0.0 0.0 + parent Data.Tree.Zipper Data/Tree/Zipper.hs:(124,1)-(132,17) 6297 349 0.0 0.0 0.0 0.0 + parents Data.Tree.Zipper Data/Tree/Zipper.hs:71:1-26 6298 349 0.0 0.0 0.0 0.0 + push EVM src/EVM.hs:2474:1-30 6292 0 0.0 0.0 0.1 0.0 + pushSym EVM src/EVM.hs:2477:1-34 6293 349 0.0 0.0 0.0 0.0 + w256lit EVM.Types src/EVM/Types.hs:346:1-48 6301 349 0.0 0.0 0.1 0.0 + genLiteral Data.SBV.Core.Model Data/SBV/Core/Model.hs:99:1-48 6302 349 0.0 0.0 0.0 0.0 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 6303 349 0.0 0.0 0.0 0.0 + svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 6304 349 0.0 0.0 0.0 0.0 + svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 6305 349 0.0 0.0 0.1 0.0 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 6306 349 0.1 0.0 0.1 0.0 + num EVM.Types src/EVM/Types.hs:492:1-18 6307 0 0.0 0.0 0.0 0.0 + ceilDiv EVM src/EVM.hs:2835:1-31 5870 754 0.0 0.0 0.0 0.0 + finishFrame EVM src/EVM.hs:(2237,1)-(2357,20) 5875 754 0.0 0.0 0.0 0.0 + readMemory EVM src/EVM.hs:2412:1-92 5877 754 0.0 0.0 0.0 0.0 + num EVM.Types src/EVM/Types.hs:492:1-18 5892 1508 0.0 0.0 0.0 0.0 + sliceWithZero EVM.Symbolic src/EVM/Symbolic.hs:(169,1)-(170,103) 5878 754 0.0 0.0 0.0 0.0 + byteStringSliceWithDefaultZeroes EVM.Concrete src/EVM/Concrete.hs:(27,1)-(35,51) 5893 754 0.0 0.0 0.0 0.0 + forceConcrete5 EVM src/EVM.hs:(1866,1)-(1868,36) 6016 640 0.1 0.0 1.0 0.6 + maybeLitWord EVM.Types src/EVM/Types.hs:324:1-68 6017 3200 0.0 0.0 0.0 0.1 + genFromCV Data.SBV.Core.Model Data/SBV/Core/Model.hs:(103,1)-(104,95) 6055 2909 0.0 0.0 0.0 0.0 + svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 6056 2909 0.0 0.0 0.0 0.0 + svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 6057 2909 0.0 0.0 0.0 0.0 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 6058 2909 0.0 0.0 0.0 0.0 + delegateCall EVM src/EVM.hs:(2052,1)-(2108,31) 6023 640 0.1 0.0 0.8 0.5 + num EVM.Types src/EVM/Types.hs:492:1-18 6113 1920 0.0 0.0 0.0 0.0 + makeUnique EVM src/EVM.hs:(1592,1)-(1602,18) 6031 1280 0.0 0.0 0.6 0.4 + num EVM.Types src/EVM/Types.hs:492:1-18 6033 1920 0.1 0.1 0.1 0.1 + maybeLitWord EVM.Types src/EVM/Types.hs:324:1-68 6032 1280 0.0 0.0 0.0 0.0 + genFromCV Data.SBV.Core.Model Data/SBV/Core/Model.hs:(103,1)-(104,95) 6050 1280 0.0 0.0 0.0 0.0 + svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 6051 1280 0.0 0.0 0.0 0.0 + svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 6052 1280 0.0 0.0 0.0 0.0 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 6053 1280 0.0 0.0 0.0 0.0 + callChecks EVM src/EVM.hs:(1338,1)-(1359,31) 6054 640 0.1 0.0 0.6 0.3 + accessMemoryRange EVM src/EVM.hs:(2383,1)-(2387,53) 6059 1280 0.1 0.0 0.5 0.3 + accessUnboundedMemoryRange EVM src/EVM.hs:(2368,1)-(2375,14) 6060 989 0.0 0.0 0.5 0.3 + num EVM.Types src/EVM/Types.hs:492:1-18 6061 2618 0.0 0.0 0.0 0.0 + burn EVM src/EVM.hs:(1826,1)-(1838,38) 6066 2269 0.1 0.1 0.5 0.3 + num EVM.Types src/EVM/Types.hs:492:1-18 6067 3258 0.1 0.0 0.1 0.0 + readMemory EVM src/EVM.hs:2412:1-92 6114 1280 0.0 0.0 0.0 0.0 + num EVM.Types src/EVM/Types.hs:492:1-18 6116 1280 0.0 0.0 0.0 0.0 + sliceWithZero EVM.Symbolic src/EVM/Symbolic.hs:(169,1)-(170,103) 6115 1280 0.0 0.0 0.0 0.0 + byteStringSliceWithDefaultZeroes EVM.Concrete src/EVM/Concrete.hs:(27,1)-(35,51) 6117 640 0.0 0.0 0.0 0.0 + memoryCost EVM src/EVM.hs:(2824,1)-(2830,30) 6286 698 0.0 0.0 0.0 0.0 + ceilDiv EVM src/EVM.hs:2835:1-31 6287 698 0.0 0.0 0.0 0.0 + costOfCall EVM src/EVM.hs:(2748,1)-(2762,40) 6068 640 0.1 0.0 0.1 0.0 + num EVM.Types src/EVM/Types.hs:492:1-18 6071 1920 0.0 0.0 0.0 0.0 + accessAccountForGas EVM src/EVM.hs:(1910,1)-(1914,17) 6069 640 0.0 0.0 0.0 0.0 + allButOne64th EVM src/EVM.hs:2838:1-30 6075 640 0.0 0.0 0.0 0.0 + fetchAccount EVM src/EVM.hs:(1639,1)-(1659,23) 6082 640 0.1 0.1 0.2 0.1 + bytecode EVM src/EVM.hs:(415,1)-(417,29) 6090 640 0.1 0.0 0.1 0.0 + pushTo EVM src/EVM.hs:1582:1-23 6087 640 0.0 0.0 0.0 0.0 + pushTrace EVM src/EVM.hs:(2438,1)-(2441,59) 6083 640 0.0 0.0 0.0 0.0 + children Data.Tree.Zipper Data/Tree/Zipper.hs:(166,1)-(172,7) 6088 640 0.0 0.0 0.0 0.0 + parents Data.Tree.Zipper Data/Tree/Zipper.hs:71:1-26 6319 637 0.0 0.0 0.0 0.0 + withTraceLocation EVM src/EVM.hs:(2426,1)-(2435,5) 6084 640 0.0 0.0 0.0 0.0 + insert Data.Tree.Zipper Data/Tree/Zipper.hs:275:1-37 6320 637 0.0 0.0 0.0 0.0 + transfer EVM src/EVM.hs:(1326,1)-(1329,31) 6091 292 0.0 0.0 0.0 0.0 + next EVM src/EVM.hs:543:1-46 6086 0 0.0 0.0 0.0 0.0 + touchAccount EVM src/EVM.hs:1895:1-57 6097 0 0.0 0.0 0.0 0.0 + pushTo EVM src/EVM.hs:1582:1-23 6098 640 0.0 0.0 0.0 0.0 + readMemoryWord32 EVM.Symbolic src/EVM/Symbolic.hs:(187,1)-(188,75) 6261 640 0.1 0.0 0.1 0.0 + num EVM.Types src/EVM/Types.hs:492:1-18 6262 640 0.0 0.0 0.0 0.0 + genLiteral Data.SBV.Core.Model Data/SBV/Core/Model.hs:99:1-48 6265 640 0.0 0.0 0.0 0.0 + ceilDiv EVM src/EVM.hs:2835:1-31 6285 349 0.0 0.0 0.0 0.0 + memoryCost EVM src/EVM.hs:(2824,1)-(2830,30) 6064 1280 0.0 0.0 0.0 0.0 + ceilDiv EVM src/EVM.hs:2835:1-31 6065 1280 0.0 0.0 0.0 0.0 + ceilDiv EVM src/EVM.hs:2835:1-31 6063 640 0.0 0.0 0.0 0.0 + accountExists EVM src/EVM.hs:(1705,1)-(1708,20) 6072 640 0.0 0.0 0.0 0.0 + accountEmpty EVM src/EVM.hs:(1712,1)-(1717,26) 6073 640 0.0 0.0 0.0 0.0 + len EVM.Symbolic src/EVM/Symbolic.hs:(161,1)-(162,38) 6074 640 0.0 0.0 0.0 0.0 + sFromIntegral Data.SBV.Core.Model Data/SBV/Core/Model.hs:(1428,1)-(1441,70) 6025 1280 0.1 0.0 0.1 0.1 + genFromCV Data.SBV.Core.Model Data/SBV/Core/Model.hs:(103,1)-(104,95) 6046 1280 0.0 0.0 0.0 0.0 + svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 6047 1280 0.0 0.0 0.0 0.0 + svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 6048 1280 0.0 0.0 0.0 0.0 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 6049 1280 0.0 0.0 0.0 0.0 + genLiteral Data.SBV.Core.Model Data/SBV/Core/Model.hs:99:1-48 6030 1280 0.0 0.0 0.0 0.0 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 6034 1280 0.0 0.0 0.0 0.0 + svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 6035 1280 0.0 0.0 0.0 0.0 + svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 6036 1280 0.0 0.0 0.0 0.0 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 6037 1280 0.0 0.0 0.0 0.0 + next EVM src/EVM.hs:543:1-46 6085 640 0.0 0.0 0.0 0.0 + opSize EVM src/EVM.hs:(2542,1)-(2543,37) 6089 640 0.0 0.0 0.0 0.0 + w256lit EVM.Types src/EVM/Types.hs:346:1-48 6107 640 0.0 0.0 0.0 0.0 + genLiteral Data.SBV.Core.Model Data/SBV/Core/Model.hs:99:1-48 6108 640 0.0 0.0 0.0 0.0 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 6109 640 0.0 0.0 0.0 0.0 + svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 6110 640 0.0 0.0 0.0 0.0 + svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 6111 640 0.0 0.0 0.0 0.0 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 6112 640 0.0 0.0 0.0 0.0 + forceLit EVM.Symbolic src/EVM/Symbolic.hs:(40,1)-(42,49) 6018 292 0.0 0.0 0.1 0.0 + genFromCV Data.SBV.Core.Model Data/SBV/Core/Model.hs:(103,1)-(104,95) 6019 292 0.0 0.0 0.1 0.0 + svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 6020 292 0.0 0.0 0.0 0.0 + svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 6021 292 0.0 0.0 0.1 0.0 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 6022 292 0.1 0.0 0.1 0.0 + litWord EVM.Symbolic src/EVM/Symbolic.hs:24:1-52 6092 292 0.0 0.0 0.1 0.0 + svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 6103 292 0.0 0.0 0.0 0.0 + svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 6104 292 0.0 0.0 0.1 0.0 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 6105 292 0.1 0.0 0.1 0.0 + litAddr EVM.Symbolic src/EVM/Symbolic.hs:27:1-36 6093 0 0.1 0.0 0.1 0.0 + genLiteral Data.SBV.Core.Model Data/SBV/Core/Model.hs:99:1-48 6094 640 0.0 0.0 0.0 0.0 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 6124 292 0.0 0.0 0.0 0.0 + svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 6125 292 0.0 0.0 0.0 0.0 + svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 6126 292 0.0 0.0 0.0 0.0 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 6127 292 0.0 0.0 0.0 0.0 + touchAccount EVM src/EVM.hs:1895:1-57 6095 0 0.0 0.0 0.0 0.0 + pushTo EVM src/EVM.hs:1582:1-23 6096 640 0.0 0.0 0.0 0.0 + makeUnique EVM src/EVM.hs:(1592,1)-(1602,18) 5950 640 0.0 0.0 0.4 0.2 + num EVM.Types src/EVM/Types.hs:492:1-18 5993 1280 0.1 0.0 0.1 0.0 + accessAndBurn EVM src/EVM.hs:(1901,1)-(1905,16) 5990 640 0.0 0.0 0.3 0.1 + accessAccountForGas EVM src/EVM.hs:(1910,1)-(1914,17) 5992 640 0.1 0.0 0.1 0.0 + burn EVM src/EVM.hs:(1826,1)-(1838,38) 5994 640 0.1 0.0 0.2 0.1 + num EVM.Types src/EVM/Types.hs:492:1-18 5995 640 0.0 0.0 0.0 0.0 + fetchAccount EVM src/EVM.hs:(1639,1)-(1659,23) 5997 0 0.1 0.0 0.1 0.1 + bytecode EVM src/EVM.hs:(415,1)-(417,29) 6009 640 0.0 0.0 0.0 0.0 + len EVM.Symbolic src/EVM/Symbolic.hs:(161,1)-(162,38) 6008 640 0.0 0.0 0.0 0.0 + num EVM.Types src/EVM/Types.hs:492:1-18 6007 640 0.0 0.0 0.0 0.0 + push EVM src/EVM.hs:2474:1-30 5998 0 0.0 0.0 0.1 0.0 + pushSym EVM src/EVM.hs:2477:1-34 5999 640 0.1 0.0 0.1 0.0 + w256lit EVM.Types src/EVM/Types.hs:346:1-48 6000 640 0.0 0.0 0.0 0.0 + genLiteral Data.SBV.Core.Model Data/SBV/Core/Model.hs:99:1-48 6001 640 0.0 0.0 0.0 0.0 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 6002 640 0.0 0.0 0.0 0.0 + svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 6003 640 0.0 0.0 0.0 0.0 + svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 6004 640 0.0 0.0 0.0 0.0 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 6005 640 0.0 0.0 0.0 0.0 + num EVM.Types src/EVM/Types.hs:492:1-18 6006 0 0.0 0.0 0.0 0.0 + fetchAccount EVM src/EVM.hs:(1639,1)-(1659,23) 5996 640 0.0 0.0 0.0 0.0 + maybeLitWord EVM.Types src/EVM/Types.hs:324:1-68 5951 640 0.0 0.0 0.0 0.0 + genFromCV Data.SBV.Core.Model Data/SBV/Core/Model.hs:(103,1)-(104,95) 5953 640 0.0 0.0 0.0 0.0 + svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 5954 640 0.0 0.0 0.0 0.0 + svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 5955 640 0.0 0.0 0.0 0.0 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 5956 640 0.0 0.0 0.0 0.0 + sFromIntegral Data.SBV.Core.Model Data/SBV/Core/Model.hs:(1428,1)-(1441,70) 6027 640 0.1 0.0 0.2 0.0 + genFromCV Data.SBV.Core.Model Data/SBV/Core/Model.hs:(103,1)-(104,95) 6042 640 0.0 0.0 0.1 0.0 + svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 6043 640 0.0 0.0 0.0 0.0 + svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 6044 640 0.0 0.0 0.1 0.0 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 6045 640 0.1 0.0 0.1 0.0 + genLiteral Data.SBV.Core.Model Data/SBV/Core/Model.hs:99:1-48 6029 640 0.0 0.0 0.0 0.0 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 6038 640 0.0 0.0 0.0 0.0 + svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 6039 640 0.0 0.0 0.0 0.0 + svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 6040 640 0.0 0.0 0.1 0.0 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 6041 640 0.1 0.0 0.1 0.0 + forceConcrete3 EVM src/EVM.hs:(1856,1)-(1858,36) 6332 1 0.0 0.0 0.0 0.0 + maybeLitWord EVM.Types src/EVM/Types.hs:324:1-68 6333 3 0.0 0.0 0.0 0.0 + genFromCV Data.SBV.Core.Model Data/SBV/Core/Model.hs:(103,1)-(104,95) 6335 3 0.0 0.0 0.0 0.0 + svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 6336 3 0.0 0.0 0.0 0.0 + svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 6337 3 0.0 0.0 0.0 0.0 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 6338 3 0.0 0.0 0.0 0.0 + burn EVM src/EVM.hs:(1826,1)-(1838,38) 6340 2 0.0 0.0 0.0 0.0 + num EVM.Types src/EVM/Types.hs:492:1-18 6341 2 0.0 0.0 0.0 0.0 + accessUnboundedMemoryRange EVM src/EVM.hs:(2368,1)-(2375,14) 6343 0 0.0 0.0 0.0 0.0 + memoryCost EVM src/EVM.hs:(2824,1)-(2830,30) 6347 2 0.0 0.0 0.0 0.0 + ceilDiv EVM src/EVM.hs:2835:1-31 6348 2 0.0 0.0 0.0 0.0 + ceilDiv EVM src/EVM.hs:2835:1-31 6346 1 0.0 0.0 0.0 0.0 + num EVM.Types src/EVM/Types.hs:492:1-18 6344 1 0.0 0.0 0.0 0.0 + copyBytesToMemory EVM src/EVM.hs:(2395,1)-(2400,45) 6350 0 0.0 0.0 0.0 0.0 + writeMemory EVM.Symbolic src/EVM/Symbolic.hs:(173,1)-(180,49) 6351 1 0.0 0.0 0.0 0.0 + writeMemory EVM.Concrete src/EVM/Concrete.hs:(46,1)-(59,22) 6353 1 0.0 0.0 0.0 0.0 + num EVM.Types src/EVM/Types.hs:492:1-18 6354 4 0.0 0.0 0.0 0.0 + sliceMemory EVM.Concrete src/EVM/Concrete.hs:(42,1)-(43,50) 6355 1 0.0 0.0 0.0 0.0 + num EVM.Types src/EVM/Types.hs:492:1-18 6356 2 0.0 0.0 0.0 0.0 + byteStringSliceWithDefaultZeroes EVM.Concrete src/EVM/Concrete.hs:(27,1)-(35,51) 6357 1 0.0 0.0 0.0 0.0 + accessUnboundedMemoryRange EVM src/EVM.hs:(2368,1)-(2375,14) 6342 1 0.0 0.0 0.0 0.0 + num EVM.Types src/EVM/Types.hs:492:1-18 6345 2 0.0 0.0 0.0 0.0 + ceilDiv EVM src/EVM.hs:2835:1-31 6339 1 0.0 0.0 0.0 0.0 + copyBytesToMemory EVM src/EVM.hs:(2395,1)-(2400,45) 6349 1 0.0 0.0 0.0 0.0 + num EVM.Types src/EVM/Types.hs:492:1-18 6334 1 0.0 0.0 0.0 0.0 + finishFrame EVM src/EVM.hs:(2237,1)-(2357,20) 5715 0 0.0 0.0 0.3 0.1 + copyCallBytesToMemory EVM src/EVM.hs:(2404,1)-(2409,66) 6267 291 0.0 0.0 0.0 0.0 + noop EVM src/EVM.hs:1579:1-14 6269 291 0.0 0.0 0.0 0.0 + insertTrace EVM src/EVM.hs:(2444,1)-(2447,60) 6259 291 0.0 0.0 0.0 0.0 + insert Data.Tree.Zipper Data/Tree/Zipper.hs:275:1-37 6274 291 0.0 0.0 0.0 0.0 + nextSpace Data.Tree.Zipper Data/Tree/Zipper.hs:153:1-69 6273 291 0.0 0.0 0.0 0.0 + withTraceLocation EVM src/EVM.hs:(2426,1)-(2435,5) 6260 291 0.0 0.0 0.0 0.0 + num EVM.Types src/EVM/Types.hs:492:1-18 6266 291 0.0 0.0 0.0 0.0 + finalize EVM src/EVM.hs:(1721,1)-(1790,66) 5716 0 0.1 0.1 0.3 0.1 + accountEmpty EVM src/EVM.hs:(1712,1)-(1717,26) 5722 1616 0.1 0.0 0.1 0.0 + len EVM.Symbolic src/EVM/Symbolic.hs:(161,1)-(162,38) 5723 1616 0.0 0.0 0.0 0.0 + num EVM.Types src/EVM/Types.hs:492:1-18 5720 808 0.1 0.0 0.1 0.0 + noop EVM src/EVM.hs:1579:1-14 5721 404 0.0 0.0 0.0 0.0 + r_block EVM.FeeSchedule src/EVM/FeeSchedule.hs:47:5-11 5724 404 0.0 0.0 0.0 0.0 + w256 EVM.Types src/EVM/Types.hs:90:1-24 5719 404 0.0 0.0 0.0 0.0 + touchAccount EVM src/EVM.hs:1895:1-57 5717 0 0.0 0.0 0.1 0.0 + pushTo EVM src/EVM.hs:1582:1-23 5718 404 0.1 0.0 0.1 0.0 + popTrace EVM src/EVM.hs:(2450,1)-(2454,42) 6272 0 0.0 0.0 0.0 0.0 + nextSpace Data.Tree.Zipper Data/Tree/Zipper.hs:153:1-69 6277 291 0.0 0.0 0.0 0.0 + parent Data.Tree.Zipper Data/Tree/Zipper.hs:(124,1)-(132,17) 6275 291 0.0 0.0 0.0 0.0 + parents Data.Tree.Zipper Data/Tree/Zipper.hs:71:1-26 6276 291 0.0 0.0 0.0 0.0 + push EVM src/EVM.hs:2474:1-30 6270 0 0.0 0.0 0.0 0.0 + pushSym EVM src/EVM.hs:2477:1-34 6271 291 0.0 0.0 0.0 0.0 + w256lit EVM.Types src/EVM/Types.hs:346:1-48 6278 291 0.0 0.0 0.0 0.0 + genLiteral Data.SBV.Core.Model Data/SBV/Core/Model.hs:99:1-48 6279 291 0.0 0.0 0.0 0.0 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 6280 291 0.0 0.0 0.0 0.0 + svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 6281 291 0.0 0.0 0.0 0.0 + svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 6282 291 0.0 0.0 0.0 0.0 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 6283 291 0.0 0.0 0.0 0.0 + num EVM.Types src/EVM/Types.hs:492:1-18 6284 0 0.0 0.0 0.0 0.0 + litWord EVM.Symbolic src/EVM/Symbolic.hs:24:1-52 6100 0 0.0 0.0 0.0 0.0 + genLiteral Data.SBV.Core.Model Data/SBV/Core/Model.hs:99:1-48 6101 292 0.0 0.0 0.0 0.0 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 6102 292 0.0 0.0 0.0 0.0 + word EVM.Types src/EVM/Types.hs:521:1-21 5373 0 0.1 0.0 1.2 2.7 + word256 EVM.Types src/EVM/Types.hs:(510,1)-(518,67) 5375 85334 0.5 0.3 1.1 2.7 + padLeft EVM.Types src/EVM/Types.hs:495:1-54 5376 85334 0.4 0.9 0.4 0.9 + bytesRead Data.Serialize.Get src/Data/Serialize/Get.hs:838:1-45 5377 0 0.3 1.5 0.3 1.5 + runUnitTest EVM.UnitTest src/EVM/UnitTest.hs:(178,1)-(180,26) 5316 0 0.0 0.0 0.2 0.1 + execTest EVM.UnitTest src/EVM/UnitTest.hs:(183,1)-(192,19) 5317 0 0.0 0.0 0.2 0.1 + abiCall EVM.UnitTest src/EVM/UnitTest.hs:(842,1)-(845,53) 5321 0 0.0 0.0 0.1 0.1 + makeTxCall EVM.UnitTest src/EVM/UnitTest.hs:(848,1)-(859,17) 5322 0 0.0 0.0 0.1 0.1 + w256 EVM.Types src/EVM/Types.hs:90:1-24 5329 810 0.0 0.0 0.0 0.0 + initTx EVM.Transaction src/EVM/Transaction.hs:(182,1)-(205,47) 5339 405 0.0 0.0 0.1 0.1 + forceLit EVM.Symbolic src/EVM/Symbolic.hs:(40,1)-(42,49) 5420 809 0.0 0.0 0.1 0.0 + genFromCV Data.SBV.Core.Model Data/SBV/Core/Model.hs:(103,1)-(104,95) 5742 651 0.0 0.0 0.1 0.0 + svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 5743 651 0.0 0.0 0.0 0.0 + svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 5744 651 0.0 0.0 0.1 0.0 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 5745 651 0.1 0.0 0.1 0.0 + maybeLitWord EVM.Types src/EVM/Types.hs:324:1-68 5343 405 0.0 0.0 0.0 0.0 + setupTx EVM.Transaction src/EVM/Transaction.hs:(171,1)-(176,38) 5340 405 0.1 0.0 0.1 0.0 + touchAccount EVM.Transaction src/EVM/Transaction.hs:164:1-57 5341 810 0.0 0.0 0.0 0.0 + touchAccount EVM.Transaction src/EVM/Transaction.hs:164:1-57 5342 405 0.0 0.0 0.0 0.0 + loadContract EVM src/EVM.hs:(1794,1)-(1806,44) 5324 0 0.0 0.0 0.0 0.0 + resetState EVM src/EVM.hs:(2210,1)-(2213,26) 5325 0 0.0 0.0 0.0 0.0 + pushTrace EVM src/EVM.hs:(2438,1)-(2441,59) 5331 0 0.1 0.0 0.1 0.0 + children Data.Tree.Zipper Data/Tree/Zipper.hs:(166,1)-(172,7) 5344 405 0.0 0.0 0.0 0.0 + view Control.Monad.Operational src/Control/Monad/Operational.hs:138:1-26 5311 0 0.0 0.0 1.1 0.8 + viewT Control.Monad.Operational src/Control/Monad/Operational.hs:(239,1)-(243,54) 5312 4858 0.0 0.0 1.1 0.8 + execFully EVM.Stepper src/EVM/Stepper.hs:(82,1)-(91,20) 5725 0 0.0 0.0 0.0 0.0 + execTest EVM.UnitTest src/EVM/UnitTest.hs:(183,1)-(192,19) 5727 0 0.0 0.0 0.0 0.0 + pushTrace EVM src/EVM.hs:(2438,1)-(2441,59) 6359 1 0.0 0.0 0.0 0.0 + children Data.Tree.Zipper Data/Tree/Zipper.hs:(166,1)-(172,7) 6424 1 0.0 0.0 0.0 0.0 + withTraceLocation EVM src/EVM.hs:(2426,1)-(2435,5) 6360 1 0.0 0.0 0.0 0.0 + evm EVM.Stepper src/EVM/Stepper.hs:78:1-21 6358 0 0.0 0.0 0.0 0.0 + runUnitTest EVM.UnitTest src/EVM/UnitTest.hs:(178,1)-(180,26) 5333 0 0.0 0.0 1.1 0.8 + checkFailures EVM.UnitTest src/EVM/UnitTest.hs:(195,1)-(210,58) 5728 405 0.1 0.0 1.1 0.8 + abiCall EVM.UnitTest src/EVM/UnitTest.hs:(842,1)-(845,53) 5730 404 0.0 0.0 1.0 0.7 + abiMethod EVM.ABI src/EVM/ABI.hs:(370,1)-(372,13) 5758 404 0.1 0.1 0.8 0.6 + abiKeccak EVM.Types src/EVM/Types.hs:(586,1)-(590,14) 5759 0 0.0 0.0 0.7 0.5 + word32 EVM.Types src/EVM/Types.hs:(576,1)-(577,52) 5787 404 0.0 0.0 0.0 0.0 + keccakBytes EVM.Types src/EVM/Types.hs:(570,1)-(573,15) 5760 0 0.0 0.0 0.7 0.5 + hash Crypto.Hash Crypto/Hash.hs:58:1-47 5761 404 0.0 0.0 0.2 0.0 + hashFinalize Crypto.Hash Crypto/Hash.hs:(92,1)-(95,17) 5762 404 0.0 0.0 0.1 0.0 + allocAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:74:1-45 5771 404 0.1 0.0 0.1 0.0 + new Basement.Block.Base Basement/Block/Base.hs:304:1-76 5772 404 0.0 0.0 0.0 0.0 + unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 5773 404 0.0 0.0 0.0 0.0 + withMutablePtrHint Basement.Block.Base Basement/Block/Base.hs:(475,1)-(489,39) 5774 404 0.0 0.0 0.0 0.0 + copy Data.ByteArray.Methods Data/ByteArray/Methods.hs:(223,1)-(226,21) 5779 404 0.0 0.0 0.0 0.0 + isMutablePinned Basement.Block.Base Basement/Block/Base.hs:100:1-90 5775 404 0.0 0.0 0.0 0.0 + compatIsMutableByteArrayPinned# Basement.Compat.Primitive Basement/Compat/Primitive.hs:70:1-65 5776 404 0.0 0.0 0.0 0.0 + toPinnedStatus# Basement.Compat.Primitive Basement/Compat/Primitive.hs:(47,1)-(48,27) 5777 404 0.0 0.0 0.0 0.0 + unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 5778 404 0.0 0.0 0.0 0.0 + hashInit Crypto.Hash Crypto/Hash.hs:(66,1)-(67,24) 5769 404 0.0 0.0 0.1 0.0 + allocAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:74:1-45 5770 404 0.1 0.0 0.1 0.0 + hashUpdate Crypto.Hash Crypto/Hash.hs:(71,1)-(73,37) 5763 404 0.0 0.0 0.1 0.0 + hashUpdates Crypto.Hash Crypto/Hash.hs:(81,1)-(86,32) 5766 404 0.0 0.0 0.1 0.0 + copyAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:(237,1)-(240,21) 5768 404 0.1 0.0 0.1 0.0 + null Data.ByteArray.Methods Data/ByteArray/Methods.hs:92:1-22 5767 404 0.0 0.0 0.0 0.0 + null Data.ByteArray.Methods Data/ByteArray/Methods.hs:92:1-22 5764 404 0.0 0.0 0.0 0.0 + unpack Data.ByteArray.Methods Data/ByteArray/Methods.hs:(104,1)-(110,34) 5780 404 0.2 0.1 0.5 0.5 + unsafeCast Basement.Block Basement/Block.hs:421:1-32 5781 13332 0.0 0.0 0.0 0.0 + withPtr Basement.Block.Base Basement/Block/Base.hs:(402,1)-(411,31) 5782 12928 0.3 0.3 0.3 0.4 + isPinned Basement.Block.Base Basement/Block/Base.hs:97:1-67 5783 12928 0.0 0.0 0.0 0.0 + compatIsByteArrayPinned# Basement.Compat.Primitive Basement/Compat/Primitive.hs:67:1-51 5784 12928 0.0 0.0 0.0 0.0 + toPinnedStatus# Basement.Compat.Primitive Basement/Compat/Primitive.hs:(47,1)-(48,27) 5785 12928 0.0 0.0 0.0 0.0 + unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 5786 12928 0.0 0.0 0.0 0.0 + putAbi EVM.ABI src/EVM/ABI.hs:(262,1)-(291,15) 5788 0 0.1 0.0 0.1 0.0 + sElems Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:121:30-35 5790 808 0.0 0.0 0.0 0.0 + unId Data.Vector.Fusion.Util Data/Vector/Fusion/Util.hs:25:21-24 5789 808 0.0 0.0 0.0 0.0 + litWord EVM.Symbolic src/EVM/Symbolic.hs:24:1-52 5752 404 0.0 0.0 0.0 0.0 + genLiteral Data.SBV.Core.Model Data/SBV/Core/Model.hs:99:1-48 5753 404 0.0 0.0 0.0 0.0 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 5754 404 0.0 0.0 0.0 0.0 + svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 5755 404 0.0 0.0 0.0 0.0 + svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 5756 404 0.0 0.0 0.0 0.0 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 5757 404 0.0 0.0 0.0 0.0 + makeTxCall EVM.UnitTest src/EVM/UnitTest.hs:(848,1)-(859,17) 5732 404 0.1 0.0 0.3 0.1 + w256 EVM.Types src/EVM/Types.hs:90:1-24 5741 1212 0.0 0.0 0.0 0.0 + initTx EVM.Transaction src/EVM/Transaction.hs:(182,1)-(205,47) 5746 404 0.2 0.0 0.2 0.0 + forceLit EVM.Symbolic src/EVM/Symbolic.hs:(40,1)-(42,49) 5751 808 0.0 0.0 0.0 0.0 + maybeLitWord EVM.Types src/EVM/Types.hs:324:1-68 5750 404 0.0 0.0 0.0 0.0 + setupTx EVM.Transaction src/EVM/Transaction.hs:(171,1)-(176,38) 5747 404 0.0 0.0 0.1 0.0 + touchAccount EVM.Transaction src/EVM/Transaction.hs:164:1-57 5748 808 0.1 0.0 0.1 0.0 + touchAccount EVM.Transaction src/EVM/Transaction.hs:164:1-57 5749 404 0.0 0.0 0.0 0.0 + loadContract EVM src/EVM.hs:(1794,1)-(1806,44) 5733 404 0.0 0.0 0.0 0.0 + litAddr EVM.Symbolic src/EVM/Symbolic.hs:27:1-36 5739 0 0.0 0.0 0.0 0.0 + genLiteral Data.SBV.Core.Model Data/SBV/Core/Model.hs:99:1-48 5740 404 0.0 0.0 0.0 0.0 + resetState EVM src/EVM.hs:(2210,1)-(2213,26) 5734 0 0.0 0.0 0.0 0.0 + num EVM.Types src/EVM/Types.hs:492:1-18 5731 404 0.0 0.0 0.0 0.0 + decodeAbiValue EVM.ABI src/EVM/ABI.hs:364:1-32 5889 0 0.0 0.0 0.0 0.1 + getAbi EVM.ABI src/EVM/ABI.hs:(226,1)-(259,66) 5890 404 0.0 0.0 0.0 0.0 + evm EVM.Stepper src/EVM/Stepper.hs:78:1-21 5729 0 0.0 0.0 0.0 0.0 + popTrace EVM src/EVM.hs:(2450,1)-(2454,42) 5735 0 0.0 0.0 0.0 0.0 + nextSpace Data.Tree.Zipper Data/Tree/Zipper.hs:153:1-69 5738 404 0.0 0.0 0.0 0.0 + parent Data.Tree.Zipper Data/Tree/Zipper.hs:(124,1)-(132,17) 5736 404 0.0 0.0 0.0 0.0 + parents Data.Tree.Zipper Data/Tree/Zipper.hs:71:1-26 5737 404 0.0 0.0 0.0 0.0 + _contractcode EVM src/EVM.hs:331:5-17 5477 405 0.0 0.0 0.0 0.0 + currentContract EVM src/EVM.hs:(443,1)-(444,65) 5475 405 0.0 0.0 0.0 0.0 + dapp EVM.UnitTest src/EVM/UnitTest.hs:87:5-8 5479 405 0.0 0.0 0.0 0.0 + generate Test.QuickCheck.Gen Test/QuickCheck/Gen.hs:(139,1)-(141,20) 5302 405 0.0 0.0 3.2 4.6 + genWithCorpus EVM.UnitTest src/EVM/UnitTest.hs:(217,1)-(224,7) 5472 405 0.0 0.0 3.2 4.6 + mutations EVM.UnitTest src/EVM/UnitTest.hs:89:5-13 5899 800 0.0 0.0 0.0 0.0 + marray# Data.Primitive.Array Data/Primitive/Array.hs:92:5-11 5590 649 0.0 0.0 0.0 0.0 + unId Data.Vector.Fusion.Util Data/Vector/Fusion/Util.hs:25:21-24 5589 649 0.0 0.0 0.0 0.0 + frequency Test.QuickCheck.Gen Test/QuickCheck/Gen.hs:(191,1)-(204,58) 5898 593 0.1 0.0 0.7 0.4 + choose Test.QuickCheck.Gen Test/QuickCheck/Gen.hs:130:1-59 5902 593 0.2 0.0 0.2 0.0 + nextInt System.Random.SplitMix src/System/Random/SplitMix.hs:(160,1)-(164,39) 5903 400 0.0 0.0 0.0 0.0 + nextWord64 System.Random.SplitMix src/System/Random/SplitMix.hs:(128,1)-(130,29) 5904 400 0.0 0.0 0.0 0.0 + splitSMGen System.Random.SplitMix src/System/Random/SplitMix.hs:(232,1)-(236,31) 5901 587 0.0 0.0 0.0 0.0 + mutateAbiValue EVM.Mutate src/EVM/Mutate.hs:(21,1)-(37,86) 5911 567 0.1 0.0 0.2 0.0 + unId Data.Vector.Fusion.Util Data/Vector/Fusion/Util.hs:25:21-24 5912 1134 0.0 0.0 0.0 0.0 + splitSMGen System.Random.SplitMix src/System/Random/SplitMix.hs:(232,1)-(236,31) 5917 573 0.0 0.0 0.0 0.0 + marray# Data.Primitive.Array Data/Primitive/Array.hs:92:5-11 5918 567 0.0 0.0 0.0 0.0 + array# Data.Primitive.Array Data/Primitive/Array.hs:87:5-10 5916 380 0.0 0.0 0.0 0.0 + sChunks Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:122:30-36 5915 187 0.0 0.0 0.0 0.0 + sSize Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:124:30-34 5914 187 0.0 0.0 0.0 0.0 + upperBound Data.Vector.Fusion.Bundle.Size Data/Vector/Fusion/Bundle/Size.hs:(126,1)-(128,30) 5913 187 0.0 0.0 0.0 0.0 + fixAbiUInt EVM.Mutate src/EVM/Mutate.hs:112:1-50 6330 16 0.0 0.0 0.0 0.0 + mutateNum EVM.Mutate src/EVM/Mutate.hs:108:1-92 6324 16 0.0 0.0 0.1 0.0 + choose Test.QuickCheck.Gen Test/QuickCheck/Gen.hs:130:1-59 6327 16 0.1 0.0 0.1 0.0 + nextInt System.Random.SplitMix src/System/Random/SplitMix.hs:(160,1)-(164,39) 6328 81 0.0 0.0 0.0 0.0 + nextWord64 System.Random.SplitMix src/System/Random/SplitMix.hs:(128,1)-(130,29) 6329 81 0.0 0.0 0.0 0.0 + splitSMGen System.Random.SplitMix src/System/Random/SplitMix.hs:(232,1)-(236,31) 6325 16 0.0 0.0 0.0 0.0 + choose Test.QuickCheck.Gen Test/QuickCheck/Gen.hs:130:1-59 6321 0 0.1 0.0 0.1 0.0 + nextInt System.Random.SplitMix src/System/Random/SplitMix.hs:(160,1)-(164,39) 6322 193 0.0 0.0 0.0 0.0 + nextWord64 System.Random.SplitMix src/System/Random/SplitMix.hs:(128,1)-(130,29) 6323 193 0.0 0.0 0.0 0.0 + elements Test.QuickCheck.Gen Test/QuickCheck/Gen.hs:(208,1)-(209,54) 5906 0 0.0 0.0 0.0 0.0 + choose Test.QuickCheck.Gen Test/QuickCheck/Gen.hs:130:1-59 5908 0 0.0 0.0 0.0 0.0 + nextInt System.Random.SplitMix src/System/Random/SplitMix.hs:(160,1)-(164,39) 5909 187 0.0 0.0 0.0 0.0 + nextWord64 System.Random.SplitMix src/System/Random/SplitMix.hs:(128,1)-(130,29) 5910 187 0.0 0.0 0.0 0.0 + genAbiValue EVM.ABI src/EVM/ABI.hs:(440,1)-(466,62) 5919 0 0.0 0.0 0.4 0.3 + splitSMGen System.Random.SplitMix src/System/Random/SplitMix.hs:(232,1)-(236,31) 5920 2319 0.0 0.0 0.0 0.0 + unId Data.Vector.Fusion.Util Data/Vector/Fusion/Util.hs:25:21-24 5924 1053 0.0 0.0 0.0 0.0 + marray# Data.Primitive.Array Data/Primitive/Array.hs:92:5-11 5925 633 0.0 0.0 0.0 0.0 + sSize Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:124:30-34 5922 426 0.0 0.0 0.0 0.0 + sChunks Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:122:30-36 5923 213 0.0 0.0 0.0 0.0 + upperBound Data.Vector.Fusion.Bundle.Size Data/Vector/Fusion/Bundle/Size.hs:(126,1)-(128,30) 5921 213 0.0 0.0 0.0 0.0 + array# Data.Primitive.Array Data/Primitive/Array.hs:87:5-10 5942 207 0.0 0.0 0.0 0.0 + sized Test.QuickCheck.Gen Test/QuickCheck/Gen.hs:99:1-52 5926 207 0.3 0.3 0.4 0.3 + splitSMGen System.Random.SplitMix src/System/Random/SplitMix.hs:(232,1)-(236,31) 5927 840 0.1 0.0 0.1 0.0 + choose Test.QuickCheck.Gen Test/QuickCheck/Gen.hs:130:1-59 5932 420 0.0 0.0 0.0 0.0 + nextInt System.Random.SplitMix src/System/Random/SplitMix.hs:(160,1)-(164,39) 5933 828 0.0 0.0 0.0 0.0 + nextWord64 System.Random.SplitMix src/System/Random/SplitMix.hs:(128,1)-(130,29) 5934 828 0.0 0.0 0.0 0.0 + elements Test.QuickCheck.Gen Test/QuickCheck/Gen.hs:(208,1)-(209,54) 5928 420 0.1 0.0 0.1 0.0 + choose Test.QuickCheck.Gen Test/QuickCheck/Gen.hs:130:1-59 5929 420 0.0 0.0 0.0 0.0 + nextInt System.Random.SplitMix src/System/Random/SplitMix.hs:(160,1)-(164,39) 5930 420 0.0 0.0 0.0 0.0 + nextWord64 System.Random.SplitMix src/System/Random/SplitMix.hs:(128,1)-(130,29) 5931 420 0.0 0.0 0.0 0.0 + hashCall EVM.UnitTest src/EVM/UnitTest.hs:(244,1)-(245,127) 5473 405 2.3 4.2 2.4 4.2 + _creationCodehash EVM.Solidity src/EVM/Solidity.hs:139:5-21 5582 405 0.0 0.0 0.0 0.0 + _runtimeCodehash EVM.Solidity src/EVM/Solidity.hs:138:5-20 5474 405 0.0 0.0 0.0 0.0 + xxhash EVM.UnitTest src/EVM/UnitTest.hs:213:1-26 5583 405 0.1 0.0 0.1 0.0 + sChunks Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:122:30-36 5588 218 0.0 0.0 0.0 0.0 + sSize Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:124:30-34 5587 218 0.0 0.0 0.0 0.0 + upperBound Data.Vector.Fusion.Bundle.Size Data/Vector/Fusion/Bundle/Size.hs:(126,1)-(128,30) 5586 218 0.0 0.0 0.0 0.0 + elements Test.QuickCheck.Gen Test/QuickCheck/Gen.hs:(208,1)-(209,54) 5905 187 0.0 0.0 0.0 0.0 + choose Test.QuickCheck.Gen Test/QuickCheck/Gen.hs:130:1-59 5907 187 0.0 0.0 0.0 0.0 + genAbiValue EVM.ABI src/EVM/ABI.hs:(440,1)-(466,62) 5585 0 0.1 0.0 0.1 0.0 + unId Data.Vector.Fusion.Util Data/Vector/Fusion/Util.hs:25:21-24 5596 245 0.0 0.0 0.0 0.0 + array# Data.Primitive.Array Data/Primitive/Array.hs:87:5-10 5597 224 0.0 0.0 0.0 0.0 + sElems Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:121:30-35 5595 218 0.0 0.0 0.0 0.0 + splitSMGen System.Random.SplitMix src/System/Random/SplitMix.hs:(232,1)-(236,31) 5591 59 0.0 0.0 0.0 0.0 + marray# Data.Primitive.Array Data/Primitive/Array.hs:92:5-11 5598 16 0.0 0.0 0.0 0.0 + sSize Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:124:30-34 5593 10 0.0 0.0 0.0 0.0 + sized Test.QuickCheck.Gen Test/QuickCheck/Gen.hs:99:1-52 5621 6 0.0 0.0 0.0 0.0 + splitSMGen System.Random.SplitMix src/System/Random/SplitMix.hs:(232,1)-(236,31) 5622 22 0.0 0.0 0.0 0.0 + choose Test.QuickCheck.Gen Test/QuickCheck/Gen.hs:130:1-59 5627 11 0.0 0.0 0.0 0.0 + nextInt System.Random.SplitMix src/System/Random/SplitMix.hs:(160,1)-(164,39) 5628 23 0.0 0.0 0.0 0.0 + nextWord64 System.Random.SplitMix src/System/Random/SplitMix.hs:(128,1)-(130,29) 5629 23 0.0 0.0 0.0 0.0 + elements Test.QuickCheck.Gen Test/QuickCheck/Gen.hs:(208,1)-(209,54) 5623 11 0.0 0.0 0.0 0.0 + choose Test.QuickCheck.Gen Test/QuickCheck/Gen.hs:130:1-59 5624 11 0.0 0.0 0.0 0.0 + nextInt System.Random.SplitMix src/System/Random/SplitMix.hs:(160,1)-(164,39) 5625 11 0.0 0.0 0.0 0.0 + nextWord64 System.Random.SplitMix src/System/Random/SplitMix.hs:(128,1)-(130,29) 5626 11 0.0 0.0 0.0 0.0 + sChunks Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:122:30-36 5594 5 0.0 0.0 0.0 0.0 + upperBound Data.Vector.Fusion.Bundle.Size Data/Vector/Fusion/Bundle/Size.hs:(126,1)-(128,30) 5592 5 0.0 0.0 0.0 0.0 + newQCGen Test.QuickCheck.Random Test/QuickCheck/Random.hs:42:1-30 5304 0 0.0 0.0 0.0 0.0 + newSMGen System.Random.SplitMix src/System/Random/SplitMix.hs:382:1-48 5306 0 0.0 0.0 0.0 0.0 + splitSMGen System.Random.SplitMix src/System/Random/SplitMix.hs:(232,1)-(236,31) 5309 405 0.0 0.0 0.0 0.0 + lookupCode EVM.Dapp src/EVM/Dapp.hs:(178,1)-(185,73) 5478 405 0.0 0.0 2.5 0.5 + stripBytecodeMetadata EVM.Solidity src/EVM/Solidity.hs:(569,1)-(573,22) 5487 405 1.8 0.0 1.8 0.0 + keccak EVM.Types src/EVM/Types.hs:(580,1)-(583,12) 5480 0 0.0 0.0 0.7 0.5 + keccakBytes EVM.Types src/EVM/Types.hs:(570,1)-(573,15) 5482 0 0.0 0.0 0.6 0.5 + hash Crypto.Hash Crypto/Hash.hs:58:1-47 5483 405 0.0 0.0 0.1 0.0 + hashFinalize Crypto.Hash Crypto/Hash.hs:(92,1)-(95,17) 5484 405 0.0 0.0 0.0 0.0 + allocAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:74:1-45 5493 405 0.0 0.0 0.0 0.0 + new Basement.Block.Base Basement/Block/Base.hs:304:1-76 5494 405 0.0 0.0 0.0 0.0 + unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 5495 405 0.0 0.0 0.0 0.0 + withMutablePtrHint Basement.Block.Base Basement/Block/Base.hs:(475,1)-(489,39) 5496 405 0.0 0.0 0.0 0.0 + copy Data.ByteArray.Methods Data/ByteArray/Methods.hs:(223,1)-(226,21) 5501 405 0.0 0.0 0.0 0.0 + isMutablePinned Basement.Block.Base Basement/Block/Base.hs:100:1-90 5497 405 0.0 0.0 0.0 0.0 + compatIsMutableByteArrayPinned# Basement.Compat.Primitive Basement/Compat/Primitive.hs:70:1-65 5498 405 0.0 0.0 0.0 0.0 + toPinnedStatus# Basement.Compat.Primitive Basement/Compat/Primitive.hs:(47,1)-(48,27) 5499 405 0.0 0.0 0.0 0.0 + unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 5500 405 0.0 0.0 0.0 0.0 + hashInit Crypto.Hash Crypto/Hash.hs:(66,1)-(67,24) 5491 405 0.0 0.0 0.0 0.0 + allocAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:74:1-45 5492 405 0.0 0.0 0.0 0.0 + hashUpdate Crypto.Hash Crypto/Hash.hs:(71,1)-(73,37) 5485 405 0.0 0.0 0.1 0.0 + hashUpdates Crypto.Hash Crypto/Hash.hs:(81,1)-(86,32) 5488 405 0.0 0.0 0.1 0.0 + copyAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:(237,1)-(240,21) 5490 405 0.1 0.0 0.1 0.0 + null Data.ByteArray.Methods Data/ByteArray/Methods.hs:92:1-22 5489 405 0.0 0.0 0.0 0.0 + null Data.ByteArray.Methods Data/ByteArray/Methods.hs:92:1-22 5486 405 0.0 0.0 0.0 0.0 + unpack Data.ByteArray.Methods Data/ByteArray/Methods.hs:(104,1)-(110,34) 5502 405 0.1 0.1 0.5 0.5 + unsafeCast Basement.Block Basement/Block.hs:421:1-32 5503 13365 0.0 0.0 0.0 0.0 + withPtr Basement.Block.Base Basement/Block/Base.hs:(402,1)-(411,31) 5504 12960 0.5 0.3 0.5 0.4 + isPinned Basement.Block.Base Basement/Block/Base.hs:97:1-67 5505 12960 0.0 0.0 0.0 0.0 + compatIsByteArrayPinned# Basement.Compat.Primitive Basement/Compat/Primitive.hs:67:1-51 5506 12960 0.0 0.0 0.0 0.0 + toPinnedStatus# Basement.Compat.Primitive Basement/Compat/Primitive.hs:(47,1)-(48,27) 5507 12960 0.0 0.0 0.0 0.0 + unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 5508 12960 0.0 0.0 0.0 0.0 + word EVM.Types src/EVM/Types.hs:521:1-21 5481 0 0.0 0.0 0.1 0.0 + word256 EVM.Types src/EVM/Types.hs:(510,1)-(518,67) 5509 405 0.1 0.0 0.1 0.0 + padLeft EVM.Types src/EVM/Types.hs:495:1-54 5510 405 0.0 0.0 0.0 0.0 + bytesRead Data.Serialize.Get src/Data/Serialize/Get.hs:838:1-45 5511 0 0.1 0.0 0.1 0.0 + runUnitTest EVM.UnitTest src/EVM/UnitTest.hs:(178,1)-(180,26) 5313 405 0.0 0.0 0.7 0.8 + execTest EVM.UnitTest src/EVM/UnitTest.hs:(183,1)-(192,19) 5314 405 0.0 0.0 0.7 0.8 + abiCall EVM.UnitTest src/EVM/UnitTest.hs:(842,1)-(845,53) 5318 405 0.0 0.0 0.7 0.8 + abiMethod EVM.ABI src/EVM/ABI.hs:(370,1)-(372,13) 5442 405 0.0 0.1 0.7 0.7 + abiKeccak EVM.Types src/EVM/Types.hs:(586,1)-(590,14) 5443 0 0.0 0.0 0.6 0.5 + word32 EVM.Types src/EVM/Types.hs:(576,1)-(577,52) 5470 405 0.0 0.0 0.0 0.0 + keccakBytes EVM.Types src/EVM/Types.hs:(570,1)-(573,15) 5444 0 0.1 0.0 0.6 0.5 + hash Crypto.Hash Crypto/Hash.hs:58:1-47 5445 405 0.0 0.0 0.2 0.0 + hashFinalize Crypto.Hash Crypto/Hash.hs:(92,1)-(95,17) 5446 405 0.0 0.0 0.2 0.0 + allocAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:74:1-45 5454 405 0.1 0.0 0.2 0.0 + new Basement.Block.Base Basement/Block/Base.hs:304:1-76 5455 405 0.0 0.0 0.0 0.0 + unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 5456 405 0.0 0.0 0.0 0.0 + withMutablePtrHint Basement.Block.Base Basement/Block/Base.hs:(475,1)-(489,39) 5457 405 0.1 0.0 0.1 0.0 + copy Data.ByteArray.Methods Data/ByteArray/Methods.hs:(223,1)-(226,21) 5462 405 0.1 0.0 0.1 0.0 + isMutablePinned Basement.Block.Base Basement/Block/Base.hs:100:1-90 5458 405 0.0 0.0 0.0 0.0 + compatIsMutableByteArrayPinned# Basement.Compat.Primitive Basement/Compat/Primitive.hs:70:1-65 5459 405 0.0 0.0 0.0 0.0 + toPinnedStatus# Basement.Compat.Primitive Basement/Compat/Primitive.hs:(47,1)-(48,27) 5460 405 0.0 0.0 0.0 0.0 + unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 5461 405 0.0 0.0 0.0 0.0 + hashInit Crypto.Hash Crypto/Hash.hs:(66,1)-(67,24) 5452 405 0.0 0.0 0.1 0.0 + allocAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:74:1-45 5453 405 0.1 0.0 0.1 0.0 + hashUpdate Crypto.Hash Crypto/Hash.hs:(71,1)-(73,37) 5447 405 0.0 0.0 0.0 0.0 + hashUpdates Crypto.Hash Crypto/Hash.hs:(81,1)-(86,32) 5449 405 0.0 0.0 0.0 0.0 + copyAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:(237,1)-(240,21) 5451 405 0.0 0.0 0.0 0.0 + null Data.ByteArray.Methods Data/ByteArray/Methods.hs:92:1-22 5450 405 0.0 0.0 0.0 0.0 + null Data.ByteArray.Methods Data/ByteArray/Methods.hs:92:1-22 5448 405 0.0 0.0 0.0 0.0 + unpack Data.ByteArray.Methods Data/ByteArray/Methods.hs:(104,1)-(110,34) 5463 405 0.0 0.1 0.3 0.5 + unsafeCast Basement.Block Basement/Block.hs:421:1-32 5464 13365 0.0 0.0 0.0 0.0 + withPtr Basement.Block.Base Basement/Block/Base.hs:(402,1)-(411,31) 5465 12960 0.3 0.3 0.3 0.4 + isPinned Basement.Block.Base Basement/Block/Base.hs:97:1-67 5466 12960 0.0 0.0 0.0 0.0 + compatIsByteArrayPinned# Basement.Compat.Primitive Basement/Compat/Primitive.hs:67:1-51 5467 12960 0.0 0.0 0.0 0.0 + toPinnedStatus# Basement.Compat.Primitive Basement/Compat/Primitive.hs:(47,1)-(48,27) 5468 12960 0.0 0.0 0.0 0.0 + unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 5469 12960 0.0 0.0 0.0 0.0 + putAbi EVM.ABI src/EVM/ABI.hs:(262,1)-(291,15) 5471 0 0.1 0.1 0.1 0.1 + unId Data.Vector.Fusion.Util Data/Vector/Fusion/Util.hs:25:21-24 5599 2432 0.0 0.0 0.0 0.0 + array# Data.Primitive.Array Data/Primitive/Array.hs:87:5-10 5600 1622 0.0 0.0 0.0 0.0 + sElems Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:121:30-35 5630 810 0.0 0.0 0.0 0.0 + abiValueType EVM.ABI src/EVM/ABI.hs:(200,1)-(210,58) 5604 0 0.0 0.0 0.0 0.0 + litWord EVM.Symbolic src/EVM/Symbolic.hs:24:1-52 5434 405 0.0 0.0 0.0 0.0 + genLiteral Data.SBV.Core.Model Data/SBV/Core/Model.hs:99:1-48 5436 405 0.0 0.0 0.0 0.0 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 5438 405 0.0 0.0 0.0 0.0 + svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 5439 405 0.0 0.0 0.0 0.0 + svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 5440 405 0.0 0.0 0.0 0.0 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 5441 405 0.0 0.0 0.0 0.0 + makeTxCall EVM.UnitTest src/EVM/UnitTest.hs:(848,1)-(859,17) 5320 405 0.0 0.0 0.0 0.0 + loadContract EVM src/EVM.hs:(1794,1)-(1806,44) 5323 405 0.0 0.0 0.0 0.0 + w256 EVM.Types src/EVM/Types.hs:90:1-24 5328 405 0.0 0.0 0.0 0.0 + litAddr EVM.Symbolic src/EVM/Symbolic.hs:27:1-36 5326 0 0.0 0.0 0.0 0.0 + genLiteral Data.SBV.Core.Model Data/SBV/Core/Model.hs:99:1-48 5327 405 0.0 0.0 0.0 0.0 + num EVM.Types src/EVM/Types.hs:492:1-18 5319 405 0.0 0.0 0.0 0.0 + pushTrace EVM src/EVM.hs:(2438,1)-(2441,59) 5330 405 0.0 0.0 0.0 0.0 + withTraceLocation EVM src/EVM.hs:(2426,1)-(2435,5) 5332 405 0.0 0.0 0.0 0.0 + evm EVM.Stepper src/EVM/Stepper.hs:78:1-21 5315 0 0.0 0.0 0.0 0.0 + hashCall EVM.UnitTest src/EVM/UnitTest.hs:(244,1)-(245,127) 5894 404 1.7 4.2 1.7 4.2 + _creationCodehash EVM.Solidity src/EVM/Solidity.hs:139:5-21 5896 404 0.0 0.0 0.0 0.0 + _runtimeCodehash EVM.Solidity src/EVM/Solidity.hs:138:5-20 5895 404 0.0 0.0 0.0 0.0 + xxhash EVM.UnitTest src/EVM/UnitTest.hs:213:1-26 5897 404 0.0 0.0 0.0 0.0 + encodeAbiValue EVM.ABI src/EVM/ABI.hs:361:1-50 6373 0 0.0 0.0 0.0 0.0 + putAbi EVM.ABI src/EVM/ABI.hs:(262,1)-(291,15) 6374 0 0.0 0.0 0.0 0.0 + unId Data.Vector.Fusion.Util Data/Vector/Fusion/Util.hs:25:21-24 6375 8 0.0 0.0 0.0 0.0 + array# Data.Primitive.Array Data/Primitive/Array.hs:87:5-10 6376 6 0.0 0.0 0.0 0.0 + sElems Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:121:30-35 6379 2 0.0 0.0 0.0 0.0 + abiValueType EVM.ABI src/EVM/ABI.hs:(200,1)-(210,58) 6378 0 0.0 0.0 0.0 0.0 + unId Data.Vector.Fusion.Util Data/Vector/Fusion/Util.hs:25:21-24 6366 8 0.0 0.0 0.0 0.0 + marray# Data.Primitive.Array Data/Primitive/Array.hs:92:5-11 6367 4 0.0 0.0 0.0 0.0 + passOutput EVM.UnitTest src/EVM/UnitTest.hs:(741,1)-(753,11) 6420 4 0.0 0.0 0.0 0.0 + array# Data.Primitive.Array Data/Primitive/Array.hs:87:5-10 6388 3 0.0 0.0 0.0 0.0 + failOutput EVM.UnitTest src/EVM/UnitTest.hs:(756,1)-(767,3) 6422 1 0.0 0.0 0.0 0.0 + formatTestLogs EVM.UnitTest src/EVM/UnitTest.hs:(770,1)-(773,47) 6425 1 0.0 0.0 0.0 0.0 + formatTestLog EVM.UnitTest src/EVM/UnitTest.hs:(779,1)-(835,61) 6428 2 0.0 0.0 0.0 0.0 + unindexed EVM.Format src/EVM/Format.hs:174:1-42 6436 3 0.0 0.0 0.0 0.0 + maybeLitWord EVM.Types src/EVM/Types.hs:324:1-68 6429 2 0.0 0.0 0.0 0.0 + genFromCV Data.SBV.Core.Model Data/SBV/Core/Model.hs:(103,1)-(104,95) 6431 2 0.0 0.0 0.0 0.0 + svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 6432 2 0.0 0.0 0.0 0.0 + svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 6433 2 0.0 0.0 0.0 0.0 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 6434 2 0.0 0.0 0.0 0.0 + parenthesise EVM.Format src/EVM/Format.hs:112:1-51 6437 2 0.0 0.0 0.0 0.0 + wordValue EVM.Concrete src/EVM/Concrete.hs:39:1-21 6430 2 0.0 0.0 0.0 0.0 + textValues EVM.Format src/EVM/Format.hs:(105,1)-(109,41) 6452 1 0.0 0.0 0.0 0.0 + getAbiSeq EVM.ABI src/EVM/ABI.hs:(294,1)-(297,56) 6453 1 0.0 0.0 0.0 0.0 + marray# Data.Primitive.Array Data/Primitive/Array.hs:92:5-11 6462 3 0.0 0.0 0.0 0.0 + unId Data.Vector.Fusion.Util Data/Vector/Fusion/Util.hs:25:21-24 6461 3 0.0 0.0 0.0 0.0 + getAbi EVM.ABI src/EVM/ABI.hs:(226,1)-(259,66) 6457 2 0.0 0.0 0.0 0.0 + sChunks Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:122:30-36 6460 1 0.0 0.0 0.0 0.0 + sSize Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:124:30-34 6459 1 0.0 0.0 0.0 0.0 + upperBound Data.Vector.Fusion.Bundle.Size Data/Vector/Fusion/Bundle/Size.hs:(126,1)-(128,30) 6458 1 0.0 0.0 0.0 0.0 + textAbiValues EVM.Format src/EVM/Format.hs:102:1-48 6463 1 0.0 0.0 0.0 0.0 + array# Data.Primitive.Array Data/Primitive/Array.hs:87:5-10 6466 2 0.0 0.0 0.0 0.0 + showAbiValue EVM.Format src/EVM/Format.hs:(83,1)-(96,30) 6467 2 0.0 0.0 0.0 0.0 + formatString EVM.ABI src/EVM/ABI.hs:(146,1)-(149,65) 6468 1 0.0 0.0 0.0 0.0 + toChecksumAddress EVM.Types src/EVM/Types.hs:(412,1)-(415,58) 6470 1 0.0 0.0 0.0 0.0 + unpackNibbles EVM.Types src/EVM/Types.hs:(558,1)-(559,35) 6497 1 0.0 0.0 0.0 0.0 + hi EVM.Types src/EVM/Types.hs:551:1-28 6498 20 0.0 0.0 0.0 0.0 + lo EVM.Types src/EVM/Types.hs:552:1-26 6499 20 0.0 0.0 0.0 0.0 + keccakBytes EVM.Types src/EVM/Types.hs:(570,1)-(573,15) 6471 0 0.0 0.0 0.0 0.0 + hash Crypto.Hash Crypto/Hash.hs:58:1-47 6472 1 0.0 0.0 0.0 0.0 + hashFinalize Crypto.Hash Crypto/Hash.hs:(92,1)-(95,17) 6473 1 0.0 0.0 0.0 0.0 + allocAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:74:1-45 6481 1 0.0 0.0 0.0 0.0 + new Basement.Block.Base Basement/Block/Base.hs:304:1-76 6482 1 0.0 0.0 0.0 0.0 + unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 6483 1 0.0 0.0 0.0 0.0 + withMutablePtrHint Basement.Block.Base Basement/Block/Base.hs:(475,1)-(489,39) 6484 1 0.0 0.0 0.0 0.0 + copy Data.ByteArray.Methods Data/ByteArray/Methods.hs:(223,1)-(226,21) 6489 1 0.0 0.0 0.0 0.0 + isMutablePinned Basement.Block.Base Basement/Block/Base.hs:100:1-90 6485 1 0.0 0.0 0.0 0.0 + compatIsMutableByteArrayPinned# Basement.Compat.Primitive Basement/Compat/Primitive.hs:70:1-65 6486 1 0.0 0.0 0.0 0.0 + toPinnedStatus# Basement.Compat.Primitive Basement/Compat/Primitive.hs:(47,1)-(48,27) 6487 1 0.0 0.0 0.0 0.0 + unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 6488 1 0.0 0.0 0.0 0.0 + hashInit Crypto.Hash Crypto/Hash.hs:(66,1)-(67,24) 6479 1 0.0 0.0 0.0 0.0 + allocAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:74:1-45 6480 1 0.0 0.0 0.0 0.0 + hashUpdate Crypto.Hash Crypto/Hash.hs:(71,1)-(73,37) 6474 1 0.0 0.0 0.0 0.0 + hashUpdates Crypto.Hash Crypto/Hash.hs:(81,1)-(86,32) 6476 1 0.0 0.0 0.0 0.0 + copyAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:(237,1)-(240,21) 6478 1 0.0 0.0 0.0 0.0 + null Data.ByteArray.Methods Data/ByteArray/Methods.hs:92:1-22 6477 1 0.0 0.0 0.0 0.0 + null Data.ByteArray.Methods Data/ByteArray/Methods.hs:92:1-22 6475 1 0.0 0.0 0.0 0.0 + unpack Data.ByteArray.Methods Data/ByteArray/Methods.hs:(104,1)-(110,34) 6490 1 0.0 0.0 0.0 0.0 + unsafeCast Basement.Block Basement/Block.hs:421:1-32 6491 33 0.0 0.0 0.0 0.0 + withPtr Basement.Block.Base Basement/Block/Base.hs:(402,1)-(411,31) 6492 32 0.0 0.0 0.0 0.0 + isPinned Basement.Block.Base Basement/Block/Base.hs:97:1-67 6493 32 0.0 0.0 0.0 0.0 + compatIsByteArrayPinned# Basement.Compat.Primitive Basement/Compat/Primitive.hs:67:1-51 6494 32 0.0 0.0 0.0 0.0 + toPinnedStatus# Basement.Compat.Primitive Basement/Compat/Primitive.hs:(47,1)-(48,27) 6495 32 0.0 0.0 0.0 0.0 + unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 6496 32 0.0 0.0 0.0 0.0 + unId Data.Vector.Fusion.Util Data/Vector/Fusion/Util.hs:25:21-24 6465 2 0.0 0.0 0.0 0.0 + sElems Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:121:30-35 6464 1 0.0 0.0 0.0 0.0 + abiTypeSolidity EVM.ABI src/EVM/ABI.hs:(213,1)-(223,104) 6440 0 0.0 0.0 0.0 0.0 + indentLines EVM.UnitTest src/EVM/UnitTest.hs:(736,1)-(738,45) 6500 1 0.0 0.0 0.0 0.0 + hexText EVM.Types src/EVM/Types.hs:(460,1)-(463,52) 6380 1 0.0 0.0 0.0 0.0 + decode Data.ByteString.Base16 Data/ByteString/Base16.hs:(100,1)-(136,75) 6381 1 0.0 0.0 0.0 0.0 + sChunks Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:122:30-36 6365 1 0.0 0.0 0.0 0.0 + sSize Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:124:30-34 6364 1 0.0 0.0 0.0 0.0 + toChecksumAddress EVM.Types src/EVM/Types.hs:(412,1)-(415,58) 6389 1 0.0 0.0 0.0 0.0 + unpackNibbles EVM.Types src/EVM/Types.hs:(558,1)-(559,35) 6416 1 0.0 0.0 0.0 0.0 + hi EVM.Types src/EVM/Types.hs:551:1-28 6417 20 0.0 0.0 0.0 0.0 + lo EVM.Types src/EVM/Types.hs:552:1-26 6418 20 0.0 0.0 0.0 0.0 + keccakBytes EVM.Types src/EVM/Types.hs:(570,1)-(573,15) 6390 0 0.0 0.0 0.0 0.0 + hash Crypto.Hash Crypto/Hash.hs:58:1-47 6391 1 0.0 0.0 0.0 0.0 + hashFinalize Crypto.Hash Crypto/Hash.hs:(92,1)-(95,17) 6392 1 0.0 0.0 0.0 0.0 + allocAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:74:1-45 6400 1 0.0 0.0 0.0 0.0 + new Basement.Block.Base Basement/Block/Base.hs:304:1-76 6401 1 0.0 0.0 0.0 0.0 + unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 6402 1 0.0 0.0 0.0 0.0 + withMutablePtrHint Basement.Block.Base Basement/Block/Base.hs:(475,1)-(489,39) 6403 1 0.0 0.0 0.0 0.0 + copy Data.ByteArray.Methods Data/ByteArray/Methods.hs:(223,1)-(226,21) 6408 1 0.0 0.0 0.0 0.0 + isMutablePinned Basement.Block.Base Basement/Block/Base.hs:100:1-90 6404 1 0.0 0.0 0.0 0.0 + compatIsMutableByteArrayPinned# Basement.Compat.Primitive Basement/Compat/Primitive.hs:70:1-65 6405 1 0.0 0.0 0.0 0.0 + toPinnedStatus# Basement.Compat.Primitive Basement/Compat/Primitive.hs:(47,1)-(48,27) 6406 1 0.0 0.0 0.0 0.0 + unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 6407 1 0.0 0.0 0.0 0.0 + hashInit Crypto.Hash Crypto/Hash.hs:(66,1)-(67,24) 6398 1 0.0 0.0 0.0 0.0 + allocAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:74:1-45 6399 1 0.0 0.0 0.0 0.0 + hashUpdate Crypto.Hash Crypto/Hash.hs:(71,1)-(73,37) 6393 1 0.0 0.0 0.0 0.0 + hashUpdates Crypto.Hash Crypto/Hash.hs:(81,1)-(86,32) 6395 1 0.0 0.0 0.0 0.0 + copyAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:(237,1)-(240,21) 6397 1 0.0 0.0 0.0 0.0 + null Data.ByteArray.Methods Data/ByteArray/Methods.hs:92:1-22 6396 1 0.0 0.0 0.0 0.0 + null Data.ByteArray.Methods Data/ByteArray/Methods.hs:92:1-22 6394 1 0.0 0.0 0.0 0.0 + unpack Data.ByteArray.Methods Data/ByteArray/Methods.hs:(104,1)-(110,34) 6409 1 0.0 0.0 0.0 0.0 + unsafeCast Basement.Block Basement/Block.hs:421:1-32 6410 33 0.0 0.0 0.0 0.0 + withPtr Basement.Block.Base Basement/Block/Base.hs:(402,1)-(411,31) 6411 32 0.0 0.0 0.0 0.0 + isPinned Basement.Block.Base Basement/Block/Base.hs:97:1-67 6412 32 0.0 0.0 0.0 0.0 + compatIsByteArrayPinned# Basement.Compat.Primitive Basement/Compat/Primitive.hs:67:1-51 6413 32 0.0 0.0 0.0 0.0 + toPinnedStatus# Basement.Compat.Primitive Basement/Compat/Primitive.hs:(47,1)-(48,27) 6414 32 0.0 0.0 0.0 0.0 + unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 6415 32 0.0 0.0 0.0 0.0 + upperBound Data.Vector.Fusion.Bundle.Size Data/Vector/Fusion/Bundle/Size.hs:(126,1)-(128,30) 6363 1 0.0 0.0 0.0 0.0 + decodeAbiValue EVM.ABI src/EVM/ABI.hs:364:1-32 6361 0 0.0 0.0 0.1 0.0 + getAbi EVM.ABI src/EVM/ABI.hs:(226,1)-(259,66) 6362 4 0.0 0.0 0.1 0.0 + unId Data.Vector.Fusion.Util Data/Vector/Fusion/Util.hs:25:21-24 6369 4 0.0 0.0 0.0 0.0 + array# Data.Primitive.Array Data/Primitive/Array.hs:87:5-10 6370 3 0.0 0.0 0.0 0.0 + getAbiSeq EVM.ABI src/EVM/ABI.hs:(294,1)-(297,56) 6368 1 0.1 0.0 0.1 0.0 + marray# Data.Primitive.Array Data/Primitive/Array.hs:92:5-11 6387 4 0.0 0.0 0.0 0.0 + unId Data.Vector.Fusion.Util Data/Vector/Fusion/Util.hs:25:21-24 6386 4 0.0 0.0 0.0 0.0 + sChunks Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:122:30-36 6385 1 0.0 0.0 0.0 0.0 + sSize Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:124:30-34 6384 1 0.0 0.0 0.0 0.0 + upperBound Data.Vector.Fusion.Bundle.Size Data/Vector/Fusion/Bundle/Size.hs:(126,1)-(128,30) 6383 1 0.0 0.0 0.0 0.0 + tick EVM.UnitTest src/EVM/UnitTest.hs:304:1-39 6419 3 0.0 0.0 0.0 0.0 + enter EVM.Stepper src/EVM/Stepper.hs:114:1-48 4276 1 0.0 0.0 0.0 0.0 + pushTrace EVM src/EVM.hs:(2438,1)-(2441,59) 4280 1 0.0 0.0 0.0 0.0 + withTraceLocation EVM src/EVM.hs:(2426,1)-(2435,5) 4283 1 0.0 0.0 0.0 0.0 + evm EVM.Stepper src/EVM/Stepper.hs:78:1-21 4278 0 0.0 0.0 0.0 0.0 + initialUnitTestVm EVM.UnitTest src/EVM/UnitTest.hs:(862,1)-(892,61) 4296 1 0.0 0.0 0.1 0.1 + w256 EVM.Types src/EVM/Types.hs:90:1-24 4394 2 0.0 0.0 0.0 0.0 + berlin EVM.FeeSchedule src/EVM/FeeSchedule.hs:185:1-25 4396 1 0.0 0.0 0.0 0.0 + initialContract EVM src/EVM.hs:(516,1)-(533,39) 4297 1 0.0 0.0 0.1 0.1 + mkCodeOps EVM src/EVM.hs:(2721,1)-(2739,79) 4332 1 0.1 0.1 0.1 0.1 + marray# Data.Primitive.Array Data/Primitive/Array.hs:92:5-11 4339 4345 0.0 0.0 0.0 0.0 + unId Data.Vector.Fusion.Util Data/Vector/Fusion/Util.hs:25:21-24 4338 4345 0.0 0.0 0.0 0.0 + opSize EVM src/EVM.hs:(2542,1)-(2543,37) 4336 4344 0.0 0.0 0.0 0.0 + num EVM.Types src/EVM/Types.hs:492:1-18 4337 1136 0.0 0.0 0.0 0.0 + readOp EVM src/EVM.hs:(2636,1)-(2718,21) 4642 1 0.0 0.0 0.0 0.0 + sChunks Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:122:30-36 4335 1 0.0 0.0 0.0 0.0 + sSize Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:124:30-34 4334 1 0.0 0.0 0.0 0.0 + upperBound Data.Vector.Fusion.Bundle.Size Data/Vector/Fusion/Bundle/Size.hs:(126,1)-(128,30) 4333 1 0.0 0.0 0.0 0.0 + mkOpIxMap EVM src/EVM.hs:(2549,1)-(2586,83) 4330 1 0.0 0.0 0.0 0.0 + len EVM.Symbolic src/EVM/Symbolic.hs:(161,1)-(162,38) 4331 1 0.0 0.0 0.0 0.0 + stripBytecodeMetadata EVM.Solidity src/EVM/Solidity.hs:(569,1)-(573,22) 4305 1 0.0 0.0 0.0 0.0 + keccak EVM.Types src/EVM/Types.hs:(580,1)-(583,12) 4298 0 0.0 0.0 0.0 0.0 + keccakBytes EVM.Types src/EVM/Types.hs:(570,1)-(573,15) 4300 0 0.0 0.0 0.0 0.0 + hash Crypto.Hash Crypto/Hash.hs:58:1-47 4301 1 0.0 0.0 0.0 0.0 + hashFinalize Crypto.Hash Crypto/Hash.hs:(92,1)-(95,17) 4302 1 0.0 0.0 0.0 0.0 + allocAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:74:1-45 4311 1 0.0 0.0 0.0 0.0 + new Basement.Block.Base Basement/Block/Base.hs:304:1-76 4312 1 0.0 0.0 0.0 0.0 + unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 4313 1 0.0 0.0 0.0 0.0 + withMutablePtrHint Basement.Block.Base Basement/Block/Base.hs:(475,1)-(489,39) 4314 1 0.0 0.0 0.0 0.0 + copy Data.ByteArray.Methods Data/ByteArray/Methods.hs:(223,1)-(226,21) 4319 1 0.0 0.0 0.0 0.0 + isMutablePinned Basement.Block.Base Basement/Block/Base.hs:100:1-90 4315 1 0.0 0.0 0.0 0.0 + compatIsMutableByteArrayPinned# Basement.Compat.Primitive Basement/Compat/Primitive.hs:70:1-65 4316 1 0.0 0.0 0.0 0.0 + toPinnedStatus# Basement.Compat.Primitive Basement/Compat/Primitive.hs:(47,1)-(48,27) 4317 1 0.0 0.0 0.0 0.0 + unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 4318 1 0.0 0.0 0.0 0.0 + hashInit Crypto.Hash Crypto/Hash.hs:(66,1)-(67,24) 4309 1 0.0 0.0 0.0 0.0 + allocAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:74:1-45 4310 1 0.0 0.0 0.0 0.0 + hashUpdate Crypto.Hash Crypto/Hash.hs:(71,1)-(73,37) 4303 1 0.0 0.0 0.0 0.0 + hashUpdates Crypto.Hash Crypto/Hash.hs:(81,1)-(86,32) 4306 1 0.0 0.0 0.0 0.0 + copyAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:(237,1)-(240,21) 4308 1 0.0 0.0 0.0 0.0 + null Data.ByteArray.Methods Data/ByteArray/Methods.hs:92:1-22 4307 1 0.0 0.0 0.0 0.0 + null Data.ByteArray.Methods Data/ByteArray/Methods.hs:92:1-22 4304 1 0.0 0.0 0.0 0.0 + unpack Data.ByteArray.Methods Data/ByteArray/Methods.hs:(104,1)-(110,34) 4320 1 0.0 0.0 0.0 0.0 + unsafeCast Basement.Block Basement/Block.hs:421:1-32 4321 33 0.0 0.0 0.0 0.0 + withPtr Basement.Block.Base Basement/Block/Base.hs:(402,1)-(411,31) 4322 32 0.0 0.0 0.0 0.0 + isPinned Basement.Block.Base Basement/Block/Base.hs:97:1-67 4323 32 0.0 0.0 0.0 0.0 + compatIsByteArrayPinned# Basement.Compat.Primitive Basement/Compat/Primitive.hs:67:1-51 4324 32 0.0 0.0 0.0 0.0 + toPinnedStatus# Basement.Compat.Primitive Basement/Compat/Primitive.hs:(47,1)-(48,27) 4325 32 0.0 0.0 0.0 0.0 + unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 4326 32 0.0 0.0 0.0 0.0 + word EVM.Types src/EVM/Types.hs:521:1-21 4299 0 0.0 0.0 0.0 0.0 + word256 EVM.Types src/EVM/Types.hs:(510,1)-(518,67) 4327 1 0.0 0.0 0.0 0.0 + padLeft EVM.Types src/EVM/Types.hs:495:1-54 4328 1 0.0 0.0 0.0 0.0 + bytesRead Data.Serialize.Get src/Data/Serialize/Get.hs:838:1-45 4329 0 0.0 0.0 0.0 0.0 + litWord EVM.Symbolic src/EVM/Symbolic.hs:24:1-52 4393 1 0.0 0.0 0.0 0.0 + makeVm EVM src/EVM.hs:(449,1)-(512,30) 4408 1 0.0 0.0 0.0 0.0 + w256 EVM.Types src/EVM/Types.hs:90:1-24 4415 8 0.0 0.0 0.0 0.0 + vmoptAddress EVM src/EVM.hs:191:5-16 4409 4 0.0 0.0 0.0 0.0 + vmoptContract EVM src/EVM.hs:188:5-17 4411 2 0.0 0.0 0.0 0.0 + vmoptCreate EVM src/EVM.hs:205:5-15 4421 2 0.0 0.0 0.0 0.0 + vmoptValue EVM src/EVM.hs:190:5-14 4413 2 0.0 0.0 0.0 0.0 + _contractcode EVM src/EVM.hs:331:5-17 4410 1 0.0 0.0 0.0 0.0 + fromForest Data.Tree.Zipper Data/Tree/Zipper.hs:222:1-78 4424 1 0.0 0.0 0.0 0.0 + vmoptCalldata EVM src/EVM.hs:189:5-17 4412 1 0.0 0.0 0.0 0.0 + vmoptCaller EVM src/EVM.hs:192:5-15 4414 1 0.0 0.0 0.0 0.0 + vmoptCoinbase EVM src/EVM.hs:198:5-17 4417 1 0.0 0.0 0.0 0.0 + vmoptGas EVM src/EVM.hs:194:5-12 4443 1 0.0 0.0 0.0 0.0 + vmoptGaslimit EVM src/EVM.hs:195:5-17 4757 1 0.0 0.0 0.0 0.0 + vmoptGasprice EVM src/EVM.hs:202:5-17 4892 1 0.0 0.0 0.0 0.0 + vmoptMaxCodeSize EVM src/EVM.hs:200:5-20 4707 1 0.0 0.0 0.0 0.0 + vmoptOrigin EVM src/EVM.hs:193:5-15 4420 1 0.0 0.0 0.0 0.0 + vmoptSchedule EVM src/EVM.hs:203:5-17 4419 1 0.0 0.0 0.0 0.0 + vmoptStorageModel EVM src/EVM.hs:206:5-21 4416 1 0.0 0.0 0.0 0.0 + vmoptTimestamp EVM src/EVM.hs:197:5-18 4418 1 0.0 0.0 0.0 0.0 + vmoptTxAccessList EVM src/EVM.hs:207:5-21 4422 1 0.0 0.0 0.0 0.0 + litAddr EVM.Symbolic src/EVM/Symbolic.hs:27:1-36 4390 0 0.0 0.0 0.0 0.0 + genLiteral Data.SBV.Core.Model Data/SBV/Core/Model.hs:99:1-48 4391 1 0.0 0.0 0.0 0.0 + initializeUnitTest EVM.UnitTest src/EVM/UnitTest.hs:(142,1)-(172,17) 4284 1 0.0 0.0 0.0 0.0 + abiCall EVM.UnitTest src/EVM/UnitTest.hs:(842,1)-(845,53) 4832 1 0.0 0.0 0.0 0.0 + abiMethod EVM.ABI src/EVM/ABI.hs:(370,1)-(372,13) 4922 1 0.0 0.0 0.0 0.0 + abiKeccak EVM.Types src/EVM/Types.hs:(586,1)-(590,14) 4923 0 0.0 0.0 0.0 0.0 + word32 EVM.Types src/EVM/Types.hs:(576,1)-(577,52) 4950 1 0.0 0.0 0.0 0.0 + keccakBytes EVM.Types src/EVM/Types.hs:(570,1)-(573,15) 4924 0 0.0 0.0 0.0 0.0 + hash Crypto.Hash Crypto/Hash.hs:58:1-47 4925 1 0.0 0.0 0.0 0.0 + hashFinalize Crypto.Hash Crypto/Hash.hs:(92,1)-(95,17) 4926 1 0.0 0.0 0.0 0.0 + allocAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:74:1-45 4934 1 0.0 0.0 0.0 0.0 + new Basement.Block.Base Basement/Block/Base.hs:304:1-76 4935 1 0.0 0.0 0.0 0.0 + unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 4936 1 0.0 0.0 0.0 0.0 + withMutablePtrHint Basement.Block.Base Basement/Block/Base.hs:(475,1)-(489,39) 4937 1 0.0 0.0 0.0 0.0 + copy Data.ByteArray.Methods Data/ByteArray/Methods.hs:(223,1)-(226,21) 4942 1 0.0 0.0 0.0 0.0 + isMutablePinned Basement.Block.Base Basement/Block/Base.hs:100:1-90 4938 1 0.0 0.0 0.0 0.0 + compatIsMutableByteArrayPinned# Basement.Compat.Primitive Basement/Compat/Primitive.hs:70:1-65 4939 1 0.0 0.0 0.0 0.0 + toPinnedStatus# Basement.Compat.Primitive Basement/Compat/Primitive.hs:(47,1)-(48,27) 4940 1 0.0 0.0 0.0 0.0 + unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 4941 1 0.0 0.0 0.0 0.0 + hashInit Crypto.Hash Crypto/Hash.hs:(66,1)-(67,24) 4932 1 0.0 0.0 0.0 0.0 + allocAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:74:1-45 4933 1 0.0 0.0 0.0 0.0 + hashUpdate Crypto.Hash Crypto/Hash.hs:(71,1)-(73,37) 4927 1 0.0 0.0 0.0 0.0 + hashUpdates Crypto.Hash Crypto/Hash.hs:(81,1)-(86,32) 4929 1 0.0 0.0 0.0 0.0 + copyAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:(237,1)-(240,21) 4931 1 0.0 0.0 0.0 0.0 + null Data.ByteArray.Methods Data/ByteArray/Methods.hs:92:1-22 4930 1 0.0 0.0 0.0 0.0 + null Data.ByteArray.Methods Data/ByteArray/Methods.hs:92:1-22 4928 1 0.0 0.0 0.0 0.0 + unpack Data.ByteArray.Methods Data/ByteArray/Methods.hs:(104,1)-(110,34) 4943 1 0.0 0.0 0.0 0.0 + unsafeCast Basement.Block Basement/Block.hs:421:1-32 4944 33 0.0 0.0 0.0 0.0 + withPtr Basement.Block.Base Basement/Block/Base.hs:(402,1)-(411,31) 4945 32 0.0 0.0 0.0 0.0 + isPinned Basement.Block.Base Basement/Block/Base.hs:97:1-67 4946 32 0.0 0.0 0.0 0.0 + compatIsByteArrayPinned# Basement.Compat.Primitive Basement/Compat/Primitive.hs:67:1-51 4947 32 0.0 0.0 0.0 0.0 + toPinnedStatus# Basement.Compat.Primitive Basement/Compat/Primitive.hs:(47,1)-(48,27) 4948 32 0.0 0.0 0.0 0.0 + unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 4949 32 0.0 0.0 0.0 0.0 + putAbi EVM.ABI src/EVM/ABI.hs:(262,1)-(291,15) 4952 0 0.0 0.0 0.0 0.0 + sElems Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:121:30-35 4960 2 0.0 0.0 0.0 0.0 + unId Data.Vector.Fusion.Util Data/Vector/Fusion/Util.hs:25:21-24 4959 2 0.0 0.0 0.0 0.0 + litWord EVM.Symbolic src/EVM/Symbolic.hs:24:1-52 4912 1 0.0 0.0 0.0 0.0 + genLiteral Data.SBV.Core.Model Data/SBV/Core/Model.hs:99:1-48 4916 1 0.0 0.0 0.0 0.0 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 4918 1 0.0 0.0 0.0 0.0 + svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 4919 1 0.0 0.0 0.0 0.0 + svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 4920 1 0.0 0.0 0.0 0.0 + mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 4921 1 0.0 0.0 0.0 0.0 + makeTxCall EVM.UnitTest src/EVM/UnitTest.hs:(848,1)-(859,17) 4834 1 0.0 0.0 0.0 0.0 + loadContract EVM src/EVM.hs:(1794,1)-(1806,44) 4838 1 0.0 0.0 0.0 0.0 + w256 EVM.Types src/EVM/Types.hs:90:1-24 4890 1 0.0 0.0 0.0 0.0 + litAddr EVM.Symbolic src/EVM/Symbolic.hs:27:1-36 4888 0 0.0 0.0 0.0 0.0 + genLiteral Data.SBV.Core.Model Data/SBV/Core/Model.hs:99:1-48 4889 1 0.0 0.0 0.0 0.0 + num EVM.Types src/EVM/Types.hs:492:1-18 4833 1 0.0 0.0 0.0 0.0 + testAddress EVM.UnitTest src/EVM/UnitTest.hs:94:5-15 4841 1 0.0 0.0 0.0 0.0 + testBalanceCreate EVM.UnitTest src/EVM/UnitTest.hs:99:5-21 5097 1 0.0 0.0 0.0 0.0 + w256 EVM.Types src/EVM/Types.hs:90:1-24 4887 1 0.0 0.0 0.0 0.0 + evm EVM.Stepper src/EVM/Stepper.hs:78:1-21 4285 0 0.0 0.0 0.0 0.0 + dsatPrecision Data.SBV.Core.Symbolic Data/SBV/Core/Symbolic.hs:1839:10-22 3637 1 0.0 0.0 0.0 0.0 + engine Data.SBV.Core.Symbolic Data/SBV/Core/Symbolic.hs:1914:10-15 3642 1 0.0 0.0 0.0 0.0 + standardEngine Data.SBV.SMT.SMT Data/SBV/SMT/SMT.hs:(628,1)-(635,44) 3645 1 0.0 0.0 0.0 0.0 + solver Data.SBV.Core.Symbolic Data/SBV/Core/Symbolic.hs:1840:10-15 3694 22 0.0 0.0 0.0 0.0 + capabilities Data.SBV.Core.Symbolic Data/SBV/Core/Symbolic.hs:1915:10-21 3701 18 0.0 0.0 0.0 0.0 + debug Data.SBV.SMT.Utils Data/SBV/SMT/Utils.hs:(103,1)-(106,59) 3646 18 0.0 0.0 0.0 0.0 + verbose Data.SBV.Core.Symbolic Data/SBV/Core/Symbolic.hs:1826:10-16 3647 18 0.0 0.0 0.0 0.0 + supportsCustomQueries Data.SBV.Core.Symbolic Data/SBV/Core/Symbolic.hs:1783:10-30 3700 17 0.0 0.0 0.0 0.0 + mergeSExpr Data.SBV.SMT.Utils Data/SBV/SMT/Utils.hs:(111,1)-(138,28) 3708 15 0.0 0.0 0.0 0.0 + transcript Data.SBV.Core.Symbolic Data/SBV/Core/Symbolic.hs:1837:10-19 3699 11 0.0 0.0 0.0 0.0 + executable Data.SBV.Core.Symbolic Data/SBV/Core/Symbolic.hs:1911:10-19 3693 2 0.0 0.0 0.0 0.0 + extraArgs Data.SBV.Core.Symbolic Data/SBV/Core/Symbolic.hs:1841:10-18 3698 1 0.0 0.0 0.0 0.0 + options Data.SBV.Core.Symbolic Data/SBV/Core/Symbolic.hs:1913:10-16 3695 1 0.0 0.0 0.0 0.0 + preprocess Data.SBV.Core.Symbolic Data/SBV/Core/Symbolic.hs:1912:10-19 3703 1 0.0 0.0 0.0 0.0 + cvc4 Data.SBV.Provers.CVC4 Data/SBV/Provers/CVC4.hs:(27,1)-(64,25) 3704 0 0.0 0.0 0.0 0.0 + rQueryState Data.SBV.Core.Symbolic Data/SBV/Core/Symbolic.hs:958:23-33 3709 1 0.0 0.0 0.0 0.0 + supportsGlobalDecls Data.SBV.Core.Symbolic Data/SBV/Core/Symbolic.hs:1784:10-28 3707 1 0.0 0.0 0.0 0.0 + parenDeficit Data.SBV.Utils.SExpr Data/SBV/Utils/SExpr.hs:(82,1)-(87,54) 3706 0 0.0 0.0 0.0 0.0 + splitArgs Data.SBV.Utils.Lib Data/SBV/Utils/Lib.hs:(88,1)-(108,40) 3697 0 0.0 0.0 0.0 0.0 + isRunIStage Data.SBV.Core.Symbolic Data/SBV/Core/Symbolic.hs:(856,1)-(859,32) 3636 1 0.0 0.0 0.0 0.0 + optsMode Main hevm-cli/hevm-cli.hs:241:1-78 3941 1 0.0 0.0 0.0 0.0 + debug Main hevm-cli/hevm-cli.hs:124:9-13 3942 1 0.0 0.0 0.0 0.0 + jsontrace Main hevm-cli/hevm-cli.hs:161:9-17 3943 1 0.0 0.0 0.0 0.0 + rSMTOptions Data.SBV.Core.Symbolic Data/SBV/Core/Symbolic.hs:952:23-33 3641 1 0.0 0.0 0.0 0.0 + rinps Data.SBV.Core.Symbolic Data/SBV/Core/Symbolic.hs:938:23-27 3635 1 0.0 0.0 0.0 0.0 + runProofOn Data.SBV.Control.Utils Data/SBV/Control/Utils.hs:(1433,1)-(1463,126) 3649 1 0.0 0.0 0.0 0.0 + isSafetyCheckingIStage Data.SBV.Core.Symbolic Data/SBV/Core/Symbolic.hs:(842,1)-(845,44) 3691 1 0.0 0.0 0.0 0.0 + isSetupIStage Data.SBV.Core.Symbolic Data/SBV/Core/Symbolic.hs:(849,1)-(852,33) 3692 1 0.0 0.0 0.0 0.0 + toSMTLib Data.SBV.SMT.SMTLib Data/SBV/SMT/SMTLib.hs:(31,1)-(32,58) 3650 1 0.0 0.0 0.0 0.0 + cvt Data.SBV.SMT.SMTLib2 Data/SBV/SMT/SMTLib2.hs:(44,1)-(328,31) 3651 1 0.0 0.0 0.0 0.0 + solverSetOptions Data.SBV.Core.Symbolic Data/SBV/Core/Symbolic.hs:1844:10-25 3652 2 0.0 0.0 0.0 0.0 + biplateData Data.Generics.Uniplate.Internal.Data Data/Generics/Uniplate/Internal/Data.hs:(299,1)-(302,27) 3658 1 0.0 0.0 0.0 0.0 + fromOracle Data.Generics.Uniplate.Internal.Data Data/Generics/Uniplate/Internal/Data.hs:115:26-35 3659 1 0.0 0.0 0.0 0.0 + uniplateData Data.Generics.Uniplate.Internal.Data Data/Generics/Uniplate/Internal/Data.hs:(306,1)-(313,36) 3687 1 0.0 0.0 0.0 0.0 + fromC Data.Generics.Uniplate.Internal.Data Data/Generics/Uniplate/Internal/Data.hs:293:20-24 3688 1 0.0 0.0 0.0 0.0 + needsFlattening Data.SBV.Core.Kind Data/SBV/Core/Kind.hs:(355,1)-(368,34) 3656 1 0.0 0.0 0.0 0.0 + typeKey Data.Generics.Uniplate.Internal.Data Data/Generics/Uniplate/Internal/Data.hs:65:1-16 3685 1 0.0 0.0 0.0 0.0 + setSMTOption Data.SBV.Control.Types Data/SBV/Control/Types.hs:(159,1)-(178,57) 3655 0 0.0 0.0 0.0 0.0 + solver Data.SBV.Core.Symbolic Data/SBV/Core/Symbolic.hs:1840:10-15 3643 1 0.0 0.0 0.0 0.0 + solverSetOptions Data.SBV.Core.Symbolic Data/SBV/Core/Symbolic.hs:1844:10-25 3653 1 0.0 0.0 0.0 0.0 + extractSymbolicSimulationState Data.SBV.Core.Symbolic Data/SBV/Core/Symbolic.hs:(1545,1)-(1570,125) 3639 0 0.0 0.0 0.0 0.0 + rconstMap Data.SBV.Core.Symbolic Data/SBV/Core/Symbolic.hs:945:23-31 3640 1 0.0 0.0 0.0 0.0 + unitTestOptions Main hevm-cli/hevm-cli.hs:(262,1)-(304,5) 3711 0 0.0 0.0 5.8 8.5 + dappInfo EVM.Dapp src/EVM/Dapp.hs:(68,1)-(95,5) 4119 1 0.0 0.0 0.0 0.0 + dappRoot Main hevm-cli/hevm-cli.hs:120:9-16 4121 1 0.0 0.0 0.0 0.0 + getParametersFromEnvironmentVariables EVM.UnitTest src/EVM/UnitTest.hs:(910,1)-(942,38) 3938 0 0.0 0.0 0.0 0.0 + readSolc EVM.Solidity src/EVM/Solidity.hs:(297,1)-(303,47) 3713 0 0.1 0.1 5.8 8.5 + readTextDevice Data.Text.Internal.IO libraries/text/Data/Text/Internal/IO.hs:133:39-64 3714 393 0.2 0.0 0.2 0.0 + readJSON EVM.Solidity src/EVM/Solidity.hs:(329,1)-(331,28) 3715 1 0.0 0.1 5.5 8.3 + lazy Control.Lens.Iso src/Control/Lens/Iso.hs:569:1-18 3716 1 0.0 0.0 1.7 2.4 + hash Data.HashMap.Base Data/HashMap/Base.hs:166:1-28 3840 1 0.0 0.0 0.0 0.0 + hashByteArrayWithSalt Data.Hashable.Class Data/Hashable/Class.hs:(770,1)-(772,20) 3841 1 0.0 0.0 0.0 0.0 + maybeResult Data.Attoparsec.ByteString.Lazy Data/Attoparsec/ByteString/Lazy.hs:(103,1)-(104,32) 3717 1 0.0 0.0 0.0 0.0 + parse Data.Attoparsec.ByteString.Lazy Data/Attoparsec/ByteString/Lazy.hs:(88,1)-(95,56) 3718 1 0.0 0.0 1.7 2.4 + runParser Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:111:7-15 3719 16 0.0 0.0 0.0 0.0 + fromPos Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:46:21-27 3722 3 0.0 0.0 0.0 0.0 + buffer Data.Attoparsec.ByteString.Buffer Data/Attoparsec/ByteString/Buffer.hs:85:1-45 3721 1 0.0 0.0 0.0 0.0 + value Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:196:1-36 3724 0 0.0 0.0 1.7 2.4 + array_ Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:169:35-59 3733 0 0.0 0.1 0.3 0.3 + runParser Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:111:7-15 3734 75877 0.0 0.0 0.0 0.0 + fromPos Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:46:21-27 3735 15377 0.0 0.0 0.0 0.0 + marray# Data.Primitive.Array Data/Primitive/Array.hs:92:5-11 3783 23 0.0 0.0 0.0 0.0 + unId Data.Vector.Fusion.Util Data/Vector/Fusion/Util.hs:25:21-24 3782 15 0.0 0.0 0.0 0.0 + sChunks Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:122:30-36 3781 6 0.0 0.0 0.0 0.0 + sSize Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:124:30-34 3780 6 0.0 0.0 0.0 0.0 + upperBound Data.Vector.Fusion.Bundle.Size Data/Vector/Fusion/Bundle/Size.hs:(126,1)-(128,30) 3779 6 0.0 0.0 0.0 0.0 + jstring Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:317:1-32 3751 0 0.2 0.1 0.2 0.1 + runParser Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:111:7-15 3752 123205 0.0 0.0 0.0 0.0 + fromPos Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:46:21-27 3753 20305 0.0 0.0 0.0 0.0 + fromList Data.HashMap.Strict.Base Data/HashMap/Strict/Base.hs:598:1-64 3787 0 0.0 0.0 0.0 0.0 + unsafeInsert Data.HashMap.Base Data/HashMap/Base.hs:(784,1)-(814,76) 3789 9 0.0 0.0 0.0 0.0 + hash Data.HashMap.Base Data/HashMap/Base.hs:166:1-28 3790 9 0.0 0.0 0.0 0.0 + hashByteArrayWithSalt Data.Hashable.Class Data/Hashable/Class.hs:(770,1)-(772,20) 3791 9 0.0 0.0 0.0 0.0 + copy Data.HashMap.Array Data/HashMap/Array.hs:(328,1)-(333,30) 3798 8 0.0 0.0 0.0 0.0 + sparseIndex Data.HashMap.Base Data/HashMap/Base.hs:1867:1-42 3799 5 0.0 0.0 0.0 0.0 + new_ Data.HashMap.Array Data/HashMap/Array.hs:256:1-28 3797 4 0.0 0.0 0.0 0.0 + jstringSlow Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:(333,44)-(337,31) 3765 0 0.0 0.0 0.0 0.0 + object_ Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:132:46-89 3754 0 0.0 0.0 0.0 0.0 + runParser Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:111:7-15 3755 335 0.0 0.0 0.0 0.0 + marray# Data.Primitive.Array Data/Primitive/Array.hs:92:5-11 3796 80 0.0 0.0 0.0 0.0 + fromPos Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:46:21-27 3756 65 0.0 0.0 0.0 0.0 + unId Data.Vector.Fusion.Util Data/Vector/Fusion/Util.hs:25:21-24 3795 28 0.0 0.0 0.0 0.0 + sChunks Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:122:30-36 3794 2 0.0 0.0 0.0 0.0 + sSize Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:124:30-34 3793 2 0.0 0.0 0.0 0.0 + upperBound Data.Vector.Fusion.Bundle.Size Data/Vector/Fusion/Bundle/Size.hs:(126,1)-(128,30) 3792 2 0.0 0.0 0.0 0.0 + scientific Data.Scientific src/Data/Scientific.hs:174:1-23 3788 0 0.0 0.0 0.0 0.0 + jstringSlow Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:(333,44)-(337,31) 3766 0 0.0 0.0 0.0 0.0 + runParser Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:111:7-15 3769 16 0.0 0.0 0.0 0.0 + fromPos Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:46:21-27 3770 3 0.0 0.0 0.0 0.0 + object_ Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:132:46-89 3767 0 0.0 0.0 0.0 0.0 + jstring Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:317:1-32 3768 0 0.0 0.0 0.0 0.0 + object_ Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:132:46-89 3739 0 0.0 0.0 0.2 0.2 + runParser Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:111:7-15 3749 2467 0.0 0.0 0.0 0.0 + fromPos Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:46:21-27 3750 481 0.0 0.0 0.0 0.0 + marray# Data.Primitive.Array Data/Primitive/Array.hs:92:5-11 3804 7 0.0 0.0 0.0 0.0 + unId Data.Vector.Fusion.Util Data/Vector/Fusion/Util.hs:25:21-24 3803 3 0.0 0.0 0.0 0.0 + sChunks Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:122:30-36 3802 1 0.0 0.0 0.0 0.0 + sSize Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:124:30-34 3801 1 0.0 0.0 0.0 0.0 + upperBound Data.Vector.Fusion.Bundle.Size Data/Vector/Fusion/Bundle/Size.hs:(126,1)-(128,30) 3800 1 0.0 0.0 0.0 0.0 + jstring Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:317:1-32 3740 0 0.2 0.2 0.2 0.2 + runParser Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:111:7-15 3741 184758 0.0 0.0 0.0 0.0 + fromPos Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:46:21-27 3742 31081 0.0 0.0 0.0 0.0 + fromList Data.HashMap.Strict.Base Data/HashMap/Strict/Base.hs:598:1-64 3773 0 0.0 0.0 0.0 0.0 + unsafeInsert Data.HashMap.Base Data/HashMap/Base.hs:(784,1)-(814,76) 3776 26 0.0 0.0 0.0 0.0 + hash Data.HashMap.Base Data/HashMap/Base.hs:166:1-28 3777 26 0.0 0.0 0.0 0.0 + hashByteArrayWithSalt Data.Hashable.Class Data/Hashable/Class.hs:(770,1)-(772,20) 3778 26 0.0 0.0 0.0 0.0 + copy Data.HashMap.Array Data/HashMap/Array.hs:(328,1)-(333,30) 3785 20 0.0 0.0 0.0 0.0 + sparseIndex Data.HashMap.Base Data/HashMap/Base.hs:1867:1-42 3786 12 0.0 0.0 0.0 0.0 + new_ Data.HashMap.Array Data/HashMap/Array.hs:256:1-28 3784 10 0.0 0.0 0.0 0.0 + jstringSlow Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:(333,44)-(337,31) 3764 0 0.0 0.0 0.0 0.0 + scientific Data.Scientific src/Data/Scientific.hs:174:1-23 3775 0 0.0 0.0 0.0 0.0 + fromList Data.HashMap.Strict.Base Data/HashMap/Strict/Base.hs:598:1-64 3772 0 0.0 0.0 0.0 0.0 + unsafeInsert Data.HashMap.Base Data/HashMap/Base.hs:(784,1)-(814,76) 3805 2 0.0 0.0 0.0 0.0 + hash Data.HashMap.Base Data/HashMap/Base.hs:166:1-28 3806 2 0.0 0.0 0.0 0.0 + hashByteArrayWithSalt Data.Hashable.Class Data/Hashable/Class.hs:(770,1)-(772,20) 3807 2 0.0 0.0 0.0 0.0 + object_ Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:132:46-89 3725 0 0.1 0.1 1.4 2.1 + runParser Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:111:7-15 3726 80825 0.0 0.0 0.0 0.0 + fromPos Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:46:21-27 3727 17308 0.0 0.0 0.0 0.0 + array_ Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:169:35-59 3743 0 0.0 0.0 0.0 0.0 + jstring Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:317:1-32 3729 0 0.9 1.5 1.3 2.0 + runParser Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:111:7-15 3730 1858836 0.0 0.0 0.0 0.0 + fromPos Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:46:21-27 3731 309351 0.0 0.0 0.0 0.0 + jstringSlow Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:(333,44)-(337,31) 3757 207 0.1 0.0 0.1 0.2 + runParser Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:111:7-15 3758 17077 0.0 0.0 0.0 0.0 + fromPos Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:46:21-27 3759 2739 0.0 0.0 0.0 0.0 + array_ Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:169:35-59 3761 0 0.0 0.1 0.0 0.1 + runParser Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:111:7-15 3762 105487 0.0 0.0 0.0 0.0 + fromPos Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:46:21-27 3763 17284 0.0 0.0 0.0 0.0 + unescapeText Data.Aeson.Parser.UnescapePure pure/Data/Aeson/Parser/UnescapePure.hs:254:1-70 3760 0 0.0 0.0 0.0 0.0 + array_ Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:169:35-59 3736 0 0.4 0.3 0.4 0.4 + runParser Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:111:7-15 3737 304197 0.0 0.0 0.0 0.0 + fromPos Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:46:21-27 3738 49863 0.0 0.0 0.0 0.0 + marray# Data.Primitive.Array Data/Primitive/Array.hs:92:5-11 3824 145 0.0 0.0 0.0 0.0 + unId Data.Vector.Fusion.Util Data/Vector/Fusion/Util.hs:25:21-24 3823 57 0.0 0.0 0.0 0.0 + sChunks Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:122:30-36 3822 8 0.0 0.0 0.0 0.0 + sSize Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:124:30-34 3821 8 0.0 0.0 0.0 0.0 + upperBound Data.Vector.Fusion.Bundle.Size Data/Vector/Fusion/Bundle/Size.hs:(126,1)-(128,30) 3820 8 0.0 0.0 0.0 0.0 + jstringSlow Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:(333,44)-(337,31) 3744 5 0.0 0.0 0.1 0.1 + runParser Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:111:7-15 3745 1383 0.0 0.0 0.0 0.0 + fromPos Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:46:21-27 3746 221 0.0 0.0 0.0 0.0 + fromList Data.HashMap.Strict.Base Data/HashMap/Strict/Base.hs:598:1-64 3808 0 0.0 0.0 0.0 0.0 + unsafeInsert Data.HashMap.Base Data/HashMap/Base.hs:(784,1)-(814,76) 3825 18 0.0 0.0 0.0 0.0 + hash Data.HashMap.Base Data/HashMap/Base.hs:166:1-28 3826 18 0.0 0.0 0.0 0.0 + hashByteArrayWithSalt Data.Hashable.Class Data/Hashable/Class.hs:(770,1)-(772,20) 3827 18 0.0 0.0 0.0 0.0 + copy Data.HashMap.Array Data/HashMap/Array.hs:(328,1)-(333,30) 3837 14 0.0 0.0 0.0 0.0 + new_ Data.HashMap.Array Data/HashMap/Array.hs:256:1-28 3836 7 0.0 0.0 0.0 0.0 + sparseIndex Data.HashMap.Base Data/HashMap/Base.hs:1867:1-42 3838 7 0.0 0.0 0.0 0.0 + unescapeText Data.Aeson.Parser.UnescapePure pure/Data/Aeson/Parser/UnescapePure.hs:254:1-70 3748 0 0.1 0.1 0.1 0.1 + fromList Data.HashMap.Strict.Base Data/HashMap/Strict/Base.hs:598:1-64 3809 0 0.0 0.0 0.0 0.0 + unsafeInsert Data.HashMap.Base Data/HashMap/Base.hs:(784,1)-(814,76) 3817 30 0.0 0.0 0.0 0.0 + hash Data.HashMap.Base Data/HashMap/Base.hs:166:1-28 3818 30 0.0 0.0 0.0 0.0 + hashByteArrayWithSalt Data.Hashable.Class Data/Hashable/Class.hs:(770,1)-(772,20) 3819 30 0.0 0.0 0.0 0.0 + copy Data.HashMap.Array Data/HashMap/Array.hs:(328,1)-(333,30) 3829 18 0.0 0.0 0.0 0.0 + sparseIndex Data.HashMap.Base Data/HashMap/Base.hs:1867:1-42 3830 12 0.0 0.0 0.0 0.0 + new_ Data.HashMap.Array Data/HashMap/Array.hs:256:1-28 3828 9 0.0 0.0 0.0 0.0 + fromList Data.HashMap.Strict.Base Data/HashMap/Strict/Base.hs:598:1-64 3810 0 0.0 0.0 0.0 0.0 + unsafeInsert Data.HashMap.Base Data/HashMap/Base.hs:(784,1)-(814,76) 3811 47 0.0 0.0 0.0 0.0 + hash Data.HashMap.Base Data/HashMap/Base.hs:166:1-28 3812 47 0.0 0.0 0.0 0.0 + hashByteArrayWithSalt Data.Hashable.Class Data/Hashable/Class.hs:(770,1)-(772,20) 3813 47 0.0 0.0 0.0 0.0 + copy Data.HashMap.Array Data/HashMap/Array.hs:(328,1)-(333,30) 3815 38 0.0 0.0 0.0 0.0 + sparseIndex Data.HashMap.Base Data/HashMap/Base.hs:1867:1-42 3816 22 0.0 0.0 0.0 0.0 + new_ Data.HashMap.Array Data/HashMap/Array.hs:256:1-28 3814 19 0.0 0.0 0.0 0.0 + readStdJSON EVM.Solidity src/EVM/Solidity.hs:(364,1)-(407,39) 3842 1 0.1 0.2 3.8 5.8 + sparseIndex Data.HashMap.Base Data/HashMap/Base.hs:1867:1-42 3930 417 0.0 0.0 0.0 0.0 + hash Data.HashMap.Base Data/HashMap/Base.hs:166:1-28 3926 415 0.0 0.0 0.0 0.0 + hashByteArrayWithSalt Data.Hashable.Class Data/Hashable/Class.hs:(770,1)-(772,20) 3927 415 0.0 0.0 0.0 0.0 + unId Data.Vector.Fusion.Util Data/Vector/Fusion/Util.hs:25:21-24 5545 152 0.0 0.0 0.0 0.0 + array# Data.Primitive.Array Data/Primitive/Array.hs:87:5-10 5546 127 0.0 0.0 0.0 0.0 + signature EVM.Solidity src/EVM/Solidity.hs:(468,1)-(478,7) 5553 83 0.0 0.0 0.0 0.0 + hash Data.HashMap.Base Data/HashMap/Base.hs:166:1-28 5554 364 0.0 0.0 0.0 0.0 + hashByteArrayWithSalt Data.Hashable.Class Data/Hashable/Class.hs:(770,1)-(772,20) 5555 364 0.0 0.0 0.0 0.0 + sparseIndex Data.HashMap.Base Data/HashMap/Base.hs:1867:1-42 5556 364 0.0 0.0 0.0 0.0 + unId Data.Vector.Fusion.Util Data/Vector/Fusion/Util.hs:25:21-24 5557 198 0.0 0.0 0.0 0.0 + array# Data.Primitive.Array Data/Primitive/Array.hs:87:5-10 5580 115 0.0 0.0 0.0 0.0 + decode Data.ByteString.Base16 Data/ByteString/Base16.hs:(100,1)-(136,75) 5520 6 0.0 0.0 0.0 0.0 + stripBytecodeMetadata EVM.Solidity src/EVM/Solidity.hs:(569,1)-(573,22) 5519 6 0.0 0.0 0.0 0.0 + lazy Control.Lens.Iso src/Control/Lens/Iso.hs:569:1-18 3843 5 0.1 0.0 3.3 4.9 + hash Data.HashMap.Base Data/HashMap/Base.hs:166:1-28 3923 5 0.0 0.0 0.0 0.0 + hashByteArrayWithSalt Data.Hashable.Class Data/Hashable/Class.hs:(770,1)-(772,20) 3924 5 0.0 0.0 0.0 0.0 + maybeResult Data.Attoparsec.ByteString.Lazy Data/Attoparsec/ByteString/Lazy.hs:(103,1)-(104,32) 3844 5 0.0 0.0 0.0 0.0 + parse Data.Attoparsec.ByteString.Lazy Data/Attoparsec/ByteString/Lazy.hs:(88,1)-(95,56) 3845 5 0.0 0.0 3.3 4.9 + runParser Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:111:7-15 3846 80 0.0 0.0 0.0 0.0 + fromPos Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:46:21-27 3848 15 0.0 0.0 0.0 0.0 + buffer Data.Attoparsec.ByteString.Buffer Data/Attoparsec/ByteString/Buffer.hs:85:1-45 3847 5 0.0 0.0 0.0 0.0 + value Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:196:1-36 3849 0 0.0 0.0 3.3 4.9 + array_ Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:169:35-59 3856 0 0.2 0.2 0.7 0.7 + runParser Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:111:7-15 3857 155263 0.0 0.0 0.0 0.0 + fromPos Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:46:21-27 3858 31458 0.0 0.0 0.0 0.0 + marray# Data.Primitive.Array Data/Primitive/Array.hs:92:5-11 3902 102 0.0 0.0 0.0 0.0 + unId Data.Vector.Fusion.Util Data/Vector/Fusion/Util.hs:25:21-24 3901 54 0.0 0.0 0.0 0.0 + sChunks Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:122:30-36 3900 20 0.0 0.0 0.0 0.0 + sSize Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:124:30-34 3899 20 0.0 0.0 0.0 0.0 + upperBound Data.Vector.Fusion.Bundle.Size Data/Vector/Fusion/Bundle/Size.hs:(126,1)-(128,30) 3898 20 0.0 0.0 0.0 0.0 + jstring Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:317:1-32 3873 0 0.2 0.2 0.2 0.2 + runParser Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:111:7-15 3874 248104 0.0 0.0 0.0 0.0 + fromPos Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:46:21-27 3875 40882 0.0 0.0 0.0 0.0 + jstringSlow Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:(333,44)-(337,31) 3887 0 0.0 0.0 0.0 0.0 + object_ Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:132:46-89 3876 0 0.0 0.0 0.0 0.0 + runParser Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:111:7-15 3877 891 0.0 0.0 0.0 0.0 + marray# Data.Primitive.Array Data/Primitive/Array.hs:92:5-11 3911 233 0.0 0.0 0.0 0.0 + fromPos Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:46:21-27 3878 173 0.0 0.0 0.0 0.0 + unId Data.Vector.Fusion.Util Data/Vector/Fusion/Util.hs:25:21-24 3910 81 0.0 0.0 0.0 0.0 + sChunks Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:122:30-36 3909 5 0.0 0.0 0.0 0.0 + sSize Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:124:30-34 3908 5 0.0 0.0 0.0 0.0 + upperBound Data.Vector.Fusion.Bundle.Size Data/Vector/Fusion/Bundle/Size.hs:(126,1)-(128,30) 3907 5 0.0 0.0 0.0 0.0 + scientific Data.Scientific src/Data/Scientific.hs:174:1-23 3906 0 0.0 0.0 0.0 0.0 + jstringSlow Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:(333,44)-(337,31) 3888 0 0.0 0.0 0.0 0.0 + runParser Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:111:7-15 3891 32 0.0 0.0 0.0 0.0 + fromPos Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:46:21-27 3892 6 0.0 0.0 0.0 0.0 + object_ Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:132:46-89 3889 0 0.0 0.0 0.0 0.0 + jstring Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:317:1-32 3890 0 0.0 0.0 0.0 0.0 + object_ Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:132:46-89 3862 0 0.0 0.0 0.3 0.3 + runParser Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:111:7-15 3871 4975 0.0 0.0 0.0 0.0 + fromPos Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:46:21-27 3872 970 0.0 0.0 0.0 0.0 + marray# Data.Primitive.Array Data/Primitive/Array.hs:92:5-11 3916 14 0.0 0.0 0.0 0.0 + unId Data.Vector.Fusion.Util Data/Vector/Fusion/Util.hs:25:21-24 3915 6 0.0 0.0 0.0 0.0 + sChunks Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:122:30-36 3914 2 0.0 0.0 0.0 0.0 + sSize Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:124:30-34 3913 2 0.0 0.0 0.0 0.0 + upperBound Data.Vector.Fusion.Bundle.Size Data/Vector/Fusion/Bundle/Size.hs:(126,1)-(128,30) 3912 2 0.0 0.0 0.0 0.0 + jstring Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:317:1-32 3863 0 0.3 0.3 0.3 0.3 + runParser Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:111:7-15 3864 372571 0.0 0.0 0.0 0.0 + fromPos Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:46:21-27 3865 62673 0.0 0.0 0.0 0.0 + jstringSlow Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:(333,44)-(337,31) 3886 0 0.0 0.0 0.0 0.0 + scientific Data.Scientific src/Data/Scientific.hs:174:1-23 3894 0 0.0 0.0 0.0 0.0 + fromList Data.HashMap.Strict.Base Data/HashMap/Strict/Base.hs:598:1-64 3893 0 0.0 0.0 0.0 0.0 + unsafeInsert Data.HashMap.Base Data/HashMap/Base.hs:(784,1)-(814,76) 3895 958 0.0 0.0 0.0 0.0 + hash Data.HashMap.Base Data/HashMap/Base.hs:166:1-28 3896 958 0.0 0.0 0.0 0.0 + hashByteArrayWithSalt Data.Hashable.Class Data/Hashable/Class.hs:(770,1)-(772,20) 3897 958 0.0 0.0 0.0 0.0 + copy Data.HashMap.Array Data/HashMap/Array.hs:(328,1)-(333,30) 3904 676 0.0 0.0 0.0 0.0 + sparseIndex Data.HashMap.Base Data/HashMap/Base.hs:1867:1-42 3905 514 0.0 0.0 0.0 0.0 + new_ Data.HashMap.Array Data/HashMap/Array.hs:256:1-28 3903 338 0.0 0.0 0.0 0.0 + object_ Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:132:46-89 3850 0 0.1 0.2 2.6 4.2 + runParser Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:111:7-15 3851 164662 0.0 0.0 0.0 0.0 + fromPos Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:46:21-27 3852 35256 0.0 0.0 0.0 0.0 + array_ Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:169:35-59 3866 0 0.0 0.0 0.0 0.0 + jstring Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:317:1-32 3853 0 2.0 3.0 2.5 4.0 + runParser Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:111:7-15 3854 3769052 0.0 0.0 0.0 0.0 + fromPos Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:46:21-27 3855 627227 0.0 0.0 0.0 0.0 + jstringSlow Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:(333,44)-(337,31) 3879 414 0.0 0.0 0.2 0.3 + runParser Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:111:7-15 3880 34154 0.0 0.0 0.0 0.0 + fromPos Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:46:21-27 3881 5478 0.0 0.0 0.0 0.0 + array_ Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:169:35-59 3883 0 0.1 0.2 0.1 0.2 + runParser Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:111:7-15 3884 210974 0.0 0.0 0.0 0.0 + fromPos Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:46:21-27 3885 34568 0.0 0.0 0.0 0.0 + unescapeText Data.Aeson.Parser.UnescapePure pure/Data/Aeson/Parser/UnescapePure.hs:254:1-70 3882 0 0.1 0.1 0.1 0.1 + array_ Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:169:35-59 3859 0 0.3 0.6 0.4 0.7 + runParser Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:111:7-15 3860 623248 0.0 0.0 0.0 0.0 + fromPos Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:46:21-27 3861 102190 0.0 0.0 0.0 0.0 + marray# Data.Primitive.Array Data/Primitive/Array.hs:92:5-11 3921 688 0.0 0.0 0.0 0.0 + unId Data.Vector.Fusion.Util Data/Vector/Fusion/Util.hs:25:21-24 3920 320 0.0 0.0 0.0 0.0 + sChunks Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:122:30-36 3919 82 0.0 0.0 0.0 0.0 + sSize Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:124:30-34 3918 82 0.0 0.0 0.0 0.0 + upperBound Data.Vector.Fusion.Bundle.Size Data/Vector/Fusion/Bundle/Size.hs:(126,1)-(128,30) 3917 82 0.0 0.0 0.0 0.0 + jstringSlow Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:(333,44)-(337,31) 3867 10 0.0 0.0 0.1 0.1 + runParser Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:111:7-15 3868 2766 0.0 0.0 0.0 0.0 + fromPos Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:46:21-27 3869 442 0.0 0.0 0.0 0.0 + unescapeText Data.Aeson.Parser.UnescapePure pure/Data/Aeson/Parser/UnescapePure.hs:254:1-70 3870 0 0.1 0.1 0.1 0.1 + scientific Data.Scientific src/Data/Scientific.hs:174:1-23 3931 0 0.0 0.0 0.0 0.0 + sparseIndex Data.HashMap.Base Data/HashMap/Base.hs:1867:1-42 3925 5 0.0 0.0 0.0 0.0 + new_ Data.HashMap.Array Data/HashMap/Array.hs:256:1-28 3932 2 0.0 0.0 0.0 0.0 + abiKeccak EVM.Types src/EVM/Types.hs:(586,1)-(590,14) 5547 0 0.0 0.0 0.0 0.0 + word32 EVM.Types src/EVM/Types.hs:(576,1)-(577,52) 5579 23 0.0 0.0 0.0 0.0 + keccakBytes EVM.Types src/EVM/Types.hs:(570,1)-(573,15) 5548 0 0.0 0.0 0.0 0.0 + hash Crypto.Hash Crypto/Hash.hs:58:1-47 5549 23 0.0 0.0 0.0 0.0 + hashFinalize Crypto.Hash Crypto/Hash.hs:(92,1)-(95,17) 5550 23 0.0 0.0 0.0 0.0 + allocAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:74:1-45 5563 23 0.0 0.0 0.0 0.0 + new Basement.Block.Base Basement/Block/Base.hs:304:1-76 5564 23 0.0 0.0 0.0 0.0 + unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 5565 23 0.0 0.0 0.0 0.0 + withMutablePtrHint Basement.Block.Base Basement/Block/Base.hs:(475,1)-(489,39) 5566 23 0.0 0.0 0.0 0.0 + copy Data.ByteArray.Methods Data/ByteArray/Methods.hs:(223,1)-(226,21) 5571 23 0.0 0.0 0.0 0.0 + isMutablePinned Basement.Block.Base Basement/Block/Base.hs:100:1-90 5567 23 0.0 0.0 0.0 0.0 + compatIsMutableByteArrayPinned# Basement.Compat.Primitive Basement/Compat/Primitive.hs:70:1-65 5568 23 0.0 0.0 0.0 0.0 + toPinnedStatus# Basement.Compat.Primitive Basement/Compat/Primitive.hs:(47,1)-(48,27) 5569 23 0.0 0.0 0.0 0.0 + unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 5570 23 0.0 0.0 0.0 0.0 + hashInit Crypto.Hash Crypto/Hash.hs:(66,1)-(67,24) 5561 23 0.0 0.0 0.0 0.0 + allocAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:74:1-45 5562 23 0.0 0.0 0.0 0.0 + hashUpdate Crypto.Hash Crypto/Hash.hs:(71,1)-(73,37) 5551 23 0.0 0.0 0.0 0.0 + hashUpdates Crypto.Hash Crypto/Hash.hs:(81,1)-(86,32) 5558 23 0.0 0.0 0.0 0.0 + copyAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:(237,1)-(240,21) 5560 23 0.0 0.0 0.0 0.0 + null Data.ByteArray.Methods Data/ByteArray/Methods.hs:92:1-22 5559 23 0.0 0.0 0.0 0.0 + null Data.ByteArray.Methods Data/ByteArray/Methods.hs:92:1-22 5552 23 0.0 0.0 0.0 0.0 + unpack Data.ByteArray.Methods Data/ByteArray/Methods.hs:(104,1)-(110,34) 5572 23 0.0 0.0 0.0 0.0 + unsafeCast Basement.Block Basement/Block.hs:421:1-32 5573 759 0.0 0.0 0.0 0.0 + withPtr Basement.Block.Base Basement/Block/Base.hs:(402,1)-(411,31) 5574 736 0.0 0.0 0.0 0.0 + isPinned Basement.Block.Base Basement/Block/Base.hs:97:1-67 5575 736 0.0 0.0 0.0 0.0 + compatIsByteArrayPinned# Basement.Compat.Primitive Basement/Compat/Primitive.hs:67:1-51 5576 736 0.0 0.0 0.0 0.0 + toPinnedStatus# Basement.Compat.Primitive Basement/Compat/Primitive.hs:(47,1)-(48,27) 5577 736 0.0 0.0 0.0 0.0 + unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 5578 736 0.0 0.0 0.0 0.0 + keccak EVM.Types src/EVM/Types.hs:(580,1)-(583,12) 5512 0 0.0 0.0 0.1 0.1 + keccakBytes EVM.Types src/EVM/Types.hs:(570,1)-(573,15) 5514 0 0.0 0.0 0.1 0.1 + hash Crypto.Hash Crypto/Hash.hs:58:1-47 5515 43 0.0 0.0 0.0 0.0 + hashFinalize Crypto.Hash Crypto/Hash.hs:(92,1)-(95,17) 5516 43 0.0 0.0 0.0 0.0 + allocAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:74:1-45 5526 43 0.0 0.0 0.0 0.0 + new Basement.Block.Base Basement/Block/Base.hs:304:1-76 5527 43 0.0 0.0 0.0 0.0 + unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 5528 43 0.0 0.0 0.0 0.0 + withMutablePtrHint Basement.Block.Base Basement/Block/Base.hs:(475,1)-(489,39) 5529 43 0.0 0.0 0.0 0.0 + copy Data.ByteArray.Methods Data/ByteArray/Methods.hs:(223,1)-(226,21) 5534 43 0.0 0.0 0.0 0.0 + isMutablePinned Basement.Block.Base Basement/Block/Base.hs:100:1-90 5530 43 0.0 0.0 0.0 0.0 + compatIsMutableByteArrayPinned# Basement.Compat.Primitive Basement/Compat/Primitive.hs:70:1-65 5531 43 0.0 0.0 0.0 0.0 + toPinnedStatus# Basement.Compat.Primitive Basement/Compat/Primitive.hs:(47,1)-(48,27) 5532 43 0.0 0.0 0.0 0.0 + unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 5533 43 0.0 0.0 0.0 0.0 + hashInit Crypto.Hash Crypto/Hash.hs:(66,1)-(67,24) 5524 43 0.0 0.0 0.0 0.0 + allocAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:74:1-45 5525 43 0.0 0.0 0.0 0.0 + hashUpdate Crypto.Hash Crypto/Hash.hs:(71,1)-(73,37) 5517 43 0.0 0.0 0.0 0.0 + hashUpdates Crypto.Hash Crypto/Hash.hs:(81,1)-(86,32) 5521 43 0.0 0.0 0.0 0.0 + copyAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:(237,1)-(240,21) 5523 43 0.0 0.0 0.0 0.0 + null Data.ByteArray.Methods Data/ByteArray/Methods.hs:92:1-22 5522 43 0.0 0.0 0.0 0.0 + null Data.ByteArray.Methods Data/ByteArray/Methods.hs:92:1-22 5518 43 0.0 0.0 0.0 0.0 + unpack Data.ByteArray.Methods Data/ByteArray/Methods.hs:(104,1)-(110,34) 5535 43 0.0 0.0 0.1 0.0 + unsafeCast Basement.Block Basement/Block.hs:421:1-32 5536 1419 0.0 0.0 0.0 0.0 + withPtr Basement.Block.Base Basement/Block/Base.hs:(402,1)-(411,31) 5537 1376 0.1 0.0 0.1 0.0 + isPinned Basement.Block.Base Basement/Block/Base.hs:97:1-67 5538 1376 0.0 0.0 0.0 0.0 + compatIsByteArrayPinned# Basement.Compat.Primitive Basement/Compat/Primitive.hs:67:1-51 5539 1376 0.0 0.0 0.0 0.0 + toPinnedStatus# Basement.Compat.Primitive Basement/Compat/Primitive.hs:(47,1)-(48,27) 5540 1376 0.0 0.0 0.0 0.0 + unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 5541 1376 0.0 0.0 0.0 0.0 + word EVM.Types src/EVM/Types.hs:521:1-21 5513 0 0.0 0.0 0.0 0.0 + word256 EVM.Types src/EVM/Types.hs:(510,1)-(518,67) 5542 43 0.0 0.0 0.0 0.0 + padLeft EVM.Types src/EVM/Types.hs:495:1-54 5543 43 0.0 0.0 0.0 0.0 + bytesRead Data.Serialize.Get src/Data/Serialize/Get.hs:838:1-45 5544 0 0.0 0.0 0.0 0.0 + makeSrcMaps EVM.Solidity src/EVM/Solidity.hs:(227,1)-(271,126) 5581 0 0.4 0.5 0.4 0.5 + parseTypeName EVM.ABI src/EVM/ABI.hs:375:1-50 6441 0 0.0 0.0 0.0 0.0 + unParser Text.Megaparsec.Internal Text/Megaparsec/Internal.hs:120:5-12 6448 47 0.0 0.0 0.0 0.0 + parseMaybe Text.Megaparsec Text/Megaparsec.hs:(191,1)-(194,21) 6442 3 0.0 0.0 0.0 0.0 + runParser Text.Megaparsec Text/Megaparsec.hs:223:1-61 6443 3 0.0 0.0 0.0 0.0 + runParser' Text.Megaparsec Text/Megaparsec.hs:236:1-42 6444 3 0.0 0.0 0.0 0.0 + runParserT' Text.Megaparsec Text/Megaparsec.hs:(261,1)-(274,54) 6445 3 0.0 0.0 0.0 0.0 + runParsecT Text.Megaparsec.Internal Text/Megaparsec/Internal.hs:(591,1)-(596,56) 6446 3 0.0 0.0 0.0 0.0 + unParser Text.Megaparsec.Internal Text/Megaparsec/Internal.hs:120:5-12 6447 50 0.0 0.0 0.0 0.0 + stateParseErrors Text.Megaparsec.State Text/Megaparsec/State.hs:48:5-20 6449 3 0.0 0.0 0.0 0.0 + union Data.HashMap.Base Data/HashMap/Base.hs:1287:1-23 3929 0 0.0 0.0 0.0 0.0 + smtdebug Main hevm-cli/hevm-cli.hs:130:9-16 3648 1 0.0 0.0 0.0 0.0 + smttimeout Main hevm-cli/hevm-cli.hs:127:9-18 3608 1 0.0 0.0 0.0 0.0 + solver Main hevm-cli/hevm-cli.hs:129:9-14 3606 1 0.0 0.0 0.0 0.0 + unitTestOptions Main hevm-cli/hevm-cli.hs:(262,1)-(304,5) 3710 1 0.0 0.0 0.0 0.0 + applyCache Main hevm-cli/hevm-cli.hs:(244,1)-(259,63) 3935 1 0.0 0.0 0.0 0.0 + cache Main hevm-cli/hevm-cli.hs:116:9-13 3933 1 0.0 0.0 0.0 0.0 + corpus Main hevm-cli/hevm-cli.hs:177:9-14 4123 1 0.0 0.0 0.0 0.0 + fuzzRuns Main hevm-cli/hevm-cli.hs:175:9-16 5300 1 0.0 0.0 0.0 0.0 + getParametersFromEnvironmentVariables EVM.UnitTest src/EVM/UnitTest.hs:(910,1)-(942,38) 3937 1 0.0 0.0 0.0 0.0 + match Main hevm-cli/hevm-cli.hs:184:9-13 4243 1 0.0 0.0 0.0 0.0 + mutations Main hevm-cli/hevm-cli.hs:176:9-17 5900 1 0.0 0.0 0.0 0.0 + readSolc EVM.Solidity src/EVM/Solidity.hs:(297,1)-(303,47) 3712 1 0.0 0.0 0.0 0.0 + replay Main hevm-cli/hevm-cli.hs:178:9-14 5298 1 0.0 0.0 0.0 0.0 + rpc Main hevm-cli/hevm-cli.hs:113:9-11 3939 1 0.0 0.0 0.0 0.0 + state Main hevm-cli/hevm-cli.hs:115:9-13 3934 1 0.0 0.0 0.0 0.0 + verbose Main hevm-cli/hevm-cli.hs:180:9-15 6421 1 0.0 0.0 0.0 0.0 + unwrapRecord Options.Generic src/Options/Generic.hs:1155:1-38 3452 1 0.0 0.0 0.1 0.0 + unHelpful Options.Generic src/Options/Generic.hs:613:57-65 3603 17 0.0 0.0 0.0 0.0 + getRecord Options.Generic src/Options/Generic.hs:(1017,1)-(1019,51) 3453 1 0.0 0.0 0.1 0.0 + getRecordWith Options.Generic src/Options/Generic.hs:(1032,1)-(1035,46) 3454 1 0.0 0.0 0.1 0.0 + customExecParser Options.Applicative.Extra src/Options/Applicative/Extra.hs:(76,1)-(78,23) 3455 1 0.0 0.0 0.1 0.0 + execParserPure Options.Applicative.Extra src/Options/Applicative/Extra.hs:(130,1)-(139,33) 3456 1 0.0 0.0 0.1 0.0 + runP Options.Applicative.Internal src/Options/Applicative/Internal.hs:91:1-59 3457 1 0.0 0.0 0.1 0.0 + bashCompletionParser Options.Applicative.BashCompletion src/Options/Applicative/BashCompletion.hs:(35,1)-(65,7) 3476 1 0.0 0.0 0.0 0.0 + infoParser Options.Applicative.Types src/Options/Applicative/Types.hs:90:5-14 3513 1 0.0 0.0 0.0 0.0 + runParserInfo Options.Applicative.Common src/Options/Applicative/Common.hs:225:1-62 3458 1 0.0 0.0 0.1 0.0 + infoParser Options.Applicative.Types src/Options/Applicative/Types.hs:90:5-14 3475 1 0.0 0.0 0.0 0.0 + infoPolicy Options.Applicative.Types src/Options/Applicative/Types.hs:97:5-14 3471 1 0.0 0.0 0.0 0.0 + runParserFully Options.Applicative.Common src/Options/Applicative/Common.hs:(228,1)-(232,33) 3459 1 0.0 0.0 0.1 0.0 + runParser Options.Applicative.Common src/Options/Applicative/Common.hs:(201,1)-(219,24) 3460 4 0.0 0.0 0.1 0.0 + evalParser Options.Applicative.Common src/Options/Applicative/Common.hs:(237,1)-(241,56) 3508 81 0.0 0.0 0.0 0.0 + parseRecord Main hevm-cli/hevm-cli.hs:(237,3)-(238,62) 3600 0 0.0 0.0 0.0 0.0 + parseRecordWithModifiers Options.Generic src/Options/Generic.hs:1006:1-78 3601 0 0.0 0.0 0.0 0.0 + optMain Options.Applicative.Types src/Options/Applicative/Types.hs:166:5-11 3488 26 0.0 0.0 0.0 0.0 + Options.Applicative.Internal src/Options/Applicative/Internal.hs:(249,1)-(252,15) 3477 5 0.0 0.0 0.0 0.0 + disamb Options.Applicative.Internal src/Options/Applicative/Internal.hs:(258,1)-(265,18) 3461 2 0.0 0.0 0.1 0.0 + runListT Options.Applicative.Internal src/Options/Applicative/Internal.hs:(183,1)-(187,43) 3462 4 0.0 0.0 0.1 0.0 + takeListT Options.Applicative.Internal src/Options/Applicative/Internal.hs:(179,1)-(180,75) 3470 0 0.0 0.0 0.1 0.0 + Options.Applicative.Internal src/Options/Applicative/Internal.hs:(249,1)-(252,15) 3478 5 0.1 0.0 0.1 0.0 + prefDisambiguate Options.Applicative.Types src/Options/Applicative/Types.hs:113:5-20 3556 4 0.0 0.0 0.0 0.0 + optMain Options.Applicative.Types src/Options/Applicative/Types.hs:166:5-11 3563 3 0.0 0.0 0.0 0.0 + infoParser Options.Applicative.Types src/Options/Applicative/Types.hs:90:5-14 3560 1 0.0 0.0 0.0 0.0 + infoPolicy Options.Applicative.Types src/Options/Applicative/Types.hs:97:5-14 3557 1 0.0 0.0 0.0 0.0 + runReadM Options.Applicative.Internal src/Options/Applicative/Internal.hs:98:1-63 3579 1 0.0 0.0 0.0 0.0 + hoistEither Options.Applicative.Internal src/Options/Applicative/Internal.hs:88:1-34 3589 1 0.0 0.0 0.0 0.0 + withReadM Options.Applicative.Internal src/Options/Applicative/Internal.hs:(101,1)-(104,12) 3581 0 0.0 0.0 0.0 0.0 + crReader Options.Applicative.Types src/Options/Applicative/Types.hs:226:5-12 3583 1 0.0 0.0 0.0 0.0 + parseRecord Main hevm-cli/hevm-cli.hs:(237,3)-(238,62) 3584 0 0.0 0.0 0.0 0.0 + parseRecordWithModifiers Options.Generic src/Options/Generic.hs:1006:1-78 3585 0 0.0 0.0 0.0 0.0 + str Options.Applicative.Builder src/Options/Applicative/Builder.hs:129:1-30 3587 0 0.0 0.0 0.0 0.0 + unReadM Options.Applicative.Types src/Options/Applicative/Types.hs:184:5-11 3582 1 0.0 0.0 0.0 0.0 + uncons Options.Applicative.Internal src/Options/Applicative/Internal.hs:(94,1)-(95,30) 3578 1 0.0 0.0 0.0 0.0 + withReadM Options.Applicative.Internal src/Options/Applicative/Internal.hs:(101,1)-(104,12) 3580 1 0.0 0.0 0.0 0.0 + takeListT Options.Applicative.Internal src/Options/Applicative/Internal.hs:(179,1)-(180,75) 3469 4 0.0 0.0 0.0 0.0 + prefBacktrack Options.Applicative.Types src/Options/Applicative/Types.hs:119:5-17 3555 1 0.0 0.0 0.0 0.0 + prefDisambiguate Options.Applicative.Types src/Options/Applicative/Types.hs:113:5-20 3463 1 0.0 0.0 0.0 0.0 + bashCompletionParser Options.Applicative.BashCompletion src/Options/Applicative/BashCompletion.hs:(35,1)-(65,7) 3509 0 0.0 0.0 0.0 0.0 + fromM Options.Applicative.Types src/Options/Applicative/Types.hs:282:1-26 3510 0 0.0 0.0 0.0 0.0 + manyM Options.Applicative.Types src/Options/Applicative/Types.hs:(288,1)-(292,30) 3511 0 0.0 0.0 0.0 0.0 + runParserM Options.Applicative.Types src/Options/Applicative/Types.hs:268:5-14 3512 1 0.0 0.0 0.0 0.0 + parseRecord Main hevm-cli/hevm-cli.hs:(237,3)-(238,62) 3546 0 0.0 0.0 0.0 0.0 + parseRecordWithModifiers Options.Generic src/Options/Generic.hs:1006:1-78 3547 0 0.0 0.0 0.0 0.0 + infoParser Options.Applicative.Types src/Options/Applicative/Types.hs:90:5-14 3562 3 0.0 0.0 0.0 0.0 + subparser Options.Applicative.Builder src/Options/Applicative/Builder.hs:(270,1)-(274,39) 3549 0 0.0 0.0 0.0 0.0 + mkCommand Options.Applicative.Builder.Internal src/Options/Applicative/Builder/Internal.hs:(154,1)-(157,59) 3550 0 0.0 0.0 0.0 0.0 + handleParseResult Options.Applicative.Extra src/Options/Applicative/Extra.hs:(82,1)-(94,17) 3599 1 0.0 0.0 0.0 0.0 + info Options.Applicative.Builder src/Options/Applicative/Builder.hs:(443,1)-(452,34) 3472 1 0.0 0.0 0.0 0.0 + header Options.Applicative.Builder src/Options/Applicative/Builder.hs:395:1-57 3474 0 0.0 0.0 0.0 0.0 + header Options.Applicative.Builder src/Options/Applicative/Builder.hs:395:1-57 3473 1 0.0 0.0 0.0 0.0 + query Data.SBV.Control Data/SBV/Control.hs:105:1-40 3628 0 0.0 0.0 0.0 0.0 + executeQuery Data.SBV.Control.Utils Data/SBV/Control/Utils.hs:(1467,1)-(1619,43) 3629 1 0.0 0.0 0.0 0.0 diff --git a/src/hevm/src/EVM/UnitTest.hs b/src/hevm/src/EVM/UnitTest.hs index 370ad29bf..06004724f 100644 --- a/src/hevm/src/EVM/UnitTest.hs +++ b/src/hevm/src/EVM/UnitTest.hs @@ -35,8 +35,6 @@ import qualified Control.Monad.State.Strict as State import Control.Monad.Par.Class (spawn_) import Control.Monad.Par.IO (runParIO) -import Data.Digest.XXHash.FFI - import qualified Data.ByteString.Lazy as BSLazy import qualified Data.SBV.Trans.Control as SBV (Query, getValue, resetAssertions) import qualified Data.SBV.Internals as SBV (State) @@ -108,9 +106,9 @@ data TestVMParams = TestVMParams , testChainId :: W256 } --- | For each tuple of (contract, method) we store the calldata required to reach each known path in the method --- | The keys in the corpus are hashed to keep the size of the serialized representation manageable -type Corpus = Map Word64 (Map [(W256, Int)] AbiValue) +-- | For each tuple of (contract, method) we store the calldata required to +-- reach each known path in the method +type Corpus = Map (W256,Text) (Map [(W256, Int)] AbiValue) instance Arbitrary (MultiSet OpLocation) where arbitrary = do @@ -209,14 +207,10 @@ checkFailures UnitTestOptions { .. } method bailed = do in pure (shouldFail == failed) _ -> error "internal error: unexpected failure code" -xxhash :: ByteString -> Word64 -xxhash bs = xxh64 bs 42069 - -- | Either generates the calldata by mutating an example from the corpus, or synthesizes a random example -genWithCorpus :: UnitTestOptions -> Corpus -> SolcContract -> Text -> [AbiType] -> Gen AbiValue -genWithCorpus opts corpus contract' sig tps = do - -- TODO: also check that the contract matches here - case Map.lookup (hashCall (contract', sig)) corpus of +genWithCorpus :: UnitTestOptions -> Corpus -> W256 -> Text -> [AbiType] -> Gen AbiValue +genWithCorpus opts corpus codeHash sig tps = do + case Map.lookup (codeHash, sig) corpus of Nothing -> genAbiValue (AbiTupleType $ Vector.fromList tps) Just examples -> frequency [ (mutations opts, Test.QuickCheck.elements (Map.elems examples) >>= mutateAbiValue) @@ -226,12 +220,11 @@ genWithCorpus opts corpus contract' sig tps = do -- | Randomly generates the calldata arguments and runs the test, updates the corpus with a new example if we explored a new path fuzzTest :: UnitTestOptions -> Text -> [AbiType] -> VM -> StateT Corpus IO FuzzResult fuzzTest opts sig types vm = do - let code' = _contractcode . fromJust $ currentContract vm - contract' = fromJust $ lookupCode code' (dapp opts) + let codeHash' = _codehash . fromJust $ currentContract vm corpus <- get - args <- liftIO . generate $ genWithCorpus opts corpus contract' sig types - (res, (vm', traceId)) <- liftIO $ runStateT (interpretWithTraceId opts (runUnitTest opts sig args)) (vm, []) - modify $ updateCorpus (hashCall (contract', sig)) traceId args + args <- liftIO . generate $ genWithCorpus opts corpus codeHash' sig types + (res, (vm', trace')) <- liftIO $ runStateT (interpretWithTraceId opts (runUnitTest opts sig args)) (vm, []) + modify $ updateCorpus (codeHash', sig) trace' args if res then pure Pass else pure $ Fail vm' (show . ByteStringS . encodeAbiValue $ args) @@ -240,10 +233,6 @@ fuzzTest opts sig types vm = do Nothing -> Map.insert k1 (Map.insert k2 v mempty) c Just m' -> Map.insert k1 (Map.insert k2 v m') c -hashCall :: (SolcContract, Text) -> Word64 -hashCall (contract', sig) = xxhash . - encodeUtf8 . Text.pack $ (show . _runtimeCodehash $ contract') <> (show . _creationCodehash $ contract') <> (Text.unpack sig) - type TraceIdState = (VM, [(W256, Int)]) -- | This interpreter is similar to interpretWithCoverage, except instead of diff --git a/src/hevm/test/test.hs b/src/hevm/test/test.hs index 34f8d4a84..c01bf0fee 100644 --- a/src/hevm/test/test.hs +++ b/src/hevm/test/test.hs @@ -117,12 +117,6 @@ main = defaultMain $ testGroup "hevm" Error _ -> False Data.Aeson.Success v -> val == v - , testProperty "Blake3 Digest" $ do - val <- arbitrary :: Gen (BLAKE3.Digest 32) - pure $ case (fromJSON . toJSON $ val) of - Error _ -> False - Data.Aeson.Success v -> val == v - , testProperty "W256" $ do val <- arbitrary :: Gen W256 pure $ case (fromJSON . toJSON $ val) of From 8ed2665e583662a3edc9e38b37306293eb46c36a Mon Sep 17 00:00:00 2001 From: David Terry Date: Fri, 28 May 2021 18:12:27 +0200 Subject: [PATCH 19/21] hevm: test: fix tests --- src/hevm/hevm.cabal | 1 + src/hevm/test/test.hs | 5 +---- 2 files changed, 2 insertions(+), 4 deletions(-) diff --git a/src/hevm/hevm.cabal b/src/hevm/hevm.cabal index ad7ff22aa..41463c283 100644 --- a/src/hevm/hevm.cabal +++ b/src/hevm/hevm.cabal @@ -227,6 +227,7 @@ test-suite test tasty >= 1.0, tasty-hunit >= 0.10, tasty-quickcheck >= 0.9, + quickcheck-text, text, vector, sbv diff --git a/src/hevm/test/test.hs b/src/hevm/test/test.hs index c01bf0fee..539ef1caf 100644 --- a/src/hevm/test/test.hs +++ b/src/hevm/test/test.hs @@ -10,8 +10,6 @@ module Main where -import Debug.Trace - import Data.Text (Text) import Data.ByteString (ByteString) @@ -24,6 +22,7 @@ import qualified Data.ByteString.Base16 as Hex import Test.Tasty import Test.Tasty.QuickCheck import Test.Tasty.HUnit +import Data.Text.Arbitrary () import Control.Monad.State.Strict (execState, runState) import Control.Lens hiding (List, pre, (.>)) @@ -38,8 +37,6 @@ import Data.SBV hiding ((===), forAll, sList) import Data.SBV.Control import qualified Data.Map as Map import Data.Binary.Get (runGetOrFail) -import qualified BLAKE3 - import Data.Aeson (fromJSON, toJSON, Result(..)) From cba0e7c023584f0653cbc311c8917798d52d9c15 Mon Sep 17 00:00:00 2001 From: David Terry Date: Fri, 28 May 2021 18:57:37 +0200 Subject: [PATCH 20/21] hevm: dappTest: serialize corpus with cbor --- src/hevm/hevm-cli/hevm-cli.hs | 10 +- src/hevm/hevm.cabal | 3 + src/hevm/hevm.prof | 3138 --------------------------------- src/hevm/src/EVM.hs | 10 - src/hevm/src/EVM/ABI.hs | 32 +- src/hevm/src/EVM/Solidity.hs | 21 - src/hevm/src/EVM/Types.hs | 17 +- src/hevm/src/EVM/UnitTest.hs | 16 - src/hevm/test/test.hs | 21 +- 9 files changed, 23 insertions(+), 3245 deletions(-) delete mode 100644 src/hevm/hevm.prof diff --git a/src/hevm/hevm-cli/hevm-cli.hs b/src/hevm/hevm-cli/hevm-cli.hs index 44ddd3a52..761b457c2 100644 --- a/src/hevm/hevm-cli/hevm-cli.hs +++ b/src/hevm/hevm-cli/hevm-cli.hs @@ -12,7 +12,6 @@ module Main where -import qualified Debug.Trace as Debug import EVM (StorageModel(..)) import qualified EVM import EVM.Concrete (createAddress, wordValue) @@ -73,6 +72,7 @@ import qualified Data.Aeson as JSON import qualified Data.Aeson.Types as JSON import Data.Aeson (FromJSON (..), (.:)) import Data.Aeson.Lens hiding (values) +import Codec.Serialise (serialise, deserialiseOrFail, DeserialiseFailure(..)) import qualified Data.Vector as V import qualified Data.ByteString.Lazy as Lazy @@ -392,9 +392,9 @@ dappTest opts solcFile cache = do let dappInfo' = EVM.UnitTest.dapp opts corpusPath = (_dappRoot dappInfo') <> "/" <> (EVM.UnitTest.corpus opts) initalCorpus <- liftIO $ doesFileExist corpusPath >>= \case - True -> liftIO $ JSON.decodeFileStrict' corpusPath >>= \case - Nothing -> error "unable to parse corpus" - Just a -> pure a + True -> liftIO $ (LazyByteString.readFile corpusPath) >>= \v -> case deserialiseOrFail v of + Left (DeserialiseFailure _ msg) -> error $ "unable to parse corpus: " <> msg + Right a -> pure a False -> pure mempty case out of @@ -415,7 +415,7 @@ dappTest opts solcFile cache = do in liftIO $ Git.saveFacts (Git.RepoAt path) (Facts.cacheFacts cache') - liftIO $ JSON.encodeFile (EVM.UnitTest.corpus opts) finalCorpus + liftIO $ LazyByteString.writeFile (EVM.UnitTest.corpus opts) (serialise finalCorpus) liftIO $ unless (and passing) exitFailure Nothing -> error ("Failed to read Solidity JSON for `" ++ solcFile ++ "'") diff --git a/src/hevm/hevm.cabal b/src/hevm/hevm.cabal index 41463c283..a4d80f203 100644 --- a/src/hevm/hevm.cabal +++ b/src/hevm/hevm.cabal @@ -131,6 +131,7 @@ library regex-tdfa >= 1.2.3 && < 1.4, base >= 4.9 && < 5, ListLike >= 4.7.2 && < 4.8, + serialise >= 0.2.3.0 && < 0.3 hs-source-dirs: src default-language: @@ -174,6 +175,7 @@ executable hevm containers, cryptonite, data-dword, + serialise, deepseq, directory, filepath, @@ -230,4 +232,5 @@ test-suite test quickcheck-text, text, vector, + serialise, sbv diff --git a/src/hevm/hevm.prof b/src/hevm/hevm.prof deleted file mode 100644 index ee0b1b342..000000000 --- a/src/hevm/hevm.prof +++ /dev/null @@ -1,3138 +0,0 @@ - Fri May 28 14:23 2021 Time and Allocation Profiling Report (Final) - - hevm +RTS -N -p -RTS dapp-test --dapp-root /home/me/code/mine/scratch/solidity - - total time = 0.52 secs (1929 ticks @ 1000 us, 8 processors) - total alloc = 2,365,287,016 bytes (excludes profiling overheads) - -COST CENTRE MODULE SRC %time %alloc - -exec1 EVM src/EVM.hs:(547,1)-(1323,42) 18.8 14.4 -burn EVM src/EVM.hs:(1826,1)-(1838,38) 8.3 14.0 -num EVM.Types src/EVM/Types.hs:492:1-18 7.5 6.0 -jstring Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:317:1-32 7.3 10.3 -mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 6.6 4.8 -runWithTraceId EVM.UnitTest src/EVM/UnitTest.hs:(286,1)-(301,90) 5.9 7.5 -hashCall EVM.UnitTest src/EVM/UnitTest.hs:(244,1)-(245,127) 4.0 8.3 -limitStack EVM src/EVM.hs:(1809,1)-(1813,17) 3.4 0.8 -vmOpIx EVM src/EVM.hs:(2603,1)-(2605,57) 3.1 2.1 -currentContract EVM src/EVM.hs:(443,1)-(444,65) 2.8 1.1 -fuzzTest EVM.UnitTest src/EVM/UnitTest.hs:(228,1)-(241,53) 2.6 0.0 -checkJump EVM src/EVM.hs:(2526,1)-(2539,35) 2.4 1.1 -stripBytecodeMetadata EVM.Solidity src/EVM/Solidity.hs:(569,1)-(573,22) 1.8 0.0 -withPtr Basement.Block.Base Basement/Block/Base.hs:(402,1)-(411,31) 1.7 1.9 -array_ Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:169:35-59 1.7 2.9 -genLiteral Data.SBV.Core.Model Data/SBV/Core/Model.hs:99:1-48 1.5 1.3 -next EVM src/EVM.hs:543:1-46 0.8 4.7 -index EVM.Symbolic src/EVM/Symbolic.hs:(207,1)-(208,47) 0.8 2.2 -makeSrcMaps EVM.Solidity src/EVM/Solidity.hs:(227,1)-(271,126) 0.8 1.0 -pushSym EVM src/EVM.hs:2477:1-34 0.6 1.7 -bytesRead Data.Serialize.Get src/Data/Serialize/Get.hs:838:1-45 0.4 1.5 - - - individual inherited -COST CENTRE MODULE SRC no. entries %time %alloc %time %alloc - -MAIN MAIN 1725 0 0.0 0.0 100.0 100.0 - CAF Main 3448 0 0.0 0.0 0.0 0.0 - main Main hevm-cli/hevm-cli.hs:(307,1)-(354,100) 3450 1 0.0 0.0 0.0 0.0 - parseRecord Main hevm-cli/hevm-cli.hs:(237,3)-(238,62) 3514 1 0.0 0.0 0.0 0.0 - parseRecordWithModifiers Options.Generic src/Options/Generic.hs:1006:1-78 3515 1 0.0 0.0 0.0 0.0 - help Options.Applicative.Builder src/Options/Applicative/Builder.hs:185:1-55 3569 18 0.0 0.0 0.0 0.0 - optionMod Options.Applicative.Builder.Internal src/Options/Applicative/Builder/Internal.hs:129:1-25 3570 0 0.0 0.0 0.0 0.0 - long Options.Applicative.Builder src/Options/Applicative/Builder.hs:161:1-32 3567 18 0.0 0.0 0.0 0.0 - fieldMod Options.Applicative.Builder.Internal src/Options/Applicative/Builder/Internal.hs:132:1-28 3568 18 0.0 0.0 0.0 0.0 - option Options.Applicative.Builder src/Options/Applicative/Builder.hs:(367,1)-(372,65) 3571 14 0.0 0.0 0.0 0.0 - mkParser Options.Applicative.Builder.Internal src/Options/Applicative/Builder/Internal.hs:(163,1)-(167,36) 3572 14 0.0 0.0 0.0 0.0 - mkOption Options.Applicative.Builder.Internal src/Options/Applicative/Builder/Internal.hs:173:1-43 3573 2 0.0 0.0 0.0 0.0 - optNames Options.Applicative.Builder.Internal src/Options/Applicative/Builder/Internal.hs:35:5-12 3574 2 0.0 0.0 0.0 0.0 - long Options.Applicative.Builder src/Options/Applicative/Builder.hs:161:1-32 3575 0 0.0 0.0 0.0 0.0 - optNames Options.Applicative.Builder.Internal src/Options/Applicative/Builder/Internal.hs:35:5-12 3577 1 0.0 0.0 0.0 0.0 - fieldMod Options.Applicative.Builder.Internal src/Options/Applicative/Builder/Internal.hs:132:1-28 3576 0 0.0 0.0 0.0 0.0 - metavar Options.Applicative.Builder src/Options/Applicative/Builder.hs:201:1-55 3538 13 0.0 0.0 0.0 0.0 - optionMod Options.Applicative.Builder.Internal src/Options/Applicative/Builder/Internal.hs:129:1-25 3539 0 0.0 0.0 0.0 0.0 - command Options.Applicative.Builder src/Options/Applicative/Builder.hs:(234,1)-(235,50) 3536 4 0.0 0.0 0.0 0.0 - fieldMod Options.Applicative.Builder.Internal src/Options/Applicative/Builder/Internal.hs:132:1-28 3537 4 0.0 0.0 0.0 0.0 - subparser Options.Applicative.Builder src/Options/Applicative/Builder.hs:(270,1)-(274,39) 3540 4 0.0 0.0 0.0 0.0 - mkCommand Options.Applicative.Builder.Internal src/Options/Applicative/Builder/Internal.hs:(154,1)-(157,59) 3548 4 0.0 0.0 0.0 0.0 - command Options.Applicative.Builder src/Options/Applicative/Builder.hs:(234,1)-(235,50) 3551 0 0.0 0.0 0.0 0.0 - cmdCommands Options.Applicative.Builder.Internal src/Options/Applicative/Builder/Internal.hs:44:5-15 3554 3 0.0 0.0 0.0 0.0 - fieldMod Options.Applicative.Builder.Internal src/Options/Applicative/Builder/Internal.hs:132:1-28 3552 0 0.0 0.0 0.0 0.0 - mkParser Options.Applicative.Builder.Internal src/Options/Applicative/Builder/Internal.hs:(163,1)-(167,36) 3544 4 0.0 0.0 0.0 0.0 - mkOption Options.Applicative.Builder.Internal src/Options/Applicative/Builder/Internal.hs:173:1-43 3545 4 0.0 0.0 0.0 0.0 - info Options.Applicative.Builder src/Options/Applicative/Builder.hs:(443,1)-(452,34) 3559 1 0.0 0.0 0.0 0.0 - lispCaseModifiers Options.Generic src/Options/Generic.hs:(816,1)-(820,29) 3553 0 0.0 0.0 0.0 0.0 - switch Options.Applicative.Builder src/Options/Applicative/Builder.hs:333:1-24 3591 0 0.0 0.0 0.0 0.0 - flag Options.Applicative.Builder src/Options/Applicative/Builder.hs:299:1-45 3592 4 0.0 0.0 0.0 0.0 - flag' Options.Applicative.Builder src/Options/Applicative/Builder.hs:(319,1)-(323,43) 3593 4 0.0 0.0 0.0 0.0 - mkParser Options.Applicative.Builder.Internal src/Options/Applicative/Builder/Internal.hs:(163,1)-(167,36) 3594 4 0.0 0.0 0.0 0.0 - metavar Options.Applicative.Builder src/Options/Applicative/Builder.hs:201:1-55 3597 0 0.0 0.0 0.0 0.0 - optionMod Options.Applicative.Builder.Internal src/Options/Applicative/Builder/Internal.hs:129:1-25 3598 0 0.0 0.0 0.0 0.0 - unitTestOptions Main hevm-cli/hevm-cli.hs:(262,1)-(304,5) 4244 0 0.0 0.0 0.0 0.0 - CAF EVM 3447 0 0.0 0.0 0.1 0.0 - blankState EVM src/EVM.hs:(385,1)-(399,3) 4842 1 0.0 0.0 0.0 0.0 - genLiteral Data.SBV.Core.Model Data/SBV/Core/Model.hs:99:1-48 4843 2 0.0 0.0 0.0 0.0 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 4906 1 0.0 0.0 0.0 0.0 - svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 4907 1 0.0 0.0 0.0 0.0 - svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 4908 1 0.0 0.0 0.0 0.0 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 4909 1 0.0 0.0 0.0 0.0 - cheatCode EVM src/EVM.hs:1936:1-42 5957 1 0.0 0.0 0.0 0.0 - num EVM.Types src/EVM/Types.hs:492:1-18 5958 1 0.0 0.0 0.0 0.0 - keccak EVM.Types src/EVM/Types.hs:(580,1)-(583,12) 5959 0 0.0 0.0 0.0 0.0 - keccakBytes EVM.Types src/EVM/Types.hs:(570,1)-(573,15) 5961 0 0.0 0.0 0.0 0.0 - hash Crypto.Hash Crypto/Hash.hs:58:1-47 5962 1 0.0 0.0 0.0 0.0 - hashFinalize Crypto.Hash Crypto/Hash.hs:(92,1)-(95,17) 5963 1 0.0 0.0 0.0 0.0 - allocAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:74:1-45 5971 1 0.0 0.0 0.0 0.0 - new Basement.Block.Base Basement/Block/Base.hs:304:1-76 5972 1 0.0 0.0 0.0 0.0 - unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 5973 1 0.0 0.0 0.0 0.0 - withMutablePtrHint Basement.Block.Base Basement/Block/Base.hs:(475,1)-(489,39) 5974 1 0.0 0.0 0.0 0.0 - copy Data.ByteArray.Methods Data/ByteArray/Methods.hs:(223,1)-(226,21) 5979 1 0.0 0.0 0.0 0.0 - isMutablePinned Basement.Block.Base Basement/Block/Base.hs:100:1-90 5975 1 0.0 0.0 0.0 0.0 - compatIsMutableByteArrayPinned# Basement.Compat.Primitive Basement/Compat/Primitive.hs:70:1-65 5976 1 0.0 0.0 0.0 0.0 - toPinnedStatus# Basement.Compat.Primitive Basement/Compat/Primitive.hs:(47,1)-(48,27) 5977 1 0.0 0.0 0.0 0.0 - unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 5978 1 0.0 0.0 0.0 0.0 - hashInit Crypto.Hash Crypto/Hash.hs:(66,1)-(67,24) 5969 1 0.0 0.0 0.0 0.0 - allocAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:74:1-45 5970 1 0.0 0.0 0.0 0.0 - hashUpdate Crypto.Hash Crypto/Hash.hs:(71,1)-(73,37) 5964 1 0.0 0.0 0.0 0.0 - hashUpdates Crypto.Hash Crypto/Hash.hs:(81,1)-(86,32) 5966 1 0.0 0.0 0.0 0.0 - copyAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:(237,1)-(240,21) 5968 1 0.0 0.0 0.0 0.0 - null Data.ByteArray.Methods Data/ByteArray/Methods.hs:92:1-22 5967 1 0.0 0.0 0.0 0.0 - null Data.ByteArray.Methods Data/ByteArray/Methods.hs:92:1-22 5965 1 0.0 0.0 0.0 0.0 - unpack Data.ByteArray.Methods Data/ByteArray/Methods.hs:(104,1)-(110,34) 5980 1 0.0 0.0 0.0 0.0 - unsafeCast Basement.Block Basement/Block.hs:421:1-32 5981 33 0.0 0.0 0.0 0.0 - withPtr Basement.Block.Base Basement/Block/Base.hs:(402,1)-(411,31) 5982 32 0.0 0.0 0.0 0.0 - isPinned Basement.Block.Base Basement/Block/Base.hs:97:1-67 5983 32 0.0 0.0 0.0 0.0 - compatIsByteArrayPinned# Basement.Compat.Primitive Basement/Compat/Primitive.hs:67:1-51 5984 32 0.0 0.0 0.0 0.0 - toPinnedStatus# Basement.Compat.Primitive Basement/Compat/Primitive.hs:(47,1)-(48,27) 5985 32 0.0 0.0 0.0 0.0 - unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 5986 32 0.0 0.0 0.0 0.0 - word EVM.Types src/EVM/Types.hs:521:1-21 5960 0 0.0 0.0 0.0 0.0 - word256 EVM.Types src/EVM/Types.hs:(510,1)-(518,67) 5987 1 0.0 0.0 0.0 0.0 - padLeft EVM.Types src/EVM/Types.hs:495:1-54 5988 1 0.0 0.0 0.0 0.0 - bytesRead Data.Serialize.Get src/Data/Serialize/Get.hs:838:1-45 5989 0 0.0 0.0 0.0 0.0 - exec1 EVM src/EVM.hs:(547,1)-(1323,42) 4428 1 0.0 0.0 0.0 0.0 - genLiteral Data.SBV.Core.Model Data/SBV/Core/Model.hs:99:1-48 4558 3 0.0 0.0 0.0 0.0 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 4562 3 0.0 0.0 0.0 0.0 - svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 4563 3 0.0 0.0 0.0 0.0 - svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 4564 3 0.0 0.0 0.0 0.0 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 4565 3 0.0 0.0 0.0 0.0 - finishFrame EVM src/EVM.hs:(2237,1)-(2357,20) 5235 1 0.0 0.0 0.0 0.0 - next EVM src/EVM.hs:543:1-46 4513 1 0.0 0.0 0.0 0.0 - opSize EVM src/EVM.hs:(2542,1)-(2543,37) 4515 1 0.0 0.0 0.0 0.0 - num EVM.Types src/EVM/Types.hs:492:1-18 5952 1 0.0 0.0 0.0 0.0 - forceConcrete EVM src/EVM.hs:(1846,1)-(1848,22) 4484 0 0.0 0.0 0.0 0.0 - next EVM src/EVM.hs:543:1-46 4485 1 0.0 0.0 0.0 0.0 - opSize EVM src/EVM.hs:(2542,1)-(2543,37) 4487 1 0.0 0.0 0.0 0.0 - litWord EVM.Symbolic src/EVM/Symbolic.hs:24:1-52 6150 0 0.0 0.0 0.0 0.0 - limitStack EVM src/EVM.hs:(1809,1)-(1813,17) 4615 0 0.0 0.0 0.0 0.0 - next EVM src/EVM.hs:543:1-46 4616 1 0.0 0.0 0.0 0.0 - opSize EVM src/EVM.hs:(2542,1)-(2543,37) 4617 1 0.0 0.0 0.0 0.0 - litWord EVM.Symbolic src/EVM/Symbolic.hs:24:1-52 5176 0 0.0 0.0 0.0 0.0 - litWord EVM.Symbolic src/EVM/Symbolic.hs:24:1-52 6099 0 0.0 0.0 0.0 0.0 - notStatic EVM src/EVM.hs:(1816,1)-(1820,17) 4611 0 0.0 0.0 0.0 0.0 - next EVM src/EVM.hs:543:1-46 4612 1 0.0 0.0 0.0 0.0 - opSize EVM src/EVM.hs:(2542,1)-(2543,37) 4614 1 0.0 0.0 0.0 0.0 - stackOp2 EVM src/EVM.hs:(2500,1)-(2507,14) 4573 0 0.0 0.0 0.0 0.0 - .^ Data.SBV.Core.Model Data/SBV/Core/Model.hs:(1262,1)-(1280,49) 4575 0 0.0 0.0 0.0 0.0 - genLiteral Data.SBV.Core.Model Data/SBV/Core/Model.hs:99:1-48 4584 1 0.0 0.0 0.0 0.0 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 4585 1 0.0 0.0 0.0 0.0 - svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 4586 1 0.0 0.0 0.0 0.0 - svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 4587 1 0.0 0.0 0.0 0.0 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 4588 1 0.0 0.0 0.0 0.0 - finalize EVM src/EVM.hs:(1721,1)-(1790,66) 4712 1 0.0 0.0 0.0 0.0 - initialContract EVM src/EVM.hs:(516,1)-(533,39) 4759 1 0.0 0.0 0.0 0.0 - mkCodeOps EVM src/EVM.hs:(2721,1)-(2739,79) 4791 1 0.0 0.0 0.0 0.0 - marray# Data.Primitive.Array Data/Primitive/Array.hs:92:5-11 4796 1 0.0 0.0 0.0 0.0 - sChunks Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:122:30-36 4794 1 0.0 0.0 0.0 0.0 - sSize Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:124:30-34 4793 1 0.0 0.0 0.0 0.0 - unId Data.Vector.Fusion.Util Data/Vector/Fusion/Util.hs:25:21-24 4795 1 0.0 0.0 0.0 0.0 - upperBound Data.Vector.Fusion.Bundle.Size Data/Vector/Fusion/Bundle/Size.hs:(126,1)-(128,30) 4792 1 0.0 0.0 0.0 0.0 - mkOpIxMap EVM src/EVM.hs:(2549,1)-(2586,83) 4789 1 0.0 0.0 0.0 0.0 - len EVM.Symbolic src/EVM/Symbolic.hs:(161,1)-(162,38) 4790 1 0.0 0.0 0.0 0.0 - stripBytecodeMetadata EVM.Solidity src/EVM/Solidity.hs:(569,1)-(573,22) 4767 1 0.0 0.0 0.0 0.0 - keccak EVM.Types src/EVM/Types.hs:(580,1)-(583,12) 4760 0 0.0 0.0 0.0 0.0 - keccakBytes EVM.Types src/EVM/Types.hs:(570,1)-(573,15) 4762 0 0.0 0.0 0.0 0.0 - hash Crypto.Hash Crypto/Hash.hs:58:1-47 4763 1 0.0 0.0 0.0 0.0 - hashFinalize Crypto.Hash Crypto/Hash.hs:(92,1)-(95,17) 4764 1 0.0 0.0 0.0 0.0 - allocAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:74:1-45 4770 1 0.0 0.0 0.0 0.0 - new Basement.Block.Base Basement/Block/Base.hs:304:1-76 4771 1 0.0 0.0 0.0 0.0 - unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 4772 1 0.0 0.0 0.0 0.0 - withMutablePtrHint Basement.Block.Base Basement/Block/Base.hs:(475,1)-(489,39) 4773 1 0.0 0.0 0.0 0.0 - copy Data.ByteArray.Methods Data/ByteArray/Methods.hs:(223,1)-(226,21) 4778 1 0.0 0.0 0.0 0.0 - isMutablePinned Basement.Block.Base Basement/Block/Base.hs:100:1-90 4774 1 0.0 0.0 0.0 0.0 - compatIsMutableByteArrayPinned# Basement.Compat.Primitive Basement/Compat/Primitive.hs:70:1-65 4775 1 0.0 0.0 0.0 0.0 - toPinnedStatus# Basement.Compat.Primitive Basement/Compat/Primitive.hs:(47,1)-(48,27) 4776 1 0.0 0.0 0.0 0.0 - unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 4777 1 0.0 0.0 0.0 0.0 - hashInit Crypto.Hash Crypto/Hash.hs:(66,1)-(67,24) 4768 1 0.0 0.0 0.0 0.0 - allocAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:74:1-45 4769 1 0.0 0.0 0.0 0.0 - hashUpdate Crypto.Hash Crypto/Hash.hs:(71,1)-(73,37) 4765 1 0.0 0.0 0.0 0.0 - null Data.ByteArray.Methods Data/ByteArray/Methods.hs:92:1-22 4766 1 0.0 0.0 0.0 0.0 - unpack Data.ByteArray.Methods Data/ByteArray/Methods.hs:(104,1)-(110,34) 4779 1 0.0 0.0 0.0 0.0 - unsafeCast Basement.Block Basement/Block.hs:421:1-32 4780 33 0.0 0.0 0.0 0.0 - withPtr Basement.Block.Base Basement/Block/Base.hs:(402,1)-(411,31) 4781 32 0.0 0.0 0.0 0.0 - isPinned Basement.Block.Base Basement/Block/Base.hs:97:1-67 4782 32 0.0 0.0 0.0 0.0 - compatIsByteArrayPinned# Basement.Compat.Primitive Basement/Compat/Primitive.hs:67:1-51 4783 32 0.0 0.0 0.0 0.0 - toPinnedStatus# Basement.Compat.Primitive Basement/Compat/Primitive.hs:(47,1)-(48,27) 4784 32 0.0 0.0 0.0 0.0 - unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 4785 32 0.0 0.0 0.0 0.0 - word EVM.Types src/EVM/Types.hs:521:1-21 4761 0 0.0 0.0 0.0 0.0 - word256 EVM.Types src/EVM/Types.hs:(510,1)-(518,67) 4786 1 0.0 0.0 0.0 0.0 - padLeft EVM.Types src/EVM/Types.hs:495:1-54 4787 1 0.0 0.0 0.0 0.0 - bytesRead Data.Serialize.Get src/Data/Serialize/Get.hs:838:1-45 4788 0 0.0 0.0 0.0 0.0 - popTrace EVM src/EVM.hs:(2450,1)-(2454,42) 4895 1 0.0 0.0 0.0 0.0 - push EVM src/EVM.hs:2474:1-30 5203 1 0.0 0.0 0.0 0.0 - num EVM.Types src/EVM/Types.hs:492:1-18 5212 1 0.0 0.0 0.0 0.0 - resetState EVM src/EVM.hs:(2210,1)-(2213,26) 4837 1 0.0 0.0 0.0 0.0 - touchAccount EVM src/EVM.hs:1895:1-57 4715 1 0.0 0.0 0.0 0.0 - accessMemoryRange EVM src/EVM.hs:(2383,1)-(2387,53) 4459 0 0.0 0.0 0.0 0.0 - accessMemoryWord EVM src/EVM.hs:2391:1-53 4457 0 0.0 0.0 0.0 0.0 - accessStorage EVM src/EVM.hs:(1674,1)-(1702,35) 4530 0 0.0 0.0 0.0 0.0 - genLiteral Data.SBV.Core.Model Data/SBV/Core/Model.hs:99:1-48 4545 1 0.0 0.0 0.0 0.0 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 4595 1 0.0 0.0 0.0 0.0 - svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 4596 1 0.0 0.0 0.0 0.0 - svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 4597 1 0.0 0.0 0.0 0.0 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 4598 1 0.0 0.0 0.0 0.0 - accessUnboundedMemoryRange EVM src/EVM.hs:(2368,1)-(2375,14) 4474 0 0.0 0.0 0.0 0.0 - num EVM.Types src/EVM/Types.hs:492:1-18 4478 1 0.0 0.0 0.0 0.0 - accountEmpty EVM src/EVM.hs:(1712,1)-(1717,26) 4800 0 0.0 0.0 0.0 0.0 - burn EVM src/EVM.hs:(1826,1)-(1838,38) 4441 0 0.1 0.0 0.1 0.0 - copyBytesToMemory EVM src/EVM.hs:(2395,1)-(2400,45) 4661 0 0.0 0.0 0.0 0.0 - copyCallBytesToMemory EVM src/EVM.hs:(2404,1)-(2409,66) 6268 0 0.0 0.0 0.0 0.0 - costOfCall EVM src/EVM.hs:(2748,1)-(2762,40) 6070 0 0.0 0.0 0.0 0.0 - create EVM src/EVM.hs:(2123,1)-(2184,30) 5123 0 0.0 0.0 0.0 0.0 - litWord EVM.Symbolic src/EVM/Symbolic.hs:24:1-52 5124 0 0.0 0.0 0.0 0.0 - delegateCall EVM src/EVM.hs:(2052,1)-(2108,31) 6024 0 0.0 0.0 0.0 0.0 - finishFrame EVM src/EVM.hs:(2237,1)-(2357,20) 5202 0 0.0 0.0 0.0 0.0 - initialContract EVM src/EVM.hs:(516,1)-(533,39) 4799 0 0.0 0.0 0.0 0.0 - makeVm EVM src/EVM.hs:(449,1)-(512,30) 4423 0 0.0 0.0 0.0 0.0 - CAF EVM.ABI 3446 0 0.0 0.0 0.0 0.0 - abiKind EVM.ABI src/EVM/ABI.hs:(191,1)-(197,33) 5601 1 0.0 0.0 0.0 0.0 - abiTypeSolidity EVM.ABI src/EVM/ABI.hs:(213,1)-(223,104) 6439 1 0.0 0.0 0.0 0.0 - abiValueType EVM.ABI src/EVM/ABI.hs:(200,1)-(210,58) 5603 1 0.0 0.0 0.0 0.0 - decodeAbiValue EVM.ABI src/EVM/ABI.hs:364:1-32 5888 1 0.0 0.0 0.0 0.0 - emptyAbi EVM.ABI src/EVM/ABI.hs:429:1-26 4953 1 0.0 0.0 0.0 0.0 - marray# Data.Primitive.Array Data/Primitive/Array.hs:92:5-11 4958 1 0.0 0.0 0.0 0.0 - sChunks Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:122:30-36 4956 1 0.0 0.0 0.0 0.0 - sSize Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:124:30-34 4955 1 0.0 0.0 0.0 0.0 - unId Data.Vector.Fusion.Util Data/Vector/Fusion/Util.hs:25:21-24 4957 1 0.0 0.0 0.0 0.0 - upperBound Data.Vector.Fusion.Bundle.Size Data/Vector/Fusion/Bundle/Size.hs:(126,1)-(128,30) 4954 1 0.0 0.0 0.0 0.0 - encodeAbiValue EVM.ABI src/EVM/ABI.hs:361:1-50 6372 1 0.0 0.0 0.0 0.0 - genAbiValue EVM.ABI src/EVM/ABI.hs:(440,1)-(466,62) 5584 1 0.0 0.0 0.0 0.0 - sized Test.QuickCheck.Gen Test/QuickCheck/Gen.hs:99:1-52 5620 1 0.0 0.0 0.0 0.0 - getAbi EVM.ABI src/EVM/ABI.hs:(226,1)-(259,66) 5891 1 0.0 0.0 0.0 0.0 - parseTypeName EVM.ABI src/EVM/ABI.hs:375:1-50 5606 1 0.0 0.0 0.0 0.0 - putAbi EVM.ABI src/EVM/ABI.hs:(262,1)-(291,15) 4951 1 0.0 0.0 0.0 0.0 - CAF EVM.Concrete 3445 0 0.0 0.0 0.0 0.0 - readMemoryWord EVM.Concrete src/EVM/Concrete.hs:(62,1)-(70,19) 4988 0 0.0 0.0 0.0 0.0 - setMemoryWord EVM.Concrete src/EVM/Concrete.hs:(82,1)-(83,43) 4692 0 0.0 0.0 0.0 0.0 - CAF EVM.Dapp 3444 0 0.0 0.0 0.0 0.0 - unitTestMarkerAbi EVM.Dapp src/EVM/Dapp.hs:111:1-54 4204 1 0.0 0.0 0.0 0.0 - abiKeccak EVM.Types src/EVM/Types.hs:(586,1)-(590,14) 4205 0 0.0 0.0 0.0 0.0 - word32 EVM.Types src/EVM/Types.hs:(576,1)-(577,52) 4232 1 0.0 0.0 0.0 0.0 - keccakBytes EVM.Types src/EVM/Types.hs:(570,1)-(573,15) 4206 0 0.0 0.0 0.0 0.0 - hash Crypto.Hash Crypto/Hash.hs:58:1-47 4207 1 0.0 0.0 0.0 0.0 - hashFinalize Crypto.Hash Crypto/Hash.hs:(92,1)-(95,17) 4208 1 0.0 0.0 0.0 0.0 - allocAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:74:1-45 4216 1 0.0 0.0 0.0 0.0 - new Basement.Block.Base Basement/Block/Base.hs:304:1-76 4217 1 0.0 0.0 0.0 0.0 - unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 4218 1 0.0 0.0 0.0 0.0 - withMutablePtrHint Basement.Block.Base Basement/Block/Base.hs:(475,1)-(489,39) 4219 1 0.0 0.0 0.0 0.0 - copy Data.ByteArray.Methods Data/ByteArray/Methods.hs:(223,1)-(226,21) 4224 1 0.0 0.0 0.0 0.0 - isMutablePinned Basement.Block.Base Basement/Block/Base.hs:100:1-90 4220 1 0.0 0.0 0.0 0.0 - compatIsMutableByteArrayPinned# Basement.Compat.Primitive Basement/Compat/Primitive.hs:70:1-65 4221 1 0.0 0.0 0.0 0.0 - toPinnedStatus# Basement.Compat.Primitive Basement/Compat/Primitive.hs:(47,1)-(48,27) 4222 1 0.0 0.0 0.0 0.0 - unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 4223 1 0.0 0.0 0.0 0.0 - hashInit Crypto.Hash Crypto/Hash.hs:(66,1)-(67,24) 4214 1 0.0 0.0 0.0 0.0 - allocAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:74:1-45 4215 1 0.0 0.0 0.0 0.0 - hashUpdate Crypto.Hash Crypto/Hash.hs:(71,1)-(73,37) 4209 1 0.0 0.0 0.0 0.0 - hashUpdates Crypto.Hash Crypto/Hash.hs:(81,1)-(86,32) 4211 1 0.0 0.0 0.0 0.0 - copyAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:(237,1)-(240,21) 4213 1 0.0 0.0 0.0 0.0 - null Data.ByteArray.Methods Data/ByteArray/Methods.hs:92:1-22 4212 1 0.0 0.0 0.0 0.0 - null Data.ByteArray.Methods Data/ByteArray/Methods.hs:92:1-22 4210 1 0.0 0.0 0.0 0.0 - unpack Data.ByteArray.Methods Data/ByteArray/Methods.hs:(104,1)-(110,34) 4225 1 0.0 0.0 0.0 0.0 - unsafeCast Basement.Block Basement/Block.hs:421:1-32 4226 33 0.0 0.0 0.0 0.0 - withPtr Basement.Block.Base Basement/Block/Base.hs:(402,1)-(411,31) 4227 32 0.0 0.0 0.0 0.0 - isPinned Basement.Block.Base Basement/Block/Base.hs:97:1-67 4228 32 0.0 0.0 0.0 0.0 - compatIsByteArrayPinned# Basement.Compat.Primitive Basement/Compat/Primitive.hs:67:1-51 4229 32 0.0 0.0 0.0 0.0 - toPinnedStatus# Basement.Compat.Primitive Basement/Compat/Primitive.hs:(47,1)-(48,27) 4230 32 0.0 0.0 0.0 0.0 - unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 4231 32 0.0 0.0 0.0 0.0 - unitTestMethods EVM.Dapp src/EVM/Dapp.hs:(150,1)-(155,27) 4234 1 0.0 0.0 0.0 0.0 - mkTest EVM.Dapp src/EVM/Dapp.hs:(117,1)-(120,23) 4237 0 0.0 0.0 0.0 0.0 - CAF EVM.Format 3437 0 0.0 0.0 0.0 0.0 - parenthesise EVM.Format src/EVM/Format.hs:112:1-51 6438 0 0.0 0.0 0.0 0.0 - showAbiValue EVM.Format src/EVM/Format.hs:(83,1)-(96,30) 6469 0 0.0 0.0 0.0 0.0 - CAF EVM.RLP 3431 0 0.0 0.0 0.0 0.0 - rlpAddrFull EVM.RLP src/EVM/RLP.hs:85:1-38 4353 1 0.0 0.0 0.0 0.0 - num EVM.Types src/EVM/Types.hs:492:1-18 4356 1 0.0 0.0 0.0 0.0 - octets EVM.RLP src/EVM/RLP.hs:(66,1)-(67,85) 4364 0 0.0 0.0 0.0 0.0 - rlpWord256 EVM.RLP src/EVM/RLP.hs:(78,1)-(79,28) 4362 0 0.0 0.0 0.0 0.0 - CAF EVM.Solidity 3430 0 0.0 0.0 0.0 0.0 - makeSrcMaps EVM.Solidity src/EVM/Solidity.hs:(227,1)-(271,126) 4202 1 0.0 0.0 0.0 0.0 - readJSON EVM.Solidity src/EVM/Solidity.hs:(329,1)-(331,28) 3839 0 0.0 0.0 0.0 0.0 - readStdJSON EVM.Solidity src/EVM/Solidity.hs:(364,1)-(407,39) 3922 0 0.0 0.0 0.0 0.0 - union Data.HashMap.Base Data/HashMap/Base.hs:1287:1-23 3928 1 0.0 0.0 0.0 0.0 - signature EVM.Solidity src/EVM/Solidity.hs:(468,1)-(478,7) 4174 0 0.0 0.0 0.0 0.0 - CAF EVM.Stepper 3429 0 0.0 0.0 0.0 0.0 - evm EVM.Stepper src/EVM/Stepper.hs:78:1-21 4277 1 0.0 0.0 0.0 0.0 - exec EVM.Stepper src/EVM/Stepper.hs:66:1-21 4292 1 0.0 0.0 0.0 0.0 - execFully EVM.Stepper src/EVM/Stepper.hs:(82,1)-(91,20) 4291 1 0.0 0.0 0.0 0.0 - interpret EVM.Stepper src/EVM/Stepper.hs:(117,1)-(141,33) 4293 0 0.0 0.0 0.0 0.0 - exec EVM.Exec src/EVM/Exec.hs:(48,1)-(51,23) 4294 129 0.0 0.0 0.0 0.0 - CAF EVM.Symbolic 3428 0 0.0 0.0 0.0 0.0 - litAddr EVM.Symbolic src/EVM/Symbolic.hs:27:1-36 4389 1 0.0 0.0 0.0 0.0 - readMemoryWord EVM.Symbolic src/EVM/Symbolic.hs:(183,1)-(184,75) 5015 0 0.0 0.0 0.0 0.0 - litWord EVM.Symbolic src/EVM/Symbolic.hs:24:1-52 5016 0 0.0 0.0 0.0 0.0 - readMemoryWord32 EVM.Symbolic src/EVM/Symbolic.hs:(187,1)-(188,75) 6263 0 0.0 0.0 0.0 0.0 - num EVM.Types src/EVM/Types.hs:492:1-18 6264 0 0.0 0.0 0.0 0.0 - readSWordWithBound EVM.Symbolic src/EVM/Symbolic.hs:(136,1)-(157,48) 4981 0 0.0 0.0 0.0 0.0 - litWord EVM.Symbolic src/EVM/Symbolic.hs:24:1-52 4982 0 0.0 0.0 0.0 0.0 - slt EVM.Symbolic src/EVM/Symbolic.hs:(75,1)-(76,79) 5678 0 0.0 0.0 0.0 0.0 - genLiteral Data.SBV.Core.Model Data/SBV/Core/Model.hs:99:1-48 5706 1 0.0 0.0 0.0 0.0 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 5707 1 0.0 0.0 0.0 0.0 - svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 5708 1 0.0 0.0 0.0 0.0 - svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 5709 1 0.0 0.0 0.0 0.0 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 5710 1 0.0 0.0 0.0 0.0 - CAF EVM.Transaction 3426 0 0.0 0.0 0.0 0.0 - setupTx EVM.Transaction src/EVM/Transaction.hs:(171,1)-(176,38) 5289 0 0.0 0.0 0.0 0.0 - CAF EVM.Types 3423 0 0.0 0.0 0.0 0.0 - abiKeccak EVM.Types src/EVM/Types.hs:(586,1)-(590,14) 4166 1 0.0 0.0 0.0 0.0 - keccak EVM.Types src/EVM/Types.hs:(580,1)-(583,12) 4125 1 0.0 0.0 0.0 0.0 - keccakBytes EVM.Types src/EVM/Types.hs:(570,1)-(573,15) 4129 1 0.0 0.0 0.0 0.0 - word EVM.Types src/EVM/Types.hs:521:1-21 4127 1 0.0 0.0 0.0 0.0 - hexText EVM.Types src/EVM/Types.hs:(460,1)-(463,52) 6382 0 0.0 0.0 0.0 0.0 - w256lit EVM.Types src/EVM/Types.hs:346:1-48 4451 0 0.0 0.0 0.0 0.0 - CAF EVM.UnitTest 3422 0 0.0 0.0 0.0 0.0 - defaultBalanceForCreator EVM.UnitTest src/EVM/UnitTest.hs:129:1-53 4891 1 0.0 0.0 0.0 0.0 - defaultGasForCreating EVM.UnitTest src/EVM/UnitTest.hs:123:1-38 4392 1 0.0 0.0 0.0 0.0 - defaultGasForInvoking EVM.UnitTest src/EVM/UnitTest.hs:126:1-38 4894 1 0.0 0.0 0.0 0.0 - defaultMaxCodeSize EVM.UnitTest src/EVM/UnitTest.hs:135:1-31 4395 1 0.0 0.0 0.0 0.0 - execWithTraceId EVM.UnitTest src/EVM/UnitTest.hs:(282,1)-(283,51) 5335 1 0.0 0.0 0.0 0.0 - runWithTraceId EVM.UnitTest src/EVM/UnitTest.hs:(286,1)-(301,90) 5337 1 0.0 0.0 0.0 0.0 - abiCall EVM.UnitTest src/EVM/UnitTest.hs:(842,1)-(845,53) 4914 0 0.0 0.0 0.0 0.0 - litWord EVM.Symbolic src/EVM/Symbolic.hs:24:1-52 4915 0 0.0 0.0 0.0 0.0 - checkFailures EVM.UnitTest src/EVM/UnitTest.hs:(195,1)-(210,58) 5765 0 0.0 0.0 0.0 0.0 - failOutput EVM.UnitTest src/EVM/UnitTest.hs:(756,1)-(767,3) 6423 0 0.0 0.0 0.0 0.0 - formatTestLog EVM.UnitTest src/EVM/UnitTest.hs:(779,1)-(835,61) 6450 0 0.0 0.0 0.0 0.0 - formatTestLogs EVM.UnitTest src/EVM/UnitTest.hs:(770,1)-(773,47) 6451 0 0.0 0.0 0.0 0.0 - fuzzRun EVM.UnitTest src/EVM/UnitTest.hs:(586,1)-(615,40) 5940 0 0.0 0.0 0.0 0.0 - getParametersFromEnvironmentVariables EVM.UnitTest src/EVM/UnitTest.hs:(910,1)-(942,38) 4341 0 0.0 0.0 0.0 0.0 - createAddress EVM.Concrete src/EVM/Concrete.hs:108:1-72 4342 1 0.0 0.0 0.0 0.0 - num EVM.Types src/EVM/Types.hs:492:1-18 4343 1 0.0 0.0 0.0 0.0 - rlpList EVM.RLP src/EVM/RLP.hs:63:1-30 4351 1 0.0 0.0 0.0 0.0 - rlpencode EVM.RLP src/EVM/RLP.hs:(50,1)-(52,70) 4352 3 0.0 0.0 0.0 0.0 - encodeLen EVM.RLP src/EVM/RLP.hs:(55,1)-(60,44) 4359 2 0.0 0.0 0.0 0.0 - num EVM.Types src/EVM/Types.hs:492:1-18 4360 2 0.0 0.0 0.0 0.0 - rlpWord256 EVM.RLP src/EVM/RLP.hs:(78,1)-(79,28) 4361 1 0.0 0.0 0.0 0.0 - octets EVM.RLP src/EVM/RLP.hs:(66,1)-(67,85) 4363 1 0.0 0.0 0.0 0.0 - keccak EVM.Types src/EVM/Types.hs:(580,1)-(583,12) 4344 0 0.0 0.0 0.0 0.0 - keccakBytes EVM.Types src/EVM/Types.hs:(570,1)-(573,15) 4346 0 0.0 0.0 0.0 0.0 - hash Crypto.Hash Crypto/Hash.hs:58:1-47 4347 1 0.0 0.0 0.0 0.0 - hashFinalize Crypto.Hash Crypto/Hash.hs:(92,1)-(95,17) 4348 1 0.0 0.0 0.0 0.0 - allocAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:74:1-45 4370 1 0.0 0.0 0.0 0.0 - new Basement.Block.Base Basement/Block/Base.hs:304:1-76 4371 1 0.0 0.0 0.0 0.0 - unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 4372 1 0.0 0.0 0.0 0.0 - withMutablePtrHint Basement.Block.Base Basement/Block/Base.hs:(475,1)-(489,39) 4373 1 0.0 0.0 0.0 0.0 - copy Data.ByteArray.Methods Data/ByteArray/Methods.hs:(223,1)-(226,21) 4378 1 0.0 0.0 0.0 0.0 - isMutablePinned Basement.Block.Base Basement/Block/Base.hs:100:1-90 4374 1 0.0 0.0 0.0 0.0 - compatIsMutableByteArrayPinned# Basement.Compat.Primitive Basement/Compat/Primitive.hs:70:1-65 4375 1 0.0 0.0 0.0 0.0 - toPinnedStatus# Basement.Compat.Primitive Basement/Compat/Primitive.hs:(47,1)-(48,27) 4376 1 0.0 0.0 0.0 0.0 - unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 4377 1 0.0 0.0 0.0 0.0 - hashInit Crypto.Hash Crypto/Hash.hs:(66,1)-(67,24) 4368 1 0.0 0.0 0.0 0.0 - allocAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:74:1-45 4369 1 0.0 0.0 0.0 0.0 - hashUpdate Crypto.Hash Crypto/Hash.hs:(71,1)-(73,37) 4349 1 0.0 0.0 0.0 0.0 - hashUpdates Crypto.Hash Crypto/Hash.hs:(81,1)-(86,32) 4365 1 0.0 0.0 0.0 0.0 - copyAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:(237,1)-(240,21) 4367 1 0.0 0.0 0.0 0.0 - null Data.ByteArray.Methods Data/ByteArray/Methods.hs:92:1-22 4366 1 0.0 0.0 0.0 0.0 - null Data.ByteArray.Methods Data/ByteArray/Methods.hs:92:1-22 4350 1 0.0 0.0 0.0 0.0 - unpack Data.ByteArray.Methods Data/ByteArray/Methods.hs:(104,1)-(110,34) 4379 1 0.0 0.0 0.0 0.0 - unsafeCast Basement.Block Basement/Block.hs:421:1-32 4380 33 0.0 0.0 0.0 0.0 - withPtr Basement.Block.Base Basement/Block/Base.hs:(402,1)-(411,31) 4381 32 0.0 0.0 0.0 0.0 - isPinned Basement.Block.Base Basement/Block/Base.hs:97:1-67 4382 32 0.0 0.0 0.0 0.0 - compatIsByteArrayPinned# Basement.Compat.Primitive Basement/Compat/Primitive.hs:67:1-51 4383 32 0.0 0.0 0.0 0.0 - toPinnedStatus# Basement.Compat.Primitive Basement/Compat/Primitive.hs:(47,1)-(48,27) 4384 32 0.0 0.0 0.0 0.0 - unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 4385 32 0.0 0.0 0.0 0.0 - word EVM.Types src/EVM/Types.hs:521:1-21 4345 0 0.0 0.0 0.0 0.0 - word256 EVM.Types src/EVM/Types.hs:(510,1)-(518,67) 4386 1 0.0 0.0 0.0 0.0 - padLeft EVM.Types src/EVM/Types.hs:495:1-54 4387 1 0.0 0.0 0.0 0.0 - bytesRead Data.Serialize.Get src/Data/Serialize/Get.hs:838:1-45 4388 0 0.0 0.0 0.0 0.0 - rlpAddrFull EVM.RLP src/EVM/RLP.hs:85:1-38 4354 0 0.0 0.0 0.0 0.0 - octetsFull EVM.RLP src/EVM/RLP.hs:(70,1)-(71,67) 4355 1 0.0 0.0 0.0 0.0 - num EVM.Types src/EVM/Types.hs:492:1-18 4357 0 0.0 0.0 0.0 0.0 - indentLines EVM.UnitTest src/EVM/UnitTest.hs:(736,1)-(738,45) 6501 0 0.0 0.0 0.0 0.0 - initialUnitTestVm EVM.UnitTest src/EVM/UnitTest.hs:(862,1)-(892,61) 4340 0 0.0 0.0 0.0 0.0 - genLiteral Data.SBV.Core.Model Data/SBV/Core/Model.hs:99:1-48 4618 1 0.0 0.0 0.0 0.0 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 4619 1 0.0 0.0 0.0 0.0 - initialContract EVM src/EVM.hs:(516,1)-(533,39) 4718 1 0.0 0.0 0.0 0.0 - mkCodeOps EVM src/EVM.hs:(2721,1)-(2739,79) 4750 1 0.0 0.0 0.0 0.0 - marray# Data.Primitive.Array Data/Primitive/Array.hs:92:5-11 4755 1 0.0 0.0 0.0 0.0 - sChunks Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:122:30-36 4753 1 0.0 0.0 0.0 0.0 - sSize Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:124:30-34 4752 1 0.0 0.0 0.0 0.0 - unId Data.Vector.Fusion.Util Data/Vector/Fusion/Util.hs:25:21-24 4754 1 0.0 0.0 0.0 0.0 - upperBound Data.Vector.Fusion.Bundle.Size Data/Vector/Fusion/Bundle/Size.hs:(126,1)-(128,30) 4751 1 0.0 0.0 0.0 0.0 - mkOpIxMap EVM src/EVM.hs:(2549,1)-(2586,83) 4748 1 0.0 0.0 0.0 0.0 - len EVM.Symbolic src/EVM/Symbolic.hs:(161,1)-(162,38) 4749 1 0.0 0.0 0.0 0.0 - stripBytecodeMetadata EVM.Solidity src/EVM/Solidity.hs:(569,1)-(573,22) 4726 1 0.0 0.0 0.0 0.0 - keccak EVM.Types src/EVM/Types.hs:(580,1)-(583,12) 4719 0 0.0 0.0 0.0 0.0 - keccakBytes EVM.Types src/EVM/Types.hs:(570,1)-(573,15) 4721 0 0.0 0.0 0.0 0.0 - hash Crypto.Hash Crypto/Hash.hs:58:1-47 4722 1 0.0 0.0 0.0 0.0 - hashFinalize Crypto.Hash Crypto/Hash.hs:(92,1)-(95,17) 4723 1 0.0 0.0 0.0 0.0 - allocAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:74:1-45 4729 1 0.0 0.0 0.0 0.0 - new Basement.Block.Base Basement/Block/Base.hs:304:1-76 4730 1 0.0 0.0 0.0 0.0 - unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 4731 1 0.0 0.0 0.0 0.0 - withMutablePtrHint Basement.Block.Base Basement/Block/Base.hs:(475,1)-(489,39) 4732 1 0.0 0.0 0.0 0.0 - copy Data.ByteArray.Methods Data/ByteArray/Methods.hs:(223,1)-(226,21) 4737 1 0.0 0.0 0.0 0.0 - isMutablePinned Basement.Block.Base Basement/Block/Base.hs:100:1-90 4733 1 0.0 0.0 0.0 0.0 - compatIsMutableByteArrayPinned# Basement.Compat.Primitive Basement/Compat/Primitive.hs:70:1-65 4734 1 0.0 0.0 0.0 0.0 - toPinnedStatus# Basement.Compat.Primitive Basement/Compat/Primitive.hs:(47,1)-(48,27) 4735 1 0.0 0.0 0.0 0.0 - unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 4736 1 0.0 0.0 0.0 0.0 - hashInit Crypto.Hash Crypto/Hash.hs:(66,1)-(67,24) 4727 1 0.0 0.0 0.0 0.0 - allocAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:74:1-45 4728 1 0.0 0.0 0.0 0.0 - hashUpdate Crypto.Hash Crypto/Hash.hs:(71,1)-(73,37) 4724 1 0.0 0.0 0.0 0.0 - null Data.ByteArray.Methods Data/ByteArray/Methods.hs:92:1-22 4725 1 0.0 0.0 0.0 0.0 - unpack Data.ByteArray.Methods Data/ByteArray/Methods.hs:(104,1)-(110,34) 4738 1 0.0 0.0 0.0 0.0 - unsafeCast Basement.Block Basement/Block.hs:421:1-32 4739 33 0.0 0.0 0.0 0.0 - withPtr Basement.Block.Base Basement/Block/Base.hs:(402,1)-(411,31) 4740 32 0.0 0.0 0.0 0.0 - isPinned Basement.Block.Base Basement/Block/Base.hs:97:1-67 4741 32 0.0 0.0 0.0 0.0 - compatIsByteArrayPinned# Basement.Compat.Primitive Basement/Compat/Primitive.hs:67:1-51 4742 32 0.0 0.0 0.0 0.0 - toPinnedStatus# Basement.Compat.Primitive Basement/Compat/Primitive.hs:(47,1)-(48,27) 4743 32 0.0 0.0 0.0 0.0 - unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 4744 32 0.0 0.0 0.0 0.0 - word EVM.Types src/EVM/Types.hs:521:1-21 4720 0 0.0 0.0 0.0 0.0 - word256 EVM.Types src/EVM/Types.hs:(510,1)-(518,67) 4745 1 0.0 0.0 0.0 0.0 - padLeft EVM.Types src/EVM/Types.hs:495:1-54 4746 1 0.0 0.0 0.0 0.0 - bytesRead Data.Serialize.Get src/Data/Serialize/Get.hs:838:1-45 4747 0 0.0 0.0 0.0 0.0 - svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 4620 1 0.0 0.0 0.0 0.0 - svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 4621 1 0.0 0.0 0.0 0.0 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 4622 1 0.0 0.0 0.0 0.0 - berlin EVM.FeeSchedule src/EVM/FeeSchedule.hs:185:1-25 4397 0 0.0 0.0 0.0 0.0 - eip2929 EVM.FeeSchedule src/EVM/FeeSchedule.hs:(175,1)-(182,3) 4398 1 0.0 0.0 0.0 0.0 - istanbul EVM.FeeSchedule src/EVM/FeeSchedule.hs:170:1-61 4399 1 0.0 0.0 0.0 0.0 - eip1108 EVM.FeeSchedule src/EVM/FeeSchedule.hs:(136,1)-(141,3) 4407 1 0.0 0.0 0.0 0.0 - eip1884 EVM.FeeSchedule src/EVM/FeeSchedule.hs:(146,1)-(150,3) 4406 1 0.0 0.0 0.0 0.0 - eip2028 EVM.FeeSchedule src/EVM/FeeSchedule.hs:(155,1)-(157,3) 4405 1 0.0 0.0 0.0 0.0 - eip2200 EVM.FeeSchedule src/EVM/FeeSchedule.hs:(162,1)-(167,3) 4404 1 0.0 0.0 0.0 0.0 - metropolis EVM.FeeSchedule src/EVM/FeeSchedule.hs:131:1-40 4400 1 0.0 0.0 0.0 0.0 - eip150 EVM.FeeSchedule src/EVM/FeeSchedule.hs:(62,1)-(69,3) 4401 1 0.0 0.0 0.0 0.0 - eip160 EVM.FeeSchedule src/EVM/FeeSchedule.hs:(74,1)-(75,20) 4403 1 0.0 0.0 0.0 0.0 - homestead EVM.FeeSchedule src/EVM/FeeSchedule.hs:(78,1)-(128,3) 4402 1 0.0 0.0 0.0 0.0 - initializeUnitTest EVM.UnitTest src/EVM/UnitTest.hs:(142,1)-(172,17) 4287 0 0.0 0.0 0.0 0.0 - pushTrace EVM src/EVM.hs:(2438,1)-(2441,59) 4288 2 0.0 0.0 0.0 0.0 - withTraceLocation EVM src/EVM.hs:(2426,1)-(2435,5) 4290 2 0.0 0.0 0.0 0.0 - abiKeccak EVM.Types src/EVM/Types.hs:(586,1)-(590,14) 4804 0 0.0 0.0 0.0 0.0 - word32 EVM.Types src/EVM/Types.hs:(576,1)-(577,52) 4831 1 0.0 0.0 0.0 0.0 - keccakBytes EVM.Types src/EVM/Types.hs:(570,1)-(573,15) 4805 0 0.0 0.0 0.0 0.0 - hash Crypto.Hash Crypto/Hash.hs:58:1-47 4806 1 0.0 0.0 0.0 0.0 - hashFinalize Crypto.Hash Crypto/Hash.hs:(92,1)-(95,17) 4807 1 0.0 0.0 0.0 0.0 - allocAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:74:1-45 4815 1 0.0 0.0 0.0 0.0 - new Basement.Block.Base Basement/Block/Base.hs:304:1-76 4816 1 0.0 0.0 0.0 0.0 - unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 4817 1 0.0 0.0 0.0 0.0 - withMutablePtrHint Basement.Block.Base Basement/Block/Base.hs:(475,1)-(489,39) 4818 1 0.0 0.0 0.0 0.0 - copy Data.ByteArray.Methods Data/ByteArray/Methods.hs:(223,1)-(226,21) 4823 1 0.0 0.0 0.0 0.0 - isMutablePinned Basement.Block.Base Basement/Block/Base.hs:100:1-90 4819 1 0.0 0.0 0.0 0.0 - compatIsMutableByteArrayPinned# Basement.Compat.Primitive Basement/Compat/Primitive.hs:70:1-65 4820 1 0.0 0.0 0.0 0.0 - toPinnedStatus# Basement.Compat.Primitive Basement/Compat/Primitive.hs:(47,1)-(48,27) 4821 1 0.0 0.0 0.0 0.0 - unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 4822 1 0.0 0.0 0.0 0.0 - hashInit Crypto.Hash Crypto/Hash.hs:(66,1)-(67,24) 4813 1 0.0 0.0 0.0 0.0 - allocAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:74:1-45 4814 1 0.0 0.0 0.0 0.0 - hashUpdate Crypto.Hash Crypto/Hash.hs:(71,1)-(73,37) 4808 1 0.0 0.0 0.0 0.0 - hashUpdates Crypto.Hash Crypto/Hash.hs:(81,1)-(86,32) 4810 1 0.0 0.0 0.0 0.0 - copyAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:(237,1)-(240,21) 4812 1 0.0 0.0 0.0 0.0 - null Data.ByteArray.Methods Data/ByteArray/Methods.hs:92:1-22 4811 1 0.0 0.0 0.0 0.0 - null Data.ByteArray.Methods Data/ByteArray/Methods.hs:92:1-22 4809 1 0.0 0.0 0.0 0.0 - unpack Data.ByteArray.Methods Data/ByteArray/Methods.hs:(104,1)-(110,34) 4824 1 0.0 0.0 0.0 0.0 - unsafeCast Basement.Block Basement/Block.hs:421:1-32 4825 33 0.0 0.0 0.0 0.0 - withPtr Basement.Block.Base Basement/Block/Base.hs:(402,1)-(411,31) 4826 32 0.0 0.0 0.0 0.0 - isPinned Basement.Block.Base Basement/Block/Base.hs:97:1-67 4827 32 0.0 0.0 0.0 0.0 - compatIsByteArrayPinned# Basement.Compat.Primitive Basement/Compat/Primitive.hs:67:1-51 4828 32 0.0 0.0 0.0 0.0 - toPinnedStatus# Basement.Compat.Primitive Basement/Compat/Primitive.hs:(47,1)-(48,27) 4829 32 0.0 0.0 0.0 0.0 - unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 4830 32 0.0 0.0 0.0 0.0 - runUnitTestContract EVM.UnitTest src/EVM/UnitTest.hs:(477,1)-(528,68) 5941 0 0.0 0.0 0.0 0.0 - CAF EVM.Mutate 3420 0 0.0 0.0 0.0 0.0 - fixAbiUInt EVM.Mutate src/EVM/Mutate.hs:112:1-50 6331 0 0.0 0.0 0.0 0.0 - CAF EVM.Exec 3417 0 0.0 0.0 0.0 0.0 - ethrunAddress EVM.Exec src/EVM/Exec.hs:19:1-63 4358 1 0.0 0.0 0.0 0.0 - CAF Data.SBV.Control 3234 0 0.0 0.0 0.0 0.0 - query Data.SBV.Control Data/SBV/Control.hs:105:1-40 3627 1 0.0 0.0 0.0 0.0 - CAF Data.SBV.Client.BaseIO 3231 0 0.0 0.0 0.0 0.0 - runSMTWith Data.SBV.Client.BaseIO Data/SBV/Client/BaseIO.hs:223:1-29 3609 1 0.0 0.0 0.0 0.0 - CAF Data.SBV.Core.Concrete 3230 0 0.0 0.0 0.0 0.0 - falseCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:263:1-31 3614 1 0.0 0.0 0.0 0.0 - trueCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:267:1-31 3626 1 0.0 0.0 0.0 0.0 - CAF Data.SBV.Core.Model 3227 0 0.0 0.0 0.0 0.0 - genLiteral Data.SBV.Core.Model Data/SBV/Core/Model.hs:99:1-48 4432 1 0.0 0.0 0.0 0.0 - CAF Data.SBV.Core.Operations 3226 0 0.0 0.0 0.0 0.0 - svFalse Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:77:1-35 4567 1 0.0 0.0 0.0 0.0 - svNot Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(417,1)-(423,34) 4590 1 0.0 0.0 0.0 0.0 - svShiftLeft Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:719:1-26 5944 1 0.0 0.0 0.0 0.0 - svShiftRight Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:726:1-28 4979 1 0.0 0.0 0.0 0.0 - svTrue Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:73:1-33 4571 1 0.0 0.0 0.0 0.0 - svUNeg Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:170:1-61 5030 1 0.0 0.0 0.0 0.0 - CAF Data.SBV.Core.Symbolic 3224 0 0.0 0.0 0.0 0.0 - falseSV Data.SBV.Core.Symbolic Data/SBV/Core/Symbolic.hs:142:1-32 3689 1 0.0 0.0 0.0 0.0 - trueSV Data.SBV.Core.Symbolic Data/SBV/Core/Symbolic.hs:146:1-32 3690 1 0.0 0.0 0.0 0.0 - CAF Data.SBV.Control.Types 3221 0 0.0 0.0 0.0 0.0 - setSMTOption Data.SBV.Control.Types Data/SBV/Control/Types.hs:(159,1)-(178,57) 3654 1 0.0 0.0 0.0 0.0 - CAF Data.SBV.SMT.SMT 3219 0 0.0 0.0 0.0 0.0 - standardEngine Data.SBV.SMT.SMT Data/SBV/SMT/SMT.hs:(628,1)-(635,44) 3702 0 0.0 0.0 0.0 0.0 - CAF Data.SBV.SMT.SMTLib2 3217 0 0.0 0.0 0.0 0.0 - cvt Data.SBV.SMT.SMTLib2 Data/SBV/SMT/SMTLib2.hs:(44,1)-(328,31) 3657 0 0.0 0.0 0.0 0.0 - dataBox Data.Generics.Uniplate.Internal.Data Data/Generics/Uniplate/Internal/Data.hs:228:1-33 3660 1 0.0 0.0 0.0 0.0 - typeKey Data.Generics.Uniplate.Internal.Data Data/Generics/Uniplate/Internal/Data.hs:65:1-16 3665 1 0.0 0.0 0.0 0.0 - readCacheFollower Data.Generics.Uniplate.Internal.Data Data/Generics/Uniplate/Internal/Data.hs:(144,1)-(162,22) 3661 1 0.0 0.0 0.0 0.0 - insertHitMap Data.Generics.Uniplate.Internal.Data Data/Generics/Uniplate/Internal/Data.hs:(262,1)-(282,56) 3667 1 0.0 0.0 0.0 0.0 - map_member Data.Generics.Uniplate.Internal.Data Data/Generics/Uniplate/Internal/Data.hs:93:1-42 3680 2 0.0 0.0 0.0 0.0 - hash Data.HashMap.Base Data/HashMap/Base.hs:166:1-28 3681 2 0.0 0.0 0.0 0.0 - sybChildren Data.Generics.Uniplate.Internal.Data Data/Generics/Uniplate/Internal/Data.hs:(233,1)-(244,27) 3682 1 0.0 0.0 0.0 0.0 - union Data.HashMap.Base Data/HashMap/Base.hs:1287:1-23 3669 0 0.0 0.0 0.0 0.0 - lookup2 Data.Generics.Uniplate.Internal.Data Data/Generics/Uniplate/Internal/Data.hs:186:1-49 3663 1 0.0 0.0 0.0 0.0 - hash Data.HashMap.Base Data/HashMap/Base.hs:166:1-28 3664 1 0.0 0.0 0.0 0.0 - typeKey Data.Generics.Uniplate.Internal.Data Data/Generics/Uniplate/Internal/Data.hs:65:1-16 3686 1 0.0 0.0 0.0 0.0 - CAF Data.SBV.Provers.Prover 3214 0 0.0 0.0 0.0 0.0 - cvc4 Data.SBV.Provers.Prover Data/SBV/Provers/Prover.hs:114:1-47 3634 1 0.0 0.0 0.0 0.0 - CAF Data.SBV.Provers.CVC4 3212 0 0.0 0.0 0.0 0.0 - cvc4 Data.SBV.Provers.CVC4 Data/SBV/Provers/CVC4.hs:(27,1)-(64,25) 3644 1 0.0 0.0 0.0 0.0 - CAF Data.SBV.Utils.Lib 3203 0 0.0 0.0 0.0 0.0 - splitArgs Data.SBV.Utils.Lib Data/SBV/Utils/Lib.hs:(88,1)-(108,40) 3696 1 0.0 0.0 0.0 0.0 - CAF Data.SBV.Utils.SExpr 3201 0 0.0 0.0 0.0 0.0 - parenDeficit Data.SBV.Utils.SExpr Data/SBV/Utils/SExpr.hs:(82,1)-(87,54) 3705 1 0.0 0.0 0.0 0.0 - CAF Data.Generics.Uniplate.Internal.Data 3197 0 0.0 0.0 0.0 0.0 - cache Data.Generics.Uniplate.Internal.Data Data/Generics/Uniplate/Internal/Data.hs:140:1-64 3662 1 0.0 0.0 0.0 0.0 - emptyHitMap Data.Generics.Uniplate.Internal.Data Data/Generics/Uniplate/Internal/Data.hs:(254,1)-(258,43) 3670 1 0.0 0.0 0.0 0.0 - typeKey Data.Generics.Uniplate.Internal.Data Data/Generics/Uniplate/Internal/Data.hs:65:1-16 3675 2 0.0 0.0 0.0 0.0 - fromList Data.HashMap.Strict.Base Data/HashMap/Strict/Base.hs:598:1-64 3671 1 0.0 0.0 0.0 0.0 - unsafeInsert Data.HashMap.Base Data/HashMap/Base.hs:(784,1)-(814,76) 3676 2 0.0 0.0 0.0 0.0 - hash Data.HashMap.Base Data/HashMap/Base.hs:166:1-28 3677 2 0.0 0.0 0.0 0.0 - singleton Data.HashSet.Base Data/HashSet/Base.hs:207:1-40 3672 1 0.0 0.0 0.0 0.0 - singleton Data.HashMap.Base Data/HashMap/Base.hs:468:1-37 3673 1 0.0 0.0 0.0 0.0 - hash Data.HashMap.Base Data/HashMap/Base.hs:166:1-28 3674 1 0.0 0.0 0.0 0.0 - union Data.HashMap.Base Data/HashMap/Base.hs:1287:1-23 3668 1 0.0 0.0 0.0 0.0 - uniplateVerbose Data.Generics.Uniplate.Internal.Data Data/Generics/Uniplate/Internal/Data.hs:(103,1)-(104,101) 3683 1 0.0 0.0 0.0 0.0 - CAF Text.Regex.TDFA.Common 3156 0 0.0 0.0 0.0 0.0 - noWin Text.Regex.TDFA.Common lib/Text/Regex/TDFA/Common.hs:69:1-12 4269 1 0.0 0.0 0.0 0.0 - CAF Text.Regex.TDFA.Pattern 3141 0 0.0 0.0 0.0 0.0 - starTrans Text.Regex.TDFA.Pattern lib/Text/Regex/TDFA/Pattern.hs:140:1-47 4250 1 0.0 0.0 0.0 0.0 - dfsPattern Text.Regex.TDFA.Pattern lib/Text/Regex/TDFA/Pattern.hs:(146,1)-(156,37) 4251 1 0.0 0.0 0.0 0.0 - CAF Text.Regex.TDFA.ReadRegex 3140 0 0.0 0.0 0.0 0.0 - CAF Options.Generic 3136 0 0.0 0.0 0.0 0.0 - metavar Options.Applicative.Builder src/Options/Applicative/Builder.hs:201:1-55 3595 2 0.0 0.0 0.0 0.0 - optionMod Options.Applicative.Builder.Internal src/Options/Applicative/Builder/Internal.hs:129:1-25 3596 0 0.0 0.0 0.0 0.0 - lispCaseModifiers Options.Generic src/Options/Generic.hs:(816,1)-(820,29) 3535 1 0.0 0.0 0.0 0.0 - multiSuffix Options.Applicative.Builder src/Options/Applicative/Builder.hs:467:1-58 3467 1 0.0 0.0 0.0 0.0 - str Options.Applicative.Builder src/Options/Applicative/Builder.hs:129:1-30 3586 1 0.0 0.0 0.0 0.0 - getRecord Options.Generic src/Options/Generic.hs:(1017,1)-(1019,51) 3464 0 0.0 0.0 0.0 0.0 - getRecordWith Options.Generic src/Options/Generic.hs:(1032,1)-(1035,46) 3465 0 0.0 0.0 0.0 0.0 - prefs Options.Applicative.Builder src/Options/Applicative/Builder.hs:(511,1)-(520,36) 3466 1 0.0 0.0 0.0 0.0 - multiSuffix Options.Applicative.Builder src/Options/Applicative/Builder.hs:467:1-58 3468 0 0.0 0.0 0.0 0.0 - CAF Options.Applicative.Builder 3132 0 0.0 0.0 0.0 0.0 - hidden Options.Applicative.Builder src/Options/Applicative/Builder.hs:(205,1)-(206,54) 3523 1 0.0 0.0 0.0 0.0 - optionMod Options.Applicative.Builder.Internal src/Options/Applicative/Builder/Internal.hs:129:1-25 3524 0 0.0 0.0 0.0 0.0 - switch Options.Applicative.Builder src/Options/Applicative/Builder.hs:333:1-24 3590 1 0.0 0.0 0.0 0.0 - abortOption Options.Applicative.Builder src/Options/Applicative/Builder.hs:(341,1)-(344,16) 3528 0 0.0 0.0 0.0 0.0 - metavar Options.Applicative.Builder src/Options/Applicative/Builder.hs:201:1-55 3530 1 0.0 0.0 0.0 0.0 - optionMod Options.Applicative.Builder.Internal src/Options/Applicative/Builder/Internal.hs:129:1-25 3531 0 0.0 0.0 0.0 0.0 - value Options.Applicative.Builder src/Options/Applicative/Builder.hs:173:1-50 3529 1 0.0 0.0 0.0 0.0 - option Options.Applicative.Builder src/Options/Applicative/Builder.hs:(367,1)-(372,65) 3496 0 0.0 0.0 0.0 0.0 - metavar Options.Applicative.Builder src/Options/Applicative/Builder.hs:201:1-55 3497 1 0.0 0.0 0.0 0.0 - optionMod Options.Applicative.Builder.Internal src/Options/Applicative/Builder/Internal.hs:129:1-25 3498 0 0.0 0.0 0.0 0.0 - subparser Options.Applicative.Builder src/Options/Applicative/Builder.hs:(270,1)-(274,39) 3541 0 0.0 0.0 0.0 0.0 - metavar Options.Applicative.Builder src/Options/Applicative/Builder.hs:201:1-55 3542 1 0.0 0.0 0.0 0.0 - optionMod Options.Applicative.Builder.Internal src/Options/Applicative/Builder/Internal.hs:129:1-25 3543 0 0.0 0.0 0.0 0.0 - CAF Options.Applicative.Builder.Internal 3130 0 0.0 0.0 0.0 0.0 - internal Options.Applicative.Builder.Internal src/Options/Applicative/Builder/Internal.hs:185:1-60 3482 1 0.0 0.0 0.0 0.0 - optionMod Options.Applicative.Builder.Internal src/Options/Applicative/Builder/Internal.hs:129:1-25 3484 0 0.0 0.0 0.0 0.0 - optionMod Options.Applicative.Builder.Internal src/Options/Applicative/Builder/Internal.hs:129:1-25 3483 1 0.0 0.0 0.0 0.0 - CAF Options.Applicative.Common 3129 0 0.0 0.0 0.0 0.0 - liftOpt Options.Applicative.Common src/Options/Applicative/Common.hs:80:1-14 3487 1 0.0 0.0 0.0 0.0 - CAF Options.Applicative.Extra 3128 0 0.0 0.0 0.0 0.0 - helper Options.Applicative.Extra src/Options/Applicative/Extra.hs:(49,1)-(53,12) 3516 1 0.0 0.0 0.0 0.0 - abortOption Options.Applicative.Builder src/Options/Applicative/Builder.hs:(341,1)-(344,16) 3525 1 0.0 0.0 0.0 0.0 - noArgError Options.Applicative.Builder src/Options/Applicative/Builder.hs:194:1-61 3526 1 0.0 0.0 0.0 0.0 - fieldMod Options.Applicative.Builder.Internal src/Options/Applicative/Builder/Internal.hs:132:1-28 3527 1 0.0 0.0 0.0 0.0 - option Options.Applicative.Builder src/Options/Applicative/Builder.hs:(367,1)-(372,65) 3532 1 0.0 0.0 0.0 0.0 - optNames Options.Applicative.Builder.Internal src/Options/Applicative/Builder/Internal.hs:35:5-12 3564 3 0.0 0.0 0.0 0.0 - mkParser Options.Applicative.Builder.Internal src/Options/Applicative/Builder/Internal.hs:(163,1)-(167,36) 3533 1 0.0 0.0 0.0 0.0 - mkOption Options.Applicative.Builder.Internal src/Options/Applicative/Builder/Internal.hs:173:1-43 3534 1 0.0 0.0 0.0 0.0 - noArgError Options.Applicative.Builder src/Options/Applicative/Builder.hs:194:1-61 3565 0 0.0 0.0 0.0 0.0 - fieldMod Options.Applicative.Builder.Internal src/Options/Applicative/Builder/Internal.hs:132:1-28 3566 0 0.0 0.0 0.0 0.0 - help Options.Applicative.Builder src/Options/Applicative/Builder.hs:185:1-55 3521 1 0.0 0.0 0.0 0.0 - optionMod Options.Applicative.Builder.Internal src/Options/Applicative/Builder/Internal.hs:129:1-25 3522 0 0.0 0.0 0.0 0.0 - long Options.Applicative.Builder src/Options/Applicative/Builder.hs:161:1-32 3517 1 0.0 0.0 0.0 0.0 - fieldMod Options.Applicative.Builder.Internal src/Options/Applicative/Builder/Internal.hs:132:1-28 3518 1 0.0 0.0 0.0 0.0 - short Options.Applicative.Builder src/Options/Applicative/Builder.hs:157:1-34 3519 1 0.0 0.0 0.0 0.0 - fieldMod Options.Applicative.Builder.Internal src/Options/Applicative/Builder/Internal.hs:132:1-28 3520 1 0.0 0.0 0.0 0.0 - CAF Options.Applicative.Types 3122 0 0.0 0.0 0.0 0.0 - readerAsk Options.Applicative.Types src/Options/Applicative/Types.hs:214:1-21 3588 1 0.0 0.0 0.0 0.0 - CAF Options.Applicative.BashCompletion 3120 0 0.0 0.0 0.0 0.0 - bashCompletionParser Options.Applicative.BashCompletion src/Options/Applicative/BashCompletion.hs:(35,1)-(65,7) 3479 0 0.0 0.0 0.0 0.0 - long Options.Applicative.Builder src/Options/Applicative/Builder.hs:161:1-32 3480 8 0.0 0.0 0.0 0.0 - fieldMod Options.Applicative.Builder.Internal src/Options/Applicative/Builder/Internal.hs:132:1-28 3481 8 0.0 0.0 0.0 0.0 - strOption Options.Applicative.Builder src/Options/Applicative/Builder.hs:352:1-22 3504 4 0.0 0.0 0.0 0.0 - option Options.Applicative.Builder src/Options/Applicative/Builder.hs:(367,1)-(372,65) 3505 4 0.0 0.0 0.0 0.0 - mkParser Options.Applicative.Builder.Internal src/Options/Applicative/Builder/Internal.hs:(163,1)-(167,36) 3506 4 0.0 0.0 0.0 0.0 - mkOption Options.Applicative.Builder.Internal src/Options/Applicative/Builder/Internal.hs:173:1-43 3507 4 0.0 0.0 0.0 0.0 - option Options.Applicative.Builder src/Options/Applicative/Builder.hs:(367,1)-(372,65) 3495 3 0.0 0.0 0.0 0.0 - mkParser Options.Applicative.Builder.Internal src/Options/Applicative/Builder/Internal.hs:(163,1)-(167,36) 3499 3 0.0 0.0 0.0 0.0 - mkOption Options.Applicative.Builder.Internal src/Options/Applicative/Builder/Internal.hs:173:1-43 3500 3 0.0 0.0 0.0 0.0 - value Options.Applicative.Builder src/Options/Applicative/Builder.hs:173:1-50 3494 2 0.0 0.0 0.0 0.0 - flag' Options.Applicative.Builder src/Options/Applicative/Builder.hs:(319,1)-(323,43) 3485 1 0.0 0.0 0.0 0.0 - flagActive Options.Applicative.Builder.Internal src/Options/Applicative/Builder/Internal.hs:41:5-14 3490 1 0.0 0.0 0.0 0.0 - mkParser Options.Applicative.Builder.Internal src/Options/Applicative/Builder/Internal.hs:(163,1)-(167,36) 3486 1 0.0 0.0 0.0 0.0 - mkOption Options.Applicative.Builder.Internal src/Options/Applicative/Builder/Internal.hs:173:1-43 3489 1 0.0 0.0 0.0 0.0 - long Options.Applicative.Builder src/Options/Applicative/Builder.hs:161:1-32 3492 0 0.0 0.0 0.0 0.0 - fieldMod Options.Applicative.Builder.Internal src/Options/Applicative/Builder/Internal.hs:132:1-28 3493 0 0.0 0.0 0.0 0.0 - fromM Options.Applicative.Types src/Options/Applicative/Types.hs:282:1-26 3501 1 0.0 0.0 0.0 0.0 - manyM Options.Applicative.Types src/Options/Applicative/Types.hs:(288,1)-(292,30) 3502 1 0.0 0.0 0.0 0.0 - oneM Options.Applicative.Types src/Options/Applicative/Types.hs:285:1-26 3503 1 0.0 0.0 0.0 0.0 - CAF Control.Monad.Operational 3119 0 0.0 0.0 0.0 0.0 - singleton Control.Monad.Operational src/Control/Monad/Operational.hs:221:1-17 4279 1 0.0 0.0 0.0 0.0 - view Control.Monad.Operational src/Control/Monad/Operational.hs:138:1-26 4273 1 0.0 0.0 0.0 0.0 - CAF System.Process.Posix 3069 0 0.0 0.0 0.0 0.0 - CAF Data.Serialize.Get 3058 0 0.0 0.0 0.0 0.0 - bytesRead Data.Serialize.Get src/Data/Serialize/Get.hs:838:1-45 4162 1 0.0 0.0 0.0 0.0 - CAF Data.DoubleWord 3015 0 0.0 0.0 0.0 0.0 - CAF Data.Memory.Internal.Compat 2930 0 0.0 0.0 0.0 0.0 - unsafeDoIO Data.Memory.Internal.Compat Data/Memory/Internal/Compat.hs:33:1-35 4143 1 0.0 0.0 0.0 0.0 - CAF System.Directory 2139 0 0.0 0.0 0.0 0.0 - CAF System.Directory.Internal.Posix 2137 0 0.0 0.0 0.0 0.0 - CAF Text.Megaparsec 2134 0 0.0 0.0 0.0 0.0 - parse Text.Megaparsec Text/Megaparsec.hs:178:1-17 5609 1 0.0 0.0 0.0 0.0 - CAF Data.Aeson.Parser.Internal 2098 0 0.0 0.0 0.0 0.0 - jstring Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:317:1-32 3728 1 0.0 0.0 0.0 0.0 - value Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:196:1-36 3720 1 0.0 0.0 0.0 0.0 - array_ Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:169:35-59 3732 1 0.0 0.0 0.0 0.0 - marray# Data.Primitive.Array Data/Primitive/Array.hs:92:5-11 3835 1 0.0 0.0 0.0 0.0 - sChunks Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:122:30-36 3833 1 0.0 0.0 0.0 0.0 - sSize Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:124:30-34 3832 1 0.0 0.0 0.0 0.0 - unId Data.Vector.Fusion.Util Data/Vector/Fusion/Util.hs:25:21-24 3834 1 0.0 0.0 0.0 0.0 - upperBound Data.Vector.Fusion.Bundle.Size Data/Vector/Fusion/Bundle/Size.hs:(126,1)-(128,30) 3831 1 0.0 0.0 0.0 0.0 - fromList Data.HashMap.Strict.Base Data/HashMap/Strict/Base.hs:598:1-64 3771 1 0.0 0.0 0.0 0.0 - object_ Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:132:46-89 3723 1 0.0 0.0 0.0 0.0 - CAF Data.Aeson.Parser.UnescapePure 2090 0 0.0 0.0 0.0 0.0 - unescapeText Data.Aeson.Parser.UnescapePure pure/Data/Aeson/Parser/UnescapePure.hs:254:1-70 3747 1 0.0 0.0 0.0 0.0 - CAF Data.HashMap.Base 2068 0 0.0 0.0 0.0 0.0 - bitsPerSubkey Data.HashMap.Base Data/HashMap/Base.hs:1858:1-17 3679 1 0.0 0.0 0.0 0.0 - empty Data.HashMap.Base Data/HashMap/Base.hs:464:1-13 3666 1 0.0 0.0 0.0 0.0 - CAF Data.HashSet.Base 2065 0 0.0 0.0 0.0 0.0 - empty Data.HashSet.Base Data/HashSet/Base.hs:203:1-23 3678 1 0.0 0.0 0.0 0.0 - CAF Data.Scientific 2033 0 0.0 0.0 0.0 0.0 - scientific Data.Scientific src/Data/Scientific.hs:174:1-23 3774 1 0.0 0.0 0.0 0.0 - CAF Data.Text 2021 0 0.0 0.0 0.0 0.0 - CAF Data.Text.Array 2020 0 0.0 0.0 0.0 0.0 - CAF Data.Text.Encoding 2019 0 0.0 0.0 0.0 0.0 - CAF Data.Text.IO 2017 0 0.0 0.0 0.0 0.0 - CAF Data.Text.Internal 2016 0 0.0 0.0 0.0 0.0 - CAF Data.ByteString.Builder.Prim.Internal.Base16 1972 0 0.0 0.0 0.0 0.0 - CAF Test.QuickCheck.Arbitrary 1971 0 0.0 0.0 0.0 0.0 - choose Test.QuickCheck.Gen Test/QuickCheck/Gen.hs:130:1-59 6326 1 0.0 0.0 0.0 0.0 - CAF Test.QuickCheck.Random 1962 0 0.0 0.0 0.0 0.0 - newQCGen Test.QuickCheck.Random Test/QuickCheck/Random.hs:42:1-30 5303 1 0.0 0.0 0.0 0.0 - CAF System.Random.SplitMix 1935 0 0.0 0.0 0.0 0.0 - initSMGen System.Random.SplitMix src/System/Random/SplitMix.hs:378:1-35 5307 1 0.0 0.0 0.0 0.0 - mkSMGen System.Random.SplitMix src/System/Random/SplitMix.hs:374:1-61 5308 1 0.0 0.0 0.0 0.0 - newSMGen System.Random.SplitMix src/System/Random/SplitMix.hs:382:1-48 5305 1 0.0 0.0 0.0 0.0 - CAF Data.Time.Clock.POSIX 1930 0 0.0 0.0 0.0 0.0 - CAF Data.Sequence.Internal 1899 0 0.0 0.0 0.0 0.0 - CAF Data.Data 1875 0 0.0 0.0 0.0 0.0 - CAF Data.Unique 1852 0 0.0 0.0 0.0 0.0 - CAF GHC.Conc.Signal 1836 0 0.0 0.0 0.0 0.0 - CAF GHC.IO.Encoding 1817 0 0.0 0.0 0.0 0.0 - CAF GHC.IO.Encoding.Iconv 1815 0 0.0 0.0 0.0 0.0 - CAF GHC.IO.Exception 1809 0 0.0 0.0 0.0 0.0 - CAF GHC.IO.FD 1808 0 0.0 0.0 0.0 0.0 - CAF GHC.IO.Handle.FD 1806 0 0.0 0.0 0.0 0.0 - CAF GHC.IO.Handle.Internals 1805 0 0.0 0.0 0.0 0.0 - CAF GHC.IO.Handle.Text 1804 0 0.0 0.0 0.0 0.0 - CAF GHC.Show 1786 0 0.0 0.0 0.0 0.0 - CAF System.CPUTime 1773 0 0.0 0.0 0.0 0.0 - CAF System.Exit 1771 0 0.0 0.0 0.0 0.0 - CAF Text.Read.Lex 1761 0 0.0 0.0 0.0 0.0 - CAF Data.Typeable.Internal 1755 0 0.0 0.0 0.0 0.0 - CAF GHC.Event.Thread 1753 0 0.0 0.0 0.0 0.0 - CAF GHC.Event.Manager 1745 0 0.0 0.0 0.0 0.0 - CAF GHC.Event.Poll 1743 0 0.0 0.0 0.0 0.0 - CAF GHC.Integer.Type 1737 0 0.0 0.0 0.0 0.0 - main Main hevm-cli/hevm-cli.hs:(307,1)-(354,100) 3451 0 0.0 0.0 99.9 100.0 - dappRoot Main hevm-cli/hevm-cli.hs:120:9-16 3602 1 0.0 0.0 0.0 0.0 - findJsonFile Main hevm-cli/hevm-cli.hs:(370,1)-(387,9) 3605 1 0.0 0.0 0.0 0.0 - jsonFile Main hevm-cli/hevm-cli.hs:119:9-16 3604 1 0.0 0.0 0.0 0.0 - runSMTWithTimeOut Main hevm-cli/hevm-cli.hs:(447,1)-(458,17) 3607 1 0.0 0.0 99.9 100.0 - runSMTWith Data.SBV.Client.BaseIO Data/SBV/Client/BaseIO.hs:223:1-29 3610 0 0.0 0.0 99.9 100.0 - runSMTWith Data.SBV.Provers.Prover Data/SBV/Provers/Prover.hs:755:1-80 3611 1 0.0 0.0 99.9 100.0 - runSymbolic Data.SBV.Core.Symbolic Data/SBV/Core/Symbolic.hs:(1472,1)-(1541,18) 3612 1 0.0 0.0 99.9 100.0 - incrementInternalCounter Data.SBV.Core.Symbolic Data/SBV/Core/Symbolic.hs:(1058,1)-(1060,43) 3615 2 0.0 0.0 0.0 0.0 - modifyState Data.SBV.Core.Symbolic Data/SBV/Core/Symbolic.hs:(1039,1)-(1044,41) 3617 2 0.0 0.0 0.0 0.0 - rctr Data.SBV.Core.Symbolic Data/SBV/Core/Symbolic.hs:935:23-26 3618 2 0.0 0.0 0.0 0.0 - rctr Data.SBV.Core.Symbolic Data/SBV/Core/Symbolic.hs:935:23-26 3616 2 0.0 0.0 0.0 0.0 - modifyState Data.SBV.Core.Symbolic Data/SBV/Core/Symbolic.hs:(1039,1)-(1044,41) 3624 2 0.0 0.0 0.0 0.0 - rconstMap Data.SBV.Core.Symbolic Data/SBV/Core/Symbolic.hs:945:23-31 3625 2 0.0 0.0 0.0 0.0 - rconstMap Data.SBV.Core.Symbolic Data/SBV/Core/Symbolic.hs:945:23-31 3613 2 0.0 0.0 0.0 0.0 - registerKind Data.SBV.Core.Symbolic Data/SBV/Core/Symbolic.hs:(1152,1)-(1193,60) 3619 2 0.0 0.0 0.0 0.0 - modifyState Data.SBV.Core.Symbolic Data/SBV/Core/Symbolic.hs:(1039,1)-(1044,41) 3622 2 0.0 0.0 0.0 0.0 - rUsedKinds Data.SBV.Core.Symbolic Data/SBV/Core/Symbolic.hs:936:23-32 3623 2 0.0 0.0 0.0 0.0 - rUsedKinds Data.SBV.Core.Symbolic Data/SBV/Core/Symbolic.hs:936:23-32 3621 2 0.0 0.0 0.0 0.0 - query Data.SBV.Control Data/SBV/Control.hs:105:1-40 3630 0 0.0 0.0 99.9 100.0 - extractSymbolicSimulationState Data.SBV.Core.Symbolic Data/SBV/Core/Symbolic.hs:(1545,1)-(1570,125) 3638 1 0.0 0.0 0.0 0.0 - executeQuery Data.SBV.Control.Utils Data/SBV/Control/Utils.hs:(1467,1)-(1619,43) 3631 0 0.0 0.0 99.9 100.0 - runMode Data.SBV.Core.Symbolic Data/SBV/Core/Symbolic.hs:931:23-29 3632 2 0.0 0.0 0.0 0.0 - allowQuantifiedQueries Data.SBV.Core.Symbolic Data/SBV/Core/Symbolic.hs:1842:10-31 3633 1 0.0 0.0 0.0 0.0 - cache Main hevm-cli/hevm-cli.hs:116:9-13 6502 1 0.0 0.0 0.0 0.0 - coverage Main hevm-cli/hevm-cli.hs:181:9-16 3940 1 0.0 0.0 0.0 0.0 - dappTest Main hevm-cli/hevm-cli.hs:(390,1)-(421,69) 3944 1 0.0 0.0 94.1 91.5 - _dappRoot EVM.Dapp src/EVM/Dapp.hs:33:5-13 4120 1 0.0 0.0 0.0 0.0 - corpus EVM.UnitTest src/EVM/UnitTest.hs:90:5-10 4122 1 0.0 0.0 0.0 0.0 - dapp EVM.UnitTest src/EVM/UnitTest.hs:87:5-8 4118 1 0.0 0.0 0.0 0.0 - findUnitTests EVM.Dapp src/EVM/Dapp.hs:(134,1)-(140,68) 4124 1 0.0 0.0 0.0 0.0 - unitTestMethodsFiltered EVM.Dapp src/EVM/Dapp.hs:(143,1)-(147,51) 4233 2 0.0 0.0 0.0 0.0 - regexMatches EVM.Dapp src/EVM/Dapp.hs:(123,1)-(131,49) 4239 0 0.0 0.0 0.0 0.0 - matchTest Text.Regex.TDFA.NewDFA.Tester lib/Text/Regex/TDFA/NewDFA/Tester.hs:(23,1)-(85,22) 4265 5 0.0 0.0 0.0 0.0 - d_dt Text.Regex.TDFA.Common lib/Text/Regex/TDFA/Common.hs:214:36-39 4267 5 0.0 0.0 0.0 0.0 - unitTestMethods EVM.Dapp src/EVM/Dapp.hs:(150,1)-(155,27) 4235 0 0.0 0.0 0.0 0.0 - mkTest EVM.Dapp src/EVM/Dapp.hs:(117,1)-(120,23) 4236 10 0.0 0.0 0.0 0.0 - regexMatches EVM.Dapp src/EVM/Dapp.hs:(123,1)-(131,49) 4238 1 0.0 0.0 0.0 0.0 - compile Text.Regex.TDFA.String lib/Text/Regex/TDFA/String.hs:(44,1)-(47,67) 4240 1 0.0 0.0 0.0 0.0 - parseRegex Text.Regex.TDFA.ReadRegex lib/Text/Regex/TDFA/ReadRegex.hs:(28,1)-(31,83) 4241 1 0.0 0.0 0.0 0.0 - patternToRegex Text.Regex.TDFA.TDFA lib/Text/Regex/TDFA/TDFA.hs:160:1-96 4245 1 0.0 0.0 0.0 0.0 - nfaToDFA Text.Regex.TDFA.TDFA lib/Text/Regex/TDFA/TDFA.hs:(53,1)-(157,65) 4247 1 0.0 0.0 0.0 0.0 - fromSinglesMerge Text.Regex.TDFA.IntArrTrieSet lib/Text/Regex/TDFA/IntArrTrieSet.hs:(45,1)-(52,33) 4260 1 0.0 0.0 0.0 0.0 - fromBounds Text.Regex.TDFA.IntArrTrieSet lib/Text/Regex/TDFA/IntArrTrieSet.hs:(32,1)-(35,86) 4261 1 0.0 0.0 0.0 0.0 - nfaToDFA.indexToDFA Text.Regex.TDFA.TDFA lib/Text/Regex/TDFA/TDFA.hs:85:52-96 4264 1 0.0 0.0 0.0 0.0 - multiline Text.Regex.TDFA.Common lib/Text/Regex/TDFA/Common.hs:86:5-13 4266 1 0.0 0.0 0.0 0.0 - nfaToDFA.indexesToDFA Text.Regex.TDFA.TDFA lib/Text/Regex/TDFA/TDFA.hs:59:54-72 4248 1 0.0 0.0 0.0 0.0 - lookupAsc Text.Regex.TDFA.IntArrTrieSet lib/Text/Regex/TDFA/IntArrTrieSet.hs:(23,1)-(25,64) 4262 2 0.0 0.0 0.0 0.0 - patternToNFA Text.Regex.TDFA.TNFA lib/Text/Regex/TDFA/TNFA.hs:(84,1)-(87,45) 4246 1 0.0 0.0 0.0 0.0 - lastStarGreedy Text.Regex.TDFA.Common lib/Text/Regex/TDFA/Common.hs:95:5-18 4268 3 0.0 0.0 0.0 0.0 - nullQ Text.Regex.TDFA.CorePattern lib/Text/Regex/TDFA/CorePattern.hs:75:13-17 4259 2 0.0 0.0 0.0 0.0 - cannotAccept Text.Regex.TDFA.CorePattern lib/Text/Regex/TDFA/CorePattern.hs:242:1-52 4257 1 0.0 0.0 0.0 0.0 - takes Text.Regex.TDFA.CorePattern lib/Text/Regex/TDFA/CorePattern.hs:76:13-17 4258 1 0.0 0.0 0.0 0.0 - multiline Text.Regex.TDFA.Common lib/Text/Regex/TDFA/Common.hs:86:5-13 4270 1 0.0 0.0 0.0 0.0 - patternToQ Text.Regex.TDFA.CorePattern lib/Text/Regex/TDFA/CorePattern.hs:(304,1)-(586,28) 4249 1 0.0 0.0 0.0 0.0 - starTrans Text.Regex.TDFA.Pattern lib/Text/Regex/TDFA/Pattern.hs:140:1-47 4252 0 0.0 0.0 0.0 0.0 - dfsPattern Text.Regex.TDFA.Pattern lib/Text/Regex/TDFA/Pattern.hs:(146,1)-(156,37) 4253 0 0.0 0.0 0.0 0.0 - simplify' Text.Regex.TDFA.Pattern lib/Text/Regex/TDFA/Pattern.hs:(326,1)-(343,23) 4255 4 0.0 0.0 0.0 0.0 - starTrans' Text.Regex.TDFA.Pattern lib/Text/Regex/TDFA/Pattern.hs:(169,1)-(320,14) 4254 4 0.0 0.0 0.0 0.0 - q_id Text.Regex.TDFA.Common lib/Text/Regex/TDFA/Common.hs:165:19-22 4263 1 0.0 0.0 0.0 0.0 - unQ Text.Regex.TDFA.CorePattern lib/Text/Regex/TDFA/CorePattern.hs:83:13-15 4256 1 0.0 0.0 0.0 0.0 - match EVM.UnitTest src/EVM/UnitTest.hs:83:5-9 4242 1 0.0 0.0 0.0 0.0 - readSolc EVM.Solidity src/EVM/Solidity.hs:(297,1)-(303,47) 3945 1 0.1 0.1 5.4 8.5 - readTextDevice Data.Text.Internal.IO libraries/text/Data/Text/Internal/IO.hs:133:39-64 3946 393 0.1 0.0 0.1 0.0 - readJSON EVM.Solidity src/EVM/Solidity.hs:(329,1)-(331,28) 3947 1 0.1 0.1 5.2 8.3 - lazy Control.Lens.Iso src/Control/Lens/Iso.hs:569:1-18 3948 1 0.0 0.0 1.5 2.4 - hash Data.HashMap.Base Data/HashMap/Base.hs:166:1-28 4027 1 0.0 0.0 0.0 0.0 - hashByteArrayWithSalt Data.Hashable.Class Data/Hashable/Class.hs:(770,1)-(772,20) 4028 1 0.0 0.0 0.0 0.0 - maybeResult Data.Attoparsec.ByteString.Lazy Data/Attoparsec/ByteString/Lazy.hs:(103,1)-(104,32) 3949 1 0.0 0.0 0.0 0.0 - parse Data.Attoparsec.ByteString.Lazy Data/Attoparsec/ByteString/Lazy.hs:(88,1)-(95,56) 3950 1 0.0 0.0 1.5 2.4 - runParser Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:111:7-15 3951 16 0.0 0.0 0.0 0.0 - fromPos Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:46:21-27 3953 3 0.0 0.0 0.0 0.0 - buffer Data.Attoparsec.ByteString.Buffer Data/Attoparsec/ByteString/Buffer.hs:85:1-45 3952 1 0.0 0.0 0.0 0.0 - value Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:196:1-36 3954 0 0.0 0.0 1.5 2.4 - array_ Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:169:35-59 3961 0 0.1 0.1 0.1 0.3 - runParser Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:111:7-15 3962 75877 0.0 0.0 0.0 0.0 - fromPos Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:46:21-27 3963 15377 0.0 0.0 0.0 0.0 - marray# Data.Primitive.Array Data/Primitive/Array.hs:92:5-11 4007 23 0.0 0.0 0.0 0.0 - unId Data.Vector.Fusion.Util Data/Vector/Fusion/Util.hs:25:21-24 4006 15 0.0 0.0 0.0 0.0 - sChunks Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:122:30-36 4005 6 0.0 0.0 0.0 0.0 - sSize Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:124:30-34 4004 6 0.0 0.0 0.0 0.0 - upperBound Data.Vector.Fusion.Bundle.Size Data/Vector/Fusion/Bundle/Size.hs:(126,1)-(128,30) 4003 6 0.0 0.0 0.0 0.0 - jstring Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:317:1-32 3978 0 0.0 0.1 0.0 0.1 - runParser Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:111:7-15 3979 123205 0.0 0.0 0.0 0.0 - fromPos Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:46:21-27 3980 20305 0.0 0.0 0.0 0.0 - jstringSlow Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:(333,44)-(337,31) 3992 0 0.0 0.0 0.0 0.0 - object_ Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:132:46-89 3981 0 0.0 0.0 0.0 0.0 - runParser Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:111:7-15 3982 335 0.0 0.0 0.0 0.0 - marray# Data.Primitive.Array Data/Primitive/Array.hs:92:5-11 4016 80 0.0 0.0 0.0 0.0 - fromPos Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:46:21-27 3983 65 0.0 0.0 0.0 0.0 - unId Data.Vector.Fusion.Util Data/Vector/Fusion/Util.hs:25:21-24 4015 28 0.0 0.0 0.0 0.0 - sChunks Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:122:30-36 4014 2 0.0 0.0 0.0 0.0 - sSize Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:124:30-34 4013 2 0.0 0.0 0.0 0.0 - upperBound Data.Vector.Fusion.Bundle.Size Data/Vector/Fusion/Bundle/Size.hs:(126,1)-(128,30) 4012 2 0.0 0.0 0.0 0.0 - scientific Data.Scientific src/Data/Scientific.hs:174:1-23 4011 0 0.0 0.0 0.0 0.0 - jstringSlow Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:(333,44)-(337,31) 3993 0 0.0 0.0 0.0 0.0 - runParser Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:111:7-15 3996 16 0.0 0.0 0.0 0.0 - fromPos Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:46:21-27 3997 3 0.0 0.0 0.0 0.0 - object_ Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:132:46-89 3994 0 0.0 0.0 0.0 0.0 - jstring Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:317:1-32 3995 0 0.0 0.0 0.0 0.0 - object_ Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:132:46-89 3967 0 0.0 0.0 0.1 0.2 - runParser Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:111:7-15 3976 2467 0.0 0.0 0.0 0.0 - fromPos Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:46:21-27 3977 481 0.0 0.0 0.0 0.0 - marray# Data.Primitive.Array Data/Primitive/Array.hs:92:5-11 4021 7 0.0 0.0 0.0 0.0 - unId Data.Vector.Fusion.Util Data/Vector/Fusion/Util.hs:25:21-24 4020 3 0.0 0.0 0.0 0.0 - sChunks Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:122:30-36 4019 1 0.0 0.0 0.0 0.0 - sSize Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:124:30-34 4018 1 0.0 0.0 0.0 0.0 - upperBound Data.Vector.Fusion.Bundle.Size Data/Vector/Fusion/Bundle/Size.hs:(126,1)-(128,30) 4017 1 0.0 0.0 0.0 0.0 - jstring Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:317:1-32 3968 0 0.1 0.2 0.1 0.2 - runParser Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:111:7-15 3969 184758 0.0 0.0 0.0 0.0 - fromPos Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:46:21-27 3970 31081 0.0 0.0 0.0 0.0 - jstringSlow Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:(333,44)-(337,31) 3991 0 0.0 0.0 0.0 0.0 - scientific Data.Scientific src/Data/Scientific.hs:174:1-23 3999 0 0.0 0.0 0.0 0.0 - fromList Data.HashMap.Strict.Base Data/HashMap/Strict/Base.hs:598:1-64 3998 0 0.0 0.0 0.0 0.0 - unsafeInsert Data.HashMap.Base Data/HashMap/Base.hs:(784,1)-(814,76) 4000 132 0.0 0.0 0.0 0.0 - hash Data.HashMap.Base Data/HashMap/Base.hs:166:1-28 4001 132 0.0 0.0 0.0 0.0 - hashByteArrayWithSalt Data.Hashable.Class Data/Hashable/Class.hs:(770,1)-(772,20) 4002 132 0.0 0.0 0.0 0.0 - copy Data.HashMap.Array Data/HashMap/Array.hs:(328,1)-(333,30) 4009 98 0.0 0.0 0.0 0.0 - sparseIndex Data.HashMap.Base Data/HashMap/Base.hs:1867:1-42 4010 58 0.0 0.0 0.0 0.0 - new_ Data.HashMap.Array Data/HashMap/Array.hs:256:1-28 4008 49 0.0 0.0 0.0 0.0 - object_ Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:132:46-89 3955 0 0.0 0.1 1.3 2.1 - runParser Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:111:7-15 3956 80825 0.0 0.0 0.0 0.0 - fromPos Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:46:21-27 3957 17308 0.0 0.0 0.0 0.0 - array_ Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:169:35-59 3971 0 0.0 0.0 0.0 0.0 - jstring Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:317:1-32 3958 0 1.1 1.5 1.3 2.0 - runParser Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:111:7-15 3959 1858836 0.0 0.0 0.0 0.0 - fromPos Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:46:21-27 3960 309351 0.0 0.0 0.0 0.0 - jstringSlow Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:(333,44)-(337,31) 3984 207 0.0 0.0 0.0 0.2 - runParser Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:111:7-15 3985 17077 0.0 0.0 0.0 0.0 - fromPos Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:46:21-27 3986 2739 0.0 0.0 0.0 0.0 - array_ Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:169:35-59 3988 0 0.0 0.1 0.0 0.1 - runParser Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:111:7-15 3989 105487 0.0 0.0 0.0 0.0 - fromPos Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:46:21-27 3990 17284 0.0 0.0 0.0 0.0 - unescapeText Data.Aeson.Parser.UnescapePure pure/Data/Aeson/Parser/UnescapePure.hs:254:1-70 3987 0 0.0 0.0 0.0 0.0 - array_ Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:169:35-59 3964 0 0.2 0.3 0.2 0.4 - runParser Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:111:7-15 3965 304197 0.0 0.0 0.0 0.0 - fromPos Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:46:21-27 3966 49863 0.0 0.0 0.0 0.0 - marray# Data.Primitive.Array Data/Primitive/Array.hs:92:5-11 4026 145 0.0 0.0 0.0 0.0 - unId Data.Vector.Fusion.Util Data/Vector/Fusion/Util.hs:25:21-24 4025 57 0.0 0.0 0.0 0.0 - sChunks Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:122:30-36 4024 8 0.0 0.0 0.0 0.0 - sSize Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:124:30-34 4023 8 0.0 0.0 0.0 0.0 - upperBound Data.Vector.Fusion.Bundle.Size Data/Vector/Fusion/Bundle/Size.hs:(126,1)-(128,30) 4022 8 0.0 0.0 0.0 0.0 - jstringSlow Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:(333,44)-(337,31) 3972 5 0.0 0.0 0.0 0.1 - runParser Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:111:7-15 3973 1383 0.0 0.0 0.0 0.0 - fromPos Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:46:21-27 3974 221 0.0 0.0 0.0 0.0 - unescapeText Data.Aeson.Parser.UnescapePure pure/Data/Aeson/Parser/UnescapePure.hs:254:1-70 3975 0 0.0 0.1 0.0 0.1 - readStdJSON EVM.Solidity src/EVM/Solidity.hs:(364,1)-(407,39) 4029 1 0.1 0.2 3.7 5.8 - hash Data.HashMap.Base Data/HashMap/Base.hs:166:1-28 4112 408 0.0 0.0 0.0 0.0 - hashByteArrayWithSalt Data.Hashable.Class Data/Hashable/Class.hs:(770,1)-(772,20) 4113 408 0.0 0.0 0.0 0.0 - sparseIndex Data.HashMap.Base Data/HashMap/Base.hs:1867:1-42 4115 406 0.0 0.0 0.0 0.0 - unId Data.Vector.Fusion.Util Data/Vector/Fusion/Util.hs:25:21-24 4164 159 0.0 0.0 0.0 0.0 - array# Data.Primitive.Array Data/Primitive/Array.hs:87:5-10 4165 131 0.0 0.0 0.0 0.0 - signature EVM.Solidity src/EVM/Solidity.hs:(468,1)-(478,7) 4173 83 0.0 0.0 0.0 0.0 - hash Data.HashMap.Base Data/HashMap/Base.hs:166:1-28 4175 364 0.0 0.0 0.0 0.0 - hashByteArrayWithSalt Data.Hashable.Class Data/Hashable/Class.hs:(770,1)-(772,20) 4176 364 0.0 0.0 0.0 0.0 - sparseIndex Data.HashMap.Base Data/HashMap/Base.hs:1867:1-42 4177 364 0.0 0.0 0.0 0.0 - unId Data.Vector.Fusion.Util Data/Vector/Fusion/Util.hs:25:21-24 4178 198 0.0 0.0 0.0 0.0 - array# Data.Primitive.Array Data/Primitive/Array.hs:87:5-10 4201 115 0.0 0.0 0.0 0.0 - parseMethodInput EVM.Solidity src/EVM/Solidity.hs:(490,1)-(493,3) 5605 11 0.0 0.0 0.0 0.0 - hash Data.HashMap.Base Data/HashMap/Base.hs:166:1-28 5615 11 0.0 0.0 0.0 0.0 - hashByteArrayWithSalt Data.Hashable.Class Data/Hashable/Class.hs:(770,1)-(772,20) 5616 11 0.0 0.0 0.0 0.0 - sparseIndex Data.HashMap.Base Data/HashMap/Base.hs:1867:1-42 5617 11 0.0 0.0 0.0 0.0 - parseTypeName EVM.ABI src/EVM/ABI.hs:375:1-50 5607 0 0.0 0.0 0.0 0.0 - unParser Text.Megaparsec.Internal Text/Megaparsec/Internal.hs:120:5-12 5618 233 0.0 0.0 0.0 0.0 - parseMaybe Text.Megaparsec Text/Megaparsec.hs:(191,1)-(194,21) 5608 11 0.0 0.0 0.0 0.0 - runParser Text.Megaparsec Text/Megaparsec.hs:223:1-61 5610 11 0.0 0.0 0.0 0.0 - runParser' Text.Megaparsec Text/Megaparsec.hs:236:1-42 5611 11 0.0 0.0 0.0 0.0 - runParserT' Text.Megaparsec Text/Megaparsec.hs:(261,1)-(274,54) 5612 11 0.0 0.0 0.0 0.0 - runParsecT Text.Megaparsec.Internal Text/Megaparsec/Internal.hs:(591,1)-(596,56) 5613 11 0.0 0.0 0.0 0.0 - unParser Text.Megaparsec.Internal Text/Megaparsec/Internal.hs:120:5-12 5614 180 0.0 0.0 0.0 0.0 - stateParseErrors Text.Megaparsec.State Text/Megaparsec/State.hs:48:5-20 5619 11 0.0 0.0 0.0 0.0 - decode Data.ByteString.Base16 Data/ByteString/Base16.hs:(100,1)-(136,75) 4136 6 0.1 0.0 0.1 0.0 - stripBytecodeMetadata EVM.Solidity src/EVM/Solidity.hs:(569,1)-(573,22) 4135 6 0.0 0.0 0.0 0.0 - lazy Control.Lens.Iso src/Control/Lens/Iso.hs:569:1-18 4030 5 0.0 0.0 3.2 4.9 - hash Data.HashMap.Base Data/HashMap/Base.hs:166:1-28 4109 5 0.0 0.0 0.0 0.0 - hashByteArrayWithSalt Data.Hashable.Class Data/Hashable/Class.hs:(770,1)-(772,20) 4110 5 0.0 0.0 0.0 0.0 - maybeResult Data.Attoparsec.ByteString.Lazy Data/Attoparsec/ByteString/Lazy.hs:(103,1)-(104,32) 4031 5 0.0 0.0 0.0 0.0 - parse Data.Attoparsec.ByteString.Lazy Data/Attoparsec/ByteString/Lazy.hs:(88,1)-(95,56) 4032 5 0.0 0.0 3.2 4.9 - runParser Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:111:7-15 4033 80 0.0 0.0 0.0 0.0 - fromPos Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:46:21-27 4035 15 0.0 0.0 0.0 0.0 - buffer Data.Attoparsec.ByteString.Buffer Data/Attoparsec/ByteString/Buffer.hs:85:1-45 4034 5 0.0 0.0 0.0 0.0 - value Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:196:1-36 4036 0 0.1 0.0 3.2 4.9 - array_ Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:169:35-59 4043 0 0.1 0.2 0.5 0.7 - runParser Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:111:7-15 4044 155263 0.0 0.0 0.0 0.0 - fromPos Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:46:21-27 4045 31458 0.0 0.0 0.0 0.0 - marray# Data.Primitive.Array Data/Primitive/Array.hs:92:5-11 4089 102 0.0 0.0 0.0 0.0 - unId Data.Vector.Fusion.Util Data/Vector/Fusion/Util.hs:25:21-24 4088 54 0.0 0.0 0.0 0.0 - sChunks Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:122:30-36 4087 20 0.0 0.0 0.0 0.0 - sSize Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:124:30-34 4086 20 0.0 0.0 0.0 0.0 - upperBound Data.Vector.Fusion.Bundle.Size Data/Vector/Fusion/Bundle/Size.hs:(126,1)-(128,30) 4085 20 0.0 0.0 0.0 0.0 - jstring Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:317:1-32 4060 0 0.3 0.2 0.3 0.2 - runParser Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:111:7-15 4061 248104 0.0 0.0 0.0 0.0 - fromPos Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:46:21-27 4062 40882 0.0 0.0 0.0 0.0 - jstringSlow Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:(333,44)-(337,31) 4074 0 0.0 0.0 0.0 0.0 - object_ Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:132:46-89 4063 0 0.0 0.0 0.0 0.0 - runParser Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:111:7-15 4064 891 0.0 0.0 0.0 0.0 - marray# Data.Primitive.Array Data/Primitive/Array.hs:92:5-11 4098 233 0.0 0.0 0.0 0.0 - fromPos Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:46:21-27 4065 173 0.0 0.0 0.0 0.0 - unId Data.Vector.Fusion.Util Data/Vector/Fusion/Util.hs:25:21-24 4097 81 0.0 0.0 0.0 0.0 - sChunks Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:122:30-36 4096 5 0.0 0.0 0.0 0.0 - sSize Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:124:30-34 4095 5 0.0 0.0 0.0 0.0 - upperBound Data.Vector.Fusion.Bundle.Size Data/Vector/Fusion/Bundle/Size.hs:(126,1)-(128,30) 4094 5 0.0 0.0 0.0 0.0 - scientific Data.Scientific src/Data/Scientific.hs:174:1-23 4093 0 0.0 0.0 0.0 0.0 - jstringSlow Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:(333,44)-(337,31) 4075 0 0.0 0.0 0.0 0.0 - runParser Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:111:7-15 4078 32 0.0 0.0 0.0 0.0 - fromPos Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:46:21-27 4079 6 0.0 0.0 0.0 0.0 - object_ Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:132:46-89 4076 0 0.0 0.0 0.0 0.0 - jstring Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:317:1-32 4077 0 0.0 0.0 0.0 0.0 - object_ Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:132:46-89 4049 0 0.0 0.0 0.1 0.3 - runParser Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:111:7-15 4058 4975 0.0 0.0 0.0 0.0 - fromPos Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:46:21-27 4059 970 0.0 0.0 0.0 0.0 - marray# Data.Primitive.Array Data/Primitive/Array.hs:92:5-11 4103 14 0.0 0.0 0.0 0.0 - unId Data.Vector.Fusion.Util Data/Vector/Fusion/Util.hs:25:21-24 4102 6 0.0 0.0 0.0 0.0 - sChunks Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:122:30-36 4101 2 0.0 0.0 0.0 0.0 - sSize Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:124:30-34 4100 2 0.0 0.0 0.0 0.0 - upperBound Data.Vector.Fusion.Bundle.Size Data/Vector/Fusion/Bundle/Size.hs:(126,1)-(128,30) 4099 2 0.0 0.0 0.0 0.0 - jstring Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:317:1-32 4050 0 0.1 0.3 0.1 0.3 - runParser Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:111:7-15 4051 372571 0.0 0.0 0.0 0.0 - fromPos Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:46:21-27 4052 62673 0.0 0.0 0.0 0.0 - jstringSlow Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:(333,44)-(337,31) 4073 0 0.0 0.0 0.0 0.0 - scientific Data.Scientific src/Data/Scientific.hs:174:1-23 4081 0 0.0 0.0 0.0 0.0 - fromList Data.HashMap.Strict.Base Data/HashMap/Strict/Base.hs:598:1-64 4080 0 0.0 0.0 0.0 0.0 - unsafeInsert Data.HashMap.Base Data/HashMap/Base.hs:(784,1)-(814,76) 4082 958 0.0 0.0 0.0 0.0 - hash Data.HashMap.Base Data/HashMap/Base.hs:166:1-28 4083 958 0.0 0.0 0.0 0.0 - hashByteArrayWithSalt Data.Hashable.Class Data/Hashable/Class.hs:(770,1)-(772,20) 4084 958 0.0 0.0 0.0 0.0 - copy Data.HashMap.Array Data/HashMap/Array.hs:(328,1)-(333,30) 4091 676 0.0 0.0 0.0 0.0 - sparseIndex Data.HashMap.Base Data/HashMap/Base.hs:1867:1-42 4092 514 0.0 0.0 0.0 0.0 - new_ Data.HashMap.Array Data/HashMap/Array.hs:256:1-28 4090 338 0.0 0.0 0.0 0.0 - object_ Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:132:46-89 4037 0 0.1 0.2 2.6 4.2 - runParser Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:111:7-15 4038 164662 0.0 0.0 0.0 0.0 - fromPos Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:46:21-27 4039 35256 0.0 0.0 0.0 0.0 - array_ Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:169:35-59 4053 0 0.0 0.0 0.0 0.0 - jstring Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:317:1-32 4040 0 2.1 3.0 2.6 4.0 - runParser Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:111:7-15 4041 3769052 0.0 0.0 0.0 0.0 - fromPos Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:46:21-27 4042 627227 0.0 0.0 0.0 0.0 - jstringSlow Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:(333,44)-(337,31) 4066 414 0.1 0.0 0.3 0.3 - runParser Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:111:7-15 4067 34154 0.0 0.0 0.0 0.0 - fromPos Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:46:21-27 4068 5478 0.0 0.0 0.0 0.0 - array_ Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:169:35-59 4070 0 0.1 0.2 0.1 0.2 - runParser Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:111:7-15 4071 210974 0.0 0.0 0.0 0.0 - fromPos Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:46:21-27 4072 34568 0.0 0.0 0.0 0.0 - unescapeText Data.Aeson.Parser.UnescapePure pure/Data/Aeson/Parser/UnescapePure.hs:254:1-70 4069 0 0.1 0.1 0.1 0.1 - array_ Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:169:35-59 4046 0 0.2 0.6 0.3 0.7 - runParser Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:111:7-15 4047 623248 0.0 0.0 0.0 0.0 - fromPos Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:46:21-27 4048 102190 0.0 0.0 0.0 0.0 - marray# Data.Primitive.Array Data/Primitive/Array.hs:92:5-11 4108 688 0.0 0.0 0.0 0.0 - unId Data.Vector.Fusion.Util Data/Vector/Fusion/Util.hs:25:21-24 4107 320 0.0 0.0 0.0 0.0 - sChunks Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:122:30-36 4106 82 0.0 0.0 0.0 0.0 - sSize Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:124:30-34 4105 82 0.0 0.0 0.0 0.0 - upperBound Data.Vector.Fusion.Bundle.Size Data/Vector/Fusion/Bundle/Size.hs:(126,1)-(128,30) 4104 82 0.0 0.0 0.0 0.0 - jstringSlow Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:(333,44)-(337,31) 4054 10 0.0 0.0 0.1 0.1 - runParser Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:111:7-15 4055 2766 0.0 0.0 0.0 0.0 - fromPos Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:46:21-27 4056 442 0.0 0.0 0.0 0.0 - unescapeText Data.Aeson.Parser.UnescapePure pure/Data/Aeson/Parser/UnescapePure.hs:254:1-70 4057 0 0.1 0.1 0.1 0.1 - scientific Data.Scientific src/Data/Scientific.hs:174:1-23 4116 0 0.0 0.0 0.0 0.0 - sparseIndex Data.HashMap.Base Data/HashMap/Base.hs:1867:1-42 4111 5 0.0 0.0 0.0 0.0 - new_ Data.HashMap.Array Data/HashMap/Array.hs:256:1-28 4117 2 0.0 0.0 0.0 0.0 - abiKeccak EVM.Types src/EVM/Types.hs:(586,1)-(590,14) 4167 0 0.0 0.0 0.1 0.0 - word32 EVM.Types src/EVM/Types.hs:(576,1)-(577,52) 4200 23 0.0 0.0 0.0 0.0 - keccakBytes EVM.Types src/EVM/Types.hs:(570,1)-(573,15) 4168 0 0.0 0.0 0.1 0.0 - hash Crypto.Hash Crypto/Hash.hs:58:1-47 4169 23 0.0 0.0 0.0 0.0 - hashFinalize Crypto.Hash Crypto/Hash.hs:(92,1)-(95,17) 4170 23 0.0 0.0 0.0 0.0 - allocAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:74:1-45 4184 23 0.0 0.0 0.0 0.0 - new Basement.Block.Base Basement/Block/Base.hs:304:1-76 4185 23 0.0 0.0 0.0 0.0 - unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 4186 23 0.0 0.0 0.0 0.0 - withMutablePtrHint Basement.Block.Base Basement/Block/Base.hs:(475,1)-(489,39) 4187 23 0.0 0.0 0.0 0.0 - copy Data.ByteArray.Methods Data/ByteArray/Methods.hs:(223,1)-(226,21) 4192 23 0.0 0.0 0.0 0.0 - isMutablePinned Basement.Block.Base Basement/Block/Base.hs:100:1-90 4188 23 0.0 0.0 0.0 0.0 - compatIsMutableByteArrayPinned# Basement.Compat.Primitive Basement/Compat/Primitive.hs:70:1-65 4189 23 0.0 0.0 0.0 0.0 - toPinnedStatus# Basement.Compat.Primitive Basement/Compat/Primitive.hs:(47,1)-(48,27) 4190 23 0.0 0.0 0.0 0.0 - unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 4191 23 0.0 0.0 0.0 0.0 - hashInit Crypto.Hash Crypto/Hash.hs:(66,1)-(67,24) 4182 23 0.0 0.0 0.0 0.0 - allocAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:74:1-45 4183 23 0.0 0.0 0.0 0.0 - hashUpdate Crypto.Hash Crypto/Hash.hs:(71,1)-(73,37) 4171 23 0.0 0.0 0.0 0.0 - hashUpdates Crypto.Hash Crypto/Hash.hs:(81,1)-(86,32) 4179 23 0.0 0.0 0.0 0.0 - copyAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:(237,1)-(240,21) 4181 23 0.0 0.0 0.0 0.0 - null Data.ByteArray.Methods Data/ByteArray/Methods.hs:92:1-22 4180 23 0.0 0.0 0.0 0.0 - null Data.ByteArray.Methods Data/ByteArray/Methods.hs:92:1-22 4172 23 0.0 0.0 0.0 0.0 - unpack Data.ByteArray.Methods Data/ByteArray/Methods.hs:(104,1)-(110,34) 4193 23 0.0 0.0 0.1 0.0 - unsafeCast Basement.Block Basement/Block.hs:421:1-32 4194 759 0.0 0.0 0.0 0.0 - withPtr Basement.Block.Base Basement/Block/Base.hs:(402,1)-(411,31) 4195 736 0.0 0.0 0.1 0.0 - isPinned Basement.Block.Base Basement/Block/Base.hs:97:1-67 4196 736 0.1 0.0 0.1 0.0 - compatIsByteArrayPinned# Basement.Compat.Primitive Basement/Compat/Primitive.hs:67:1-51 4197 736 0.0 0.0 0.0 0.0 - toPinnedStatus# Basement.Compat.Primitive Basement/Compat/Primitive.hs:(47,1)-(48,27) 4198 736 0.0 0.0 0.0 0.0 - unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 4199 736 0.0 0.0 0.0 0.0 - keccak EVM.Types src/EVM/Types.hs:(580,1)-(583,12) 4126 0 0.0 0.0 0.0 0.1 - keccakBytes EVM.Types src/EVM/Types.hs:(570,1)-(573,15) 4130 0 0.0 0.0 0.0 0.1 - hash Crypto.Hash Crypto/Hash.hs:58:1-47 4131 43 0.0 0.0 0.0 0.0 - hashFinalize Crypto.Hash Crypto/Hash.hs:(92,1)-(95,17) 4132 43 0.0 0.0 0.0 0.0 - allocAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:74:1-45 4144 43 0.0 0.0 0.0 0.0 - new Basement.Block.Base Basement/Block/Base.hs:304:1-76 4145 43 0.0 0.0 0.0 0.0 - unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 4146 43 0.0 0.0 0.0 0.0 - withMutablePtrHint Basement.Block.Base Basement/Block/Base.hs:(475,1)-(489,39) 4147 43 0.0 0.0 0.0 0.0 - copy Data.ByteArray.Methods Data/ByteArray/Methods.hs:(223,1)-(226,21) 4152 43 0.0 0.0 0.0 0.0 - isMutablePinned Basement.Block.Base Basement/Block/Base.hs:100:1-90 4148 43 0.0 0.0 0.0 0.0 - compatIsMutableByteArrayPinned# Basement.Compat.Primitive Basement/Compat/Primitive.hs:70:1-65 4149 43 0.0 0.0 0.0 0.0 - toPinnedStatus# Basement.Compat.Primitive Basement/Compat/Primitive.hs:(47,1)-(48,27) 4150 43 0.0 0.0 0.0 0.0 - unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 4151 43 0.0 0.0 0.0 0.0 - hashInit Crypto.Hash Crypto/Hash.hs:(66,1)-(67,24) 4141 43 0.0 0.0 0.0 0.0 - allocAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:74:1-45 4142 43 0.0 0.0 0.0 0.0 - hashUpdate Crypto.Hash Crypto/Hash.hs:(71,1)-(73,37) 4133 43 0.0 0.0 0.0 0.0 - hashUpdates Crypto.Hash Crypto/Hash.hs:(81,1)-(86,32) 4138 43 0.0 0.0 0.0 0.0 - copyAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:(237,1)-(240,21) 4140 43 0.0 0.0 0.0 0.0 - null Data.ByteArray.Methods Data/ByteArray/Methods.hs:92:1-22 4139 43 0.0 0.0 0.0 0.0 - null Data.ByteArray.Methods Data/ByteArray/Methods.hs:92:1-22 4134 43 0.0 0.0 0.0 0.0 - unpack Data.ByteArray.Methods Data/ByteArray/Methods.hs:(104,1)-(110,34) 4153 43 0.0 0.0 0.0 0.0 - unsafeCast Basement.Block Basement/Block.hs:421:1-32 4154 1419 0.0 0.0 0.0 0.0 - withPtr Basement.Block.Base Basement/Block/Base.hs:(402,1)-(411,31) 4155 1376 0.0 0.0 0.0 0.0 - isPinned Basement.Block.Base Basement/Block/Base.hs:97:1-67 4156 1376 0.0 0.0 0.0 0.0 - compatIsByteArrayPinned# Basement.Compat.Primitive Basement/Compat/Primitive.hs:67:1-51 4157 1376 0.0 0.0 0.0 0.0 - toPinnedStatus# Basement.Compat.Primitive Basement/Compat/Primitive.hs:(47,1)-(48,27) 4158 1376 0.0 0.0 0.0 0.0 - unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 4159 1376 0.0 0.0 0.0 0.0 - word EVM.Types src/EVM/Types.hs:521:1-21 4128 0 0.0 0.0 0.0 0.0 - word256 EVM.Types src/EVM/Types.hs:(510,1)-(518,67) 4160 43 0.0 0.0 0.0 0.0 - padLeft EVM.Types src/EVM/Types.hs:495:1-54 4161 43 0.0 0.0 0.0 0.0 - bytesRead Data.Serialize.Get src/Data/Serialize/Get.hs:838:1-45 4163 0 0.0 0.0 0.0 0.0 - makeSrcMaps EVM.Solidity src/EVM/Solidity.hs:(227,1)-(271,126) 4203 0 0.4 0.5 0.4 0.5 - union Data.HashMap.Base Data/HashMap/Base.hs:1287:1-23 4114 0 0.0 0.0 0.0 0.0 - runUnitTestContract EVM.UnitTest src/EVM/UnitTest.hs:(477,1)-(528,68) 4271 1 0.0 0.0 88.6 83.0 - interpret EVM.Stepper src/EVM/Stepper.hs:(117,1)-(141,33) 4272 7 0.0 0.0 0.1 0.2 - enter EVM.Stepper src/EVM/Stepper.hs:114:1-48 4281 0 0.0 0.0 0.0 0.0 - pushTrace EVM src/EVM.hs:(2438,1)-(2441,59) 4282 0 0.0 0.0 0.0 0.0 - children Data.Tree.Zipper Data/Tree/Zipper.hs:(166,1)-(172,7) 4425 1 0.0 0.0 0.0 0.0 - exec EVM.Exec src/EVM/Exec.hs:(48,1)-(51,23) 4295 0 0.0 0.0 0.1 0.2 - exec1 EVM src/EVM.hs:(547,1)-(1323,42) 4429 0 0.0 0.0 0.1 0.2 - genFromCV Data.SBV.Core.Model Data/SBV/Core/Model.hs:(103,1)-(104,95) 4435 166 0.0 0.0 0.0 0.0 - index EVM.Symbolic src/EVM/Symbolic.hs:(207,1)-(208,47) 4431 166 0.0 0.0 0.0 0.0 - genLiteral Data.SBV.Core.Model Data/SBV/Core/Model.hs:99:1-48 4433 0 0.0 0.0 0.0 0.0 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 4434 166 0.0 0.0 0.0 0.0 - len EVM.Symbolic src/EVM/Symbolic.hs:(161,1)-(162,38) 4430 166 0.0 0.0 0.0 0.0 - num EVM.Types src/EVM/Types.hs:492:1-18 4436 81 0.0 0.0 0.0 0.0 - limitStack EVM src/EVM.hs:(1809,1)-(1813,17) 4438 76 0.0 0.0 0.0 0.0 - burn EVM src/EVM.hs:(1826,1)-(1838,38) 4440 76 0.0 0.0 0.0 0.0 - num EVM.Types src/EVM/Types.hs:492:1-18 4442 76 0.0 0.0 0.0 0.0 - next EVM src/EVM.hs:543:1-46 4445 0 0.0 0.0 0.0 0.0 - pushSym EVM src/EVM.hs:2477:1-34 4447 0 0.0 0.0 0.0 0.0 - pushSym EVM src/EVM.hs:2477:1-34 4446 76 0.0 0.0 0.0 0.0 - next EVM src/EVM.hs:543:1-46 4444 71 0.0 0.0 0.0 0.0 - opSize EVM src/EVM.hs:(2542,1)-(2543,37) 4448 71 0.0 0.0 0.0 0.0 - num EVM.Types src/EVM/Types.hs:492:1-18 4449 49 0.0 0.0 0.0 0.0 - genFromCV Data.SBV.Core.Model Data/SBV/Core/Model.hs:(103,1)-(104,95) 5186 1 0.0 0.0 0.0 0.0 - svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 5187 1 0.0 0.0 0.0 0.0 - svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 5188 1 0.0 0.0 0.0 0.0 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 5189 1 0.0 0.0 0.0 0.0 - litWord EVM.Symbolic src/EVM/Symbolic.hs:24:1-52 5175 1 0.0 0.0 0.0 0.0 - genLiteral Data.SBV.Core.Model Data/SBV/Core/Model.hs:99:1-48 5177 1 0.0 0.0 0.0 0.0 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 5178 1 0.0 0.0 0.0 0.0 - svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 5179 1 0.0 0.0 0.0 0.0 - svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 5180 1 0.0 0.0 0.0 0.0 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 5181 1 0.0 0.0 0.0 0.0 - num EVM.Types src/EVM/Types.hs:492:1-18 5174 1 0.0 0.0 0.0 0.0 - w256lit EVM.Types src/EVM/Types.hs:346:1-48 4437 49 0.0 0.0 0.0 0.0 - genLiteral Data.SBV.Core.Model Data/SBV/Core/Model.hs:99:1-48 4452 47 0.0 0.0 0.0 0.0 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 4460 46 0.0 0.0 0.0 0.0 - svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 4461 46 0.0 0.0 0.0 0.0 - svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 4462 46 0.0 0.0 0.0 0.0 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 4463 46 0.0 0.0 0.0 0.0 - padRight EVM.Types src/EVM/Types.hs:498:1-55 4465 46 0.0 0.0 0.0 0.0 - burn EVM src/EVM.hs:(1826,1)-(1838,38) 4507 34 0.0 0.0 0.0 0.0 - num EVM.Types src/EVM/Types.hs:492:1-18 4508 34 0.0 0.0 0.0 0.0 - accessStorage EVM src/EVM.hs:(1674,1)-(1702,35) 4510 0 0.0 0.0 0.0 0.0 - readStorage EVM src/EVM.hs:(1662,1)-(1663,58) 4511 3 0.0 0.0 0.0 0.0 - forceLit EVM.Symbolic src/EVM/Symbolic.hs:(40,1)-(42,49) 4512 3 0.0 0.0 0.0 0.0 - genFromCV Data.SBV.Core.Model Data/SBV/Core/Model.hs:(103,1)-(104,95) 5219 1 0.0 0.0 0.0 0.0 - svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 5220 1 0.0 0.0 0.0 0.0 - svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 5221 1 0.0 0.0 0.0 0.0 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 5222 1 0.0 0.0 0.0 0.0 - writeStorage EVM src/EVM.hs:(1666,1)-(1667,78) 4529 2 0.0 0.0 0.0 0.0 - forceLit EVM.Symbolic src/EVM/Symbolic.hs:(40,1)-(42,49) 4531 2 0.0 0.0 0.0 0.0 - genFromCV Data.SBV.Core.Model Data/SBV/Core/Model.hs:(103,1)-(104,95) 4538 2 0.0 0.0 0.0 0.0 - svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 4539 2 0.0 0.0 0.0 0.0 - svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 4540 2 0.0 0.0 0.0 0.0 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 4541 2 0.0 0.0 0.0 0.0 - forceConcrete EVM src/EVM.hs:(1846,1)-(1848,22) 5000 0 0.0 0.0 0.0 0.0 - checkJump EVM src/EVM.hs:(2526,1)-(2539,35) 5001 0 0.0 0.0 0.0 0.0 - unId Data.Vector.Fusion.Util Data/Vector/Fusion/Util.hs:25:21-24 5008 16 0.0 0.0 0.0 0.0 - num EVM.Types src/EVM/Types.hs:492:1-18 5002 8 0.0 0.0 0.0 0.0 - array# Data.Primitive.Array Data/Primitive/Array.hs:87:5-10 5009 4 0.0 0.0 0.0 0.0 - genFromCV Data.SBV.Core.Model Data/SBV/Core/Model.hs:(103,1)-(104,95) 5007 4 0.0 0.0 0.0 0.0 - index EVM.Symbolic src/EVM/Symbolic.hs:(207,1)-(208,47) 5004 4 0.0 0.0 0.0 0.0 - genLiteral Data.SBV.Core.Model Data/SBV/Core/Model.hs:99:1-48 5005 0 0.0 0.0 0.0 0.0 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 5006 4 0.0 0.0 0.0 0.0 - len EVM.Symbolic src/EVM/Symbolic.hs:(161,1)-(162,38) 5003 4 0.0 0.0 0.0 0.0 - next EVM src/EVM.hs:543:1-46 4523 0 0.0 0.0 0.0 0.0 - stackOp2 EVM src/EVM.hs:(2500,1)-(2507,14) 4492 23 0.0 0.0 0.0 0.0 - burn EVM src/EVM.hs:(1826,1)-(1838,38) 4499 23 0.0 0.0 0.0 0.0 - num EVM.Types src/EVM/Types.hs:492:1-18 4500 23 0.0 0.0 0.0 0.0 - next EVM src/EVM.hs:543:1-46 4502 0 0.0 0.0 0.0 0.0 - next EVM src/EVM.hs:543:1-46 4501 23 0.0 0.0 0.0 0.0 - opSize EVM src/EVM.hs:(2542,1)-(2543,37) 4503 23 0.0 0.0 0.0 0.0 - svTimes Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(155,1)-(160,81) 4572 6 0.0 0.0 0.0 0.0 - cvVal Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:155:16-20 5228 2 0.0 0.0 0.0 0.0 - mapCV2 Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(359,1)-(371,141) 5229 2 0.0 0.0 0.0 0.0 - cvVal Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:155:16-20 5231 4 0.0 0.0 0.0 0.0 - cvSameType Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:231:1-37 5230 2 0.0 0.0 0.0 0.0 - svAnd Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(373,1)-(383,50) 4594 5 0.0 0.0 0.0 0.0 - mapCV2 Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(359,1)-(371,141) 5190 3 0.0 0.0 0.0 0.0 - cvVal Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:155:16-20 5192 6 0.0 0.0 0.0 0.0 - cvSameType Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:231:1-37 5191 3 0.0 0.0 0.0 0.0 - .^ Data.SBV.Core.Model Data/SBV/Core/Model.hs:(1262,1)-(1280,49) 4574 3 0.0 0.0 0.0 0.0 - genFromCV Data.SBV.Core.Model Data/SBV/Core/Model.hs:(103,1)-(104,95) 4578 3 0.0 0.0 0.0 0.0 - sFromIntegral Data.SBV.Core.Model Data/SBV/Core/Model.hs:(1428,1)-(1441,70) 4576 3 0.0 0.0 0.0 0.0 - genFromCV Data.SBV.Core.Model Data/SBV/Core/Model.hs:(103,1)-(104,95) 4580 3 0.0 0.0 0.0 0.0 - svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 4581 3 0.0 0.0 0.0 0.0 - svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 4582 3 0.0 0.0 0.0 0.0 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 4583 3 0.0 0.0 0.0 0.0 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 4579 3 0.0 0.0 0.0 0.0 - svTimes Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(155,1)-(160,81) 5223 2 0.0 0.0 0.0 0.0 - cvVal Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:155:16-20 5224 1 0.0 0.0 0.0 0.0 - mapCV2 Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(359,1)-(371,141) 5225 1 0.0 0.0 0.0 0.0 - cvVal Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:155:16-20 5227 2 0.0 0.0 0.0 0.0 - cvSameType Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:231:1-37 5226 1 0.0 0.0 0.0 0.0 - forceLit EVM.Symbolic src/EVM/Symbolic.hs:(40,1)-(42,49) 4494 3 0.0 0.0 0.0 0.0 - genFromCV Data.SBV.Core.Model Data/SBV/Core/Model.hs:(103,1)-(104,95) 4495 3 0.0 0.0 0.0 0.0 - svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 4496 3 0.0 0.0 0.0 0.0 - svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 4497 3 0.0 0.0 0.0 0.0 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 4498 3 0.0 0.0 0.0 0.0 - iteWhiff EVM.Types src/EVM/Types.hs:211:1-34 4913 3 0.0 0.0 0.0 0.0 - ite Data.SBV.Core.Model Data/SBV/Core/Model.hs:(1817,1)-(1819,52) 4965 3 0.0 0.0 0.0 0.0 - cvToBool Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:235:1-34 4966 3 0.0 0.0 0.0 0.0 - cvVal Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:155:16-20 4967 3 0.0 0.0 0.0 0.0 - svOr Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(387,1)-(398,48) 4589 3 0.0 0.0 0.0 0.0 - mapCV2 Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(359,1)-(371,141) 5232 1 0.0 0.0 0.0 0.0 - cvVal Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:155:16-20 5234 2 0.0 0.0 0.0 0.0 - cvSameType Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:231:1-37 5233 1 0.0 0.0 0.0 0.0 - svPlus Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(148,1)-(151,80) 5025 2 0.0 0.0 0.0 0.0 - cvVal Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:155:16-20 5026 2 0.0 0.0 0.0 0.0 - mapCV2 Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(359,1)-(371,141) 5027 2 0.0 0.0 0.0 0.0 - cvVal Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:155:16-20 5029 4 0.0 0.0 0.0 0.0 - cvSameType Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:231:1-37 5028 2 0.0 0.0 0.0 0.0 - ceilDiv EVM src/EVM.hs:2835:1-31 5218 1 0.0 0.0 0.0 0.0 - log2 EVM src/EVM.hs:2841:1-50 5217 1 0.0 0.0 0.0 0.0 - num EVM.Types src/EVM/Types.hs:492:1-18 5216 1 0.0 0.0 0.0 0.0 - sShiftRight Data.SBV.Core.Model Data/SBV/Core/Model.hs:1464:1-38 4978 1 0.0 0.0 0.0 0.0 - svShiftRight Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:726:1-28 4980 0 0.0 0.0 0.0 0.0 - svEqual Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(288,1)-(292,129) 4995 1 0.0 0.0 0.0 0.0 - cvVal Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:155:16-20 4996 1 0.0 0.0 0.0 0.0 - liftCV2 Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(310,1)-(322,148) 4997 1 0.0 0.0 0.0 0.0 - cvVal Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:155:16-20 4998 2 0.0 0.0 0.0 0.0 - svBool Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:81:1-40 4999 1 0.0 0.0 0.0 0.0 - svGreaterThan Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(352,1)-(355,147) 4990 1 0.0 0.0 0.0 0.0 - cvVal Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:155:16-20 4991 1 0.0 0.0 0.0 0.0 - liftCV2 Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(310,1)-(322,148) 4992 1 0.0 0.0 0.0 0.0 - cvVal Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:155:16-20 4993 2 0.0 0.0 0.0 0.0 - svBool Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:81:1-40 4994 1 0.0 0.0 0.0 0.0 - svLessThan Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(345,1)-(348,143) 4917 1 0.0 0.0 0.0 0.0 - cvVal Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:155:16-20 4961 1 0.0 0.0 0.0 0.0 - liftCV2 Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(310,1)-(322,148) 4962 1 0.0 0.0 0.0 0.0 - cvVal Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:155:16-20 4963 2 0.0 0.0 0.0 0.0 - svBool Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:81:1-40 4964 1 0.0 0.0 0.0 0.0 - svUNeg Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:170:1-61 5031 0 0.0 0.0 0.0 0.0 - mapCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(334,1)-(346,133) 5032 1 0.0 0.0 0.0 0.0 - cvVal Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:155:16-20 5033 1 0.0 0.0 0.0 0.0 - next EVM src/EVM.hs:543:1-46 4514 20 0.0 0.0 0.0 0.0 - opSize EVM src/EVM.hs:(2542,1)-(2543,37) 4524 20 0.0 0.0 0.0 0.0 - forceConcrete EVM src/EVM.hs:(1846,1)-(1848,22) 4450 16 0.0 0.0 0.0 0.0 - maybeLitWord EVM.Types src/EVM/Types.hs:324:1-68 4453 23 0.0 0.0 0.0 0.0 - genFromCV Data.SBV.Core.Model Data/SBV/Core/Model.hs:(103,1)-(104,95) 4469 22 0.0 0.0 0.0 0.0 - svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 4470 22 0.0 0.0 0.0 0.0 - svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 4471 22 0.0 0.0 0.0 0.0 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 4472 22 0.0 0.0 0.0 0.0 - burn EVM src/EVM.hs:(1826,1)-(1838,38) 4454 17 0.0 0.0 0.0 0.0 - num EVM.Types src/EVM/Types.hs:492:1-18 4455 17 0.0 0.0 0.0 0.0 - accessMemoryWord EVM src/EVM.hs:2391:1-53 4475 0 0.0 0.0 0.0 0.0 - accessMemoryRange EVM src/EVM.hs:(2383,1)-(2387,53) 4476 0 0.0 0.0 0.0 0.0 - accessUnboundedMemoryRange EVM src/EVM.hs:(2368,1)-(2375,14) 4477 0 0.0 0.0 0.0 0.0 - memoryCost EVM src/EVM.hs:(2824,1)-(2830,30) 4482 10 0.0 0.0 0.0 0.0 - ceilDiv EVM src/EVM.hs:2835:1-31 4483 10 0.0 0.0 0.0 0.0 - ceilDiv EVM src/EVM.hs:2835:1-31 4481 5 0.0 0.0 0.0 0.0 - num EVM.Types src/EVM/Types.hs:492:1-18 4479 5 0.0 0.0 0.0 0.0 - word256At EVM src/EVM.hs:(2418,1)-(2420,34) 4489 0 0.0 0.0 0.0 0.0 - setMemoryWord EVM.Symbolic src/EVM/Symbolic.hs:(191,1)-(194,61) 4490 3 0.0 0.0 0.0 0.0 - maybeLitWord EVM.Types src/EVM/Types.hs:324:1-68 4491 3 0.0 0.0 0.0 0.0 - genFromCV Data.SBV.Core.Model Data/SBV/Core/Model.hs:(103,1)-(104,95) 4696 3 0.0 0.0 0.0 0.0 - svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 4697 3 0.0 0.0 0.0 0.0 - svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 4698 3 0.0 0.0 0.0 0.0 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 4699 3 0.0 0.0 0.0 0.0 - setMemoryWord EVM.Concrete src/EVM/Concrete.hs:(82,1)-(83,43) 4688 3 0.0 0.0 0.0 0.0 - num EVM.Types src/EVM/Types.hs:492:1-18 4690 3 0.0 0.0 0.0 0.0 - word256Bytes EVM.Types src/EVM/Types.hs:537:1-59 4693 3 0.0 0.0 0.0 0.0 - byteAt EVM.Types src/EVM/Types.hs:524:1-46 4694 96 0.0 0.0 0.0 0.0 - num EVM.Types src/EVM/Types.hs:492:1-18 4695 96 0.0 0.0 0.0 0.0 - writeMemory EVM.Concrete src/EVM/Concrete.hs:(46,1)-(59,22) 4689 3 0.0 0.0 0.0 0.0 - num EVM.Types src/EVM/Types.hs:492:1-18 4691 12 0.0 0.0 0.0 0.0 - sliceMemory EVM.Concrete src/EVM/Concrete.hs:(42,1)-(43,50) 4700 3 0.0 0.0 0.0 0.0 - num EVM.Types src/EVM/Types.hs:492:1-18 4701 6 0.0 0.0 0.0 0.0 - byteStringSliceWithDefaultZeroes EVM.Concrete src/EVM/Concrete.hs:(27,1)-(35,51) 4702 3 0.0 0.0 0.0 0.0 - checkJump EVM src/EVM.hs:(2526,1)-(2539,35) 4624 0 0.0 0.0 0.0 0.0 - unId Data.Vector.Fusion.Util Data/Vector/Fusion/Util.hs:25:21-24 4640 24 0.0 0.0 0.0 0.0 - num EVM.Types src/EVM/Types.hs:492:1-18 4625 12 0.0 0.0 0.0 0.0 - array# Data.Primitive.Array Data/Primitive/Array.hs:87:5-10 4641 6 0.0 0.0 0.0 0.0 - genFromCV Data.SBV.Core.Model Data/SBV/Core/Model.hs:(103,1)-(104,95) 4632 6 0.0 0.0 0.0 0.0 - index EVM.Symbolic src/EVM/Symbolic.hs:(207,1)-(208,47) 4628 6 0.0 0.0 0.0 0.0 - genLiteral Data.SBV.Core.Model Data/SBV/Core/Model.hs:99:1-48 4629 0 0.0 0.0 0.0 0.0 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 4630 6 0.0 0.0 0.0 0.0 - len EVM.Symbolic src/EVM/Symbolic.hs:(161,1)-(162,38) 4626 6 0.0 0.0 0.0 0.0 - checkJump EVM src/EVM.hs:(2526,1)-(2539,35) 4623 10 0.0 0.0 0.0 0.0 - num EVM.Types src/EVM/Types.hs:492:1-18 4631 10 0.0 0.0 0.0 0.0 - accessMemoryWord EVM src/EVM.hs:2391:1-53 4456 5 0.0 0.0 0.0 0.0 - accessMemoryRange EVM src/EVM.hs:(2383,1)-(2387,53) 4458 5 0.0 0.0 0.0 0.0 - accessUnboundedMemoryRange EVM src/EVM.hs:(2368,1)-(2375,14) 4473 5 0.0 0.0 0.0 0.0 - num EVM.Types src/EVM/Types.hs:492:1-18 4480 10 0.0 0.0 0.0 0.0 - num EVM.Types src/EVM/Types.hs:492:1-18 4687 5 0.0 0.0 0.0 0.0 - word256At EVM src/EVM.hs:(2418,1)-(2420,34) 4488 5 0.0 0.0 0.0 0.0 - readMemoryWord EVM.Symbolic src/EVM/Symbolic.hs:(183,1)-(184,75) 5010 2 0.0 0.0 0.0 0.0 - litWord EVM.Symbolic src/EVM/Symbolic.hs:24:1-52 5014 2 0.0 0.0 0.0 0.0 - genLiteral Data.SBV.Core.Model Data/SBV/Core/Model.hs:99:1-48 5017 2 0.0 0.0 0.0 0.0 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 5018 2 0.0 0.0 0.0 0.0 - svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 5019 2 0.0 0.0 0.0 0.0 - svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 5020 2 0.0 0.0 0.0 0.0 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 5021 2 0.0 0.0 0.0 0.0 - readMemoryWord EVM.Concrete src/EVM/Concrete.hs:(62,1)-(70,19) 5011 2 0.0 0.0 0.0 0.0 - num EVM.Types src/EVM/Types.hs:492:1-18 5012 68 0.0 0.0 0.0 0.0 - readByteOrZero EVM.Concrete src/EVM/Concrete.hs:24:1-46 5022 64 0.0 0.0 0.0 0.0 - readMemoryWord EVM.Concrete src/EVM/Concrete.hs:70:5-19 5013 2 0.0 0.0 0.0 0.0 - next EVM src/EVM.hs:543:1-46 4486 0 0.0 0.0 0.0 0.0 - stackOp1 EVM src/EVM.hs:(2485,1)-(2493,14) 4516 11 0.0 0.0 0.0 0.0 - burn EVM src/EVM.hs:(1826,1)-(1838,38) 4518 11 0.0 0.0 0.0 0.0 - num EVM.Types src/EVM/Types.hs:492:1-18 4519 11 0.0 0.0 0.0 0.0 - next EVM src/EVM.hs:543:1-46 4521 0 0.0 0.0 0.0 0.0 - next EVM src/EVM.hs:543:1-46 4520 11 0.0 0.0 0.0 0.0 - opSize EVM src/EVM.hs:(2542,1)-(2543,37) 4522 11 0.0 0.0 0.0 0.0 - iteWhiff EVM.Types src/EVM/Types.hs:211:1-34 4525 7 0.0 0.0 0.0 0.0 - ite Data.SBV.Core.Model Data/SBV/Core/Model.hs:(1817,1)-(1819,52) 4568 7 0.0 0.0 0.0 0.0 - cvToBool Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:235:1-34 4569 7 0.0 0.0 0.0 0.0 - cvVal Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:155:16-20 4570 7 0.0 0.0 0.0 0.0 - svEqual Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(288,1)-(292,129) 4557 7 0.0 0.0 0.0 0.0 - cvVal Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:155:16-20 4559 7 0.0 0.0 0.0 0.0 - liftCV2 Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(310,1)-(322,148) 4560 7 0.0 0.0 0.0 0.0 - cvVal Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:155:16-20 4561 14 0.0 0.0 0.0 0.0 - svBool Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:81:1-40 4566 7 0.0 0.0 0.0 0.0 - readSWordWithBound EVM.Symbolic src/EVM/Symbolic.hs:(136,1)-(157,48) 4968 1 0.0 0.0 0.0 0.0 - litWord EVM.Symbolic src/EVM/Symbolic.hs:24:1-52 4977 1 0.0 0.0 0.0 0.0 - genLiteral Data.SBV.Core.Model Data/SBV/Core/Model.hs:99:1-48 4983 1 0.0 0.0 0.0 0.0 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 4984 1 0.0 0.0 0.0 0.0 - svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 4985 1 0.0 0.0 0.0 0.0 - svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 4986 1 0.0 0.0 0.0 0.0 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 4987 1 0.0 0.0 0.0 0.0 - maybeLitWord EVM.Types src/EVM/Types.hs:324:1-68 4969 1 0.0 0.0 0.0 0.0 - genFromCV Data.SBV.Core.Model Data/SBV/Core/Model.hs:(103,1)-(104,95) 4970 1 0.0 0.0 0.0 0.0 - svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 4971 1 0.0 0.0 0.0 0.0 - svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 4972 1 0.0 0.0 0.0 0.0 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 4973 1 0.0 0.0 0.0 0.0 - readMemoryWord EVM.Concrete src/EVM/Concrete.hs:(62,1)-(70,19) 4974 1 0.0 0.0 0.0 0.0 - num EVM.Types src/EVM/Types.hs:492:1-18 4975 34 0.0 0.0 0.0 0.0 - readByteOrZero EVM.Concrete src/EVM/Concrete.hs:24:1-46 4989 32 0.0 0.0 0.0 0.0 - readMemoryWord EVM.Concrete src/EVM/Concrete.hs:70:5-19 4976 1 0.0 0.0 0.0 0.0 - svNot Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(417,1)-(423,34) 4591 0 0.0 0.0 0.0 0.0 - mapCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(334,1)-(346,133) 4592 3 0.0 0.0 0.0 0.0 - cvVal Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:155:16-20 4593 3 0.0 0.0 0.0 0.0 - notStatic EVM src/EVM.hs:(1816,1)-(1820,17) 4526 4 0.0 0.0 0.1 0.0 - accessStorage EVM src/EVM.hs:(1674,1)-(1702,35) 4528 3 0.0 0.0 0.0 0.0 - maybeLitWord EVM.Types src/EVM/Types.hs:324:1-68 4556 6 0.0 0.0 0.0 0.0 - genFromCV Data.SBV.Core.Model Data/SBV/Core/Model.hs:(103,1)-(104,95) 4600 6 0.0 0.0 0.0 0.0 - svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 4601 6 0.0 0.0 0.0 0.0 - svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 4602 6 0.0 0.0 0.0 0.0 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 4603 6 0.0 0.0 0.0 0.0 - accessStorageForGas EVM src/EVM.hs:(1919,1)-(1927,21) 4543 3 0.0 0.0 0.0 0.0 - maybeLitWord EVM.Types src/EVM/Types.hs:324:1-68 4544 3 0.0 0.0 0.0 0.0 - genFromCV Data.SBV.Core.Model Data/SBV/Core/Model.hs:(103,1)-(104,95) 4547 3 0.0 0.0 0.0 0.0 - svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 4548 3 0.0 0.0 0.0 0.0 - svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 4549 3 0.0 0.0 0.0 0.0 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 4550 3 0.0 0.0 0.0 0.0 - wordValue EVM.Concrete src/EVM/Concrete.hs:39:1-21 4546 3 0.0 0.0 0.0 0.0 - burn EVM src/EVM.hs:(1826,1)-(1838,38) 4609 3 0.0 0.0 0.0 0.0 - num EVM.Types src/EVM/Types.hs:492:1-18 4610 3 0.0 0.0 0.0 0.0 - writeStorage EVM src/EVM.hs:(1666,1)-(1667,78) 4633 3 0.0 0.0 0.0 0.0 - num EVM.Types src/EVM/Types.hs:492:1-18 4542 3 0.0 0.0 0.0 0.0 - readStorage EVM src/EVM.hs:(1662,1)-(1663,58) 4532 3 0.0 0.0 0.0 0.0 - forceLit EVM.Symbolic src/EVM/Symbolic.hs:(40,1)-(42,49) 4533 3 0.0 0.0 0.0 0.0 - genFromCV Data.SBV.Core.Model Data/SBV/Core/Model.hs:(103,1)-(104,95) 4534 3 0.0 0.0 0.0 0.0 - svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 4535 3 0.0 0.0 0.0 0.0 - svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 4536 3 0.0 0.0 0.0 0.0 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 4537 3 0.0 0.0 0.0 0.0 - forceLit EVM.Symbolic src/EVM/Symbolic.hs:(40,1)-(42,49) 4608 3 0.0 0.0 0.0 0.0 - maybeLitWord EVM.Types src/EVM/Types.hs:324:1-68 4599 3 0.0 0.0 0.0 0.0 - genFromCV Data.SBV.Core.Model Data/SBV/Core/Model.hs:(103,1)-(104,95) 4604 3 0.0 0.0 0.0 0.0 - svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 4605 3 0.0 0.0 0.0 0.0 - svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 4606 3 0.0 0.0 0.0 0.0 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 4607 3 0.0 0.0 0.0 0.0 - forceConcrete3 EVM src/EVM.hs:(1856,1)-(1858,36) 5023 1 0.0 0.0 0.1 0.0 - maybeLitWord EVM.Types src/EVM/Types.hs:324:1-68 5024 3 0.0 0.0 0.0 0.0 - genFromCV Data.SBV.Core.Model Data/SBV/Core/Model.hs:(103,1)-(104,95) 5034 3 0.0 0.0 0.0 0.0 - svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 5035 3 0.0 0.0 0.0 0.0 - svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 5036 3 0.0 0.0 0.0 0.0 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 5037 3 0.0 0.0 0.0 0.0 - num EVM.Types src/EVM/Types.hs:492:1-18 5121 2 0.0 0.0 0.0 0.0 - accessAccountForGas EVM src/EVM.hs:(1910,1)-(1914,17) 5046 1 0.0 0.0 0.0 0.0 - accessMemoryRange EVM src/EVM.hs:(2383,1)-(2387,53) 5038 1 0.0 0.0 0.1 0.0 - accessUnboundedMemoryRange EVM src/EVM.hs:(2368,1)-(2375,14) 5039 1 0.0 0.0 0.1 0.0 - burn EVM src/EVM.hs:(1826,1)-(1838,38) 5044 3 0.0 0.0 0.1 0.0 - num EVM.Types src/EVM/Types.hs:492:1-18 5045 4 0.0 0.0 0.0 0.0 - costOfCreate EVM src/EVM.hs:(2768,1)-(2774,58) 5048 1 0.0 0.0 0.0 0.0 - num EVM.Types src/EVM/Types.hs:492:1-18 5049 2 0.0 0.0 0.0 0.0 - allButOne64th EVM src/EVM.hs:2838:1-30 5051 1 0.0 0.0 0.0 0.0 - ceilDiv EVM src/EVM.hs:2835:1-31 5050 1 0.0 0.0 0.0 0.0 - create EVM src/EVM.hs:(2123,1)-(2184,30) 5096 1 0.0 0.0 0.1 0.0 - collision EVM src/EVM.hs:(2114,1)-(2118,18) 5102 1 0.0 0.0 0.0 0.0 - initialContract EVM src/EVM.hs:(516,1)-(533,39) 5130 1 0.0 0.0 0.1 0.0 - mkCodeOps EVM src/EVM.hs:(2721,1)-(2739,79) 5165 1 0.1 0.0 0.1 0.0 - marray# Data.Primitive.Array Data/Primitive/Array.hs:92:5-11 5172 1866 0.0 0.0 0.0 0.0 - unId Data.Vector.Fusion.Util Data/Vector/Fusion/Util.hs:25:21-24 5171 1866 0.0 0.0 0.0 0.0 - opSize EVM src/EVM.hs:(2542,1)-(2543,37) 5169 1865 0.0 0.0 0.0 0.0 - num EVM.Types src/EVM/Types.hs:492:1-18 5170 494 0.0 0.0 0.0 0.0 - readOp EVM src/EVM.hs:(2636,1)-(2718,21) 5173 1 0.0 0.0 0.0 0.0 - sChunks Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:122:30-36 5168 1 0.0 0.0 0.0 0.0 - sSize Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:124:30-34 5167 1 0.0 0.0 0.0 0.0 - upperBound Data.Vector.Fusion.Bundle.Size Data/Vector/Fusion/Bundle/Size.hs:(126,1)-(128,30) 5166 1 0.0 0.0 0.0 0.0 - mkOpIxMap EVM src/EVM.hs:(2549,1)-(2586,83) 5163 1 0.0 0.0 0.0 0.0 - len EVM.Symbolic src/EVM/Symbolic.hs:(161,1)-(162,38) 5164 1 0.0 0.0 0.0 0.0 - stripBytecodeMetadata EVM.Solidity src/EVM/Solidity.hs:(569,1)-(573,22) 5138 1 0.0 0.0 0.0 0.0 - keccak EVM.Types src/EVM/Types.hs:(580,1)-(583,12) 5131 0 0.0 0.0 0.0 0.0 - keccakBytes EVM.Types src/EVM/Types.hs:(570,1)-(573,15) 5133 0 0.0 0.0 0.0 0.0 - hash Crypto.Hash Crypto/Hash.hs:58:1-47 5134 1 0.0 0.0 0.0 0.0 - hashFinalize Crypto.Hash Crypto/Hash.hs:(92,1)-(95,17) 5135 1 0.0 0.0 0.0 0.0 - allocAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:74:1-45 5144 1 0.0 0.0 0.0 0.0 - new Basement.Block.Base Basement/Block/Base.hs:304:1-76 5145 1 0.0 0.0 0.0 0.0 - unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 5146 1 0.0 0.0 0.0 0.0 - withMutablePtrHint Basement.Block.Base Basement/Block/Base.hs:(475,1)-(489,39) 5147 1 0.0 0.0 0.0 0.0 - copy Data.ByteArray.Methods Data/ByteArray/Methods.hs:(223,1)-(226,21) 5152 1 0.0 0.0 0.0 0.0 - isMutablePinned Basement.Block.Base Basement/Block/Base.hs:100:1-90 5148 1 0.0 0.0 0.0 0.0 - compatIsMutableByteArrayPinned# Basement.Compat.Primitive Basement/Compat/Primitive.hs:70:1-65 5149 1 0.0 0.0 0.0 0.0 - toPinnedStatus# Basement.Compat.Primitive Basement/Compat/Primitive.hs:(47,1)-(48,27) 5150 1 0.0 0.0 0.0 0.0 - unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 5151 1 0.0 0.0 0.0 0.0 - hashInit Crypto.Hash Crypto/Hash.hs:(66,1)-(67,24) 5142 1 0.0 0.0 0.0 0.0 - allocAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:74:1-45 5143 1 0.0 0.0 0.0 0.0 - hashUpdate Crypto.Hash Crypto/Hash.hs:(71,1)-(73,37) 5136 1 0.0 0.0 0.0 0.0 - hashUpdates Crypto.Hash Crypto/Hash.hs:(81,1)-(86,32) 5139 1 0.0 0.0 0.0 0.0 - copyAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:(237,1)-(240,21) 5141 1 0.0 0.0 0.0 0.0 - null Data.ByteArray.Methods Data/ByteArray/Methods.hs:92:1-22 5140 1 0.0 0.0 0.0 0.0 - null Data.ByteArray.Methods Data/ByteArray/Methods.hs:92:1-22 5137 1 0.0 0.0 0.0 0.0 - unpack Data.ByteArray.Methods Data/ByteArray/Methods.hs:(104,1)-(110,34) 5153 1 0.0 0.0 0.0 0.0 - unsafeCast Basement.Block Basement/Block.hs:421:1-32 5154 33 0.0 0.0 0.0 0.0 - withPtr Basement.Block.Base Basement/Block/Base.hs:(402,1)-(411,31) 5155 32 0.0 0.0 0.0 0.0 - isPinned Basement.Block.Base Basement/Block/Base.hs:97:1-67 5156 32 0.0 0.0 0.0 0.0 - compatIsByteArrayPinned# Basement.Compat.Primitive Basement/Compat/Primitive.hs:67:1-51 5157 32 0.0 0.0 0.0 0.0 - toPinnedStatus# Basement.Compat.Primitive Basement/Compat/Primitive.hs:(47,1)-(48,27) 5158 32 0.0 0.0 0.0 0.0 - unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 5159 32 0.0 0.0 0.0 0.0 - word EVM.Types src/EVM/Types.hs:521:1-21 5132 0 0.0 0.0 0.0 0.0 - word256 EVM.Types src/EVM/Types.hs:(510,1)-(518,67) 5160 1 0.0 0.0 0.0 0.0 - padLeft EVM.Types src/EVM/Types.hs:495:1-54 5161 1 0.0 0.0 0.0 0.0 - bytesRead Data.Serialize.Get src/Data/Serialize/Get.hs:838:1-45 5162 0 0.0 0.0 0.0 0.0 - litWord EVM.Symbolic src/EVM/Symbolic.hs:24:1-52 5117 1 0.0 0.0 0.0 0.0 - genLiteral Data.SBV.Core.Model Data/SBV/Core/Model.hs:99:1-48 5125 1 0.0 0.0 0.0 0.0 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 5126 1 0.0 0.0 0.0 0.0 - svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 5127 1 0.0 0.0 0.0 0.0 - svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 5128 1 0.0 0.0 0.0 0.0 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 5129 1 0.0 0.0 0.0 0.0 - num EVM.Types src/EVM/Types.hs:492:1-18 5103 1 0.0 0.0 0.0 0.0 - pushTo EVM src/EVM.hs:1582:1-23 5112 1 0.0 0.0 0.0 0.0 - pushTrace EVM src/EVM.hs:(2438,1)-(2441,59) 5107 1 0.0 0.0 0.0 0.0 - children Data.Tree.Zipper Data/Tree/Zipper.hs:(166,1)-(172,7) 5113 1 0.0 0.0 0.0 0.0 - parents Data.Tree.Zipper Data/Tree/Zipper.hs:71:1-26 5294 1 0.0 0.0 0.0 0.0 - insert Data.Tree.Zipper Data/Tree/Zipper.hs:275:1-37 5295 1 0.0 0.0 0.0 0.0 - withTraceLocation EVM src/EVM.hs:(2426,1)-(2435,5) 5108 1 0.0 0.0 0.0 0.0 - transfer EVM src/EVM.hs:(1326,1)-(1329,31) 5106 1 0.0 0.0 0.0 0.0 - w256 EVM.Types src/EVM/Types.hs:90:1-24 5215 1 0.0 0.0 0.0 0.0 - litAddr EVM.Symbolic src/EVM/Symbolic.hs:27:1-36 5118 0 0.0 0.0 0.0 0.0 - genLiteral Data.SBV.Core.Model Data/SBV/Core/Model.hs:99:1-48 5119 1 0.0 0.0 0.0 0.0 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 5182 1 0.0 0.0 0.0 0.0 - svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 5183 1 0.0 0.0 0.0 0.0 - svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 5184 1 0.0 0.0 0.0 0.0 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 5185 1 0.0 0.0 0.0 0.0 - next EVM src/EVM.hs:543:1-46 5111 0 0.0 0.0 0.0 0.0 - touchAccount EVM src/EVM.hs:1895:1-57 5104 0 0.0 0.0 0.0 0.0 - pushTo EVM src/EVM.hs:1582:1-23 5105 2 0.0 0.0 0.0 0.0 - accessAccountForGas EVM src/EVM.hs:(1910,1)-(1914,17) 5047 0 0.0 0.0 0.0 0.0 - num EVM.Types src/EVM/Types.hs:492:1-18 5040 3 0.0 0.0 0.0 0.0 - memoryCost EVM src/EVM.hs:(2824,1)-(2830,30) 5042 2 0.0 0.0 0.0 0.0 - ceilDiv EVM src/EVM.hs:2835:1-31 5043 2 0.0 0.0 0.0 0.0 - ceilDiv EVM src/EVM.hs:2835:1-31 5041 1 0.0 0.0 0.0 0.0 - createAddress EVM.Concrete src/EVM/Concrete.hs:108:1-72 5052 1 0.0 0.0 0.0 0.0 - num EVM.Types src/EVM/Types.hs:492:1-18 5053 1 0.0 0.0 0.0 0.0 - rlpList EVM.RLP src/EVM/RLP.hs:63:1-30 5061 1 0.0 0.0 0.0 0.0 - rlpencode EVM.RLP src/EVM/RLP.hs:(50,1)-(52,70) 5062 3 0.0 0.0 0.0 0.0 - encodeLen EVM.RLP src/EVM/RLP.hs:(55,1)-(60,44) 5066 2 0.0 0.0 0.0 0.0 - num EVM.Types src/EVM/Types.hs:492:1-18 5067 2 0.0 0.0 0.0 0.0 - rlpWord256 EVM.RLP src/EVM/RLP.hs:(78,1)-(79,28) 5069 1 0.0 0.0 0.0 0.0 - octets EVM.RLP src/EVM/RLP.hs:(66,1)-(67,85) 5070 1 0.0 0.0 0.0 0.0 - keccak EVM.Types src/EVM/Types.hs:(580,1)-(583,12) 5054 0 0.0 0.0 0.0 0.0 - keccakBytes EVM.Types src/EVM/Types.hs:(570,1)-(573,15) 5056 0 0.0 0.0 0.0 0.0 - hash Crypto.Hash Crypto/Hash.hs:58:1-47 5057 1 0.0 0.0 0.0 0.0 - hashFinalize Crypto.Hash Crypto/Hash.hs:(92,1)-(95,17) 5058 1 0.0 0.0 0.0 0.0 - allocAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:74:1-45 5076 1 0.0 0.0 0.0 0.0 - new Basement.Block.Base Basement/Block/Base.hs:304:1-76 5077 1 0.0 0.0 0.0 0.0 - unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 5078 1 0.0 0.0 0.0 0.0 - withMutablePtrHint Basement.Block.Base Basement/Block/Base.hs:(475,1)-(489,39) 5079 1 0.0 0.0 0.0 0.0 - copy Data.ByteArray.Methods Data/ByteArray/Methods.hs:(223,1)-(226,21) 5084 1 0.0 0.0 0.0 0.0 - isMutablePinned Basement.Block.Base Basement/Block/Base.hs:100:1-90 5080 1 0.0 0.0 0.0 0.0 - compatIsMutableByteArrayPinned# Basement.Compat.Primitive Basement/Compat/Primitive.hs:70:1-65 5081 1 0.0 0.0 0.0 0.0 - toPinnedStatus# Basement.Compat.Primitive Basement/Compat/Primitive.hs:(47,1)-(48,27) 5082 1 0.0 0.0 0.0 0.0 - unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 5083 1 0.0 0.0 0.0 0.0 - hashInit Crypto.Hash Crypto/Hash.hs:(66,1)-(67,24) 5074 1 0.0 0.0 0.0 0.0 - allocAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:74:1-45 5075 1 0.0 0.0 0.0 0.0 - hashUpdate Crypto.Hash Crypto/Hash.hs:(71,1)-(73,37) 5059 1 0.0 0.0 0.0 0.0 - hashUpdates Crypto.Hash Crypto/Hash.hs:(81,1)-(86,32) 5071 1 0.0 0.0 0.0 0.0 - copyAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:(237,1)-(240,21) 5073 1 0.0 0.0 0.0 0.0 - null Data.ByteArray.Methods Data/ByteArray/Methods.hs:92:1-22 5072 1 0.0 0.0 0.0 0.0 - null Data.ByteArray.Methods Data/ByteArray/Methods.hs:92:1-22 5060 1 0.0 0.0 0.0 0.0 - unpack Data.ByteArray.Methods Data/ByteArray/Methods.hs:(104,1)-(110,34) 5085 1 0.0 0.0 0.0 0.0 - unsafeCast Basement.Block Basement/Block.hs:421:1-32 5086 33 0.0 0.0 0.0 0.0 - withPtr Basement.Block.Base Basement/Block/Base.hs:(402,1)-(411,31) 5087 32 0.0 0.0 0.0 0.0 - isPinned Basement.Block.Base Basement/Block/Base.hs:97:1-67 5088 32 0.0 0.0 0.0 0.0 - compatIsByteArrayPinned# Basement.Compat.Primitive Basement/Compat/Primitive.hs:67:1-51 5089 32 0.0 0.0 0.0 0.0 - toPinnedStatus# Basement.Compat.Primitive Basement/Compat/Primitive.hs:(47,1)-(48,27) 5090 32 0.0 0.0 0.0 0.0 - unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 5091 32 0.0 0.0 0.0 0.0 - word EVM.Types src/EVM/Types.hs:521:1-21 5055 0 0.0 0.0 0.0 0.0 - word256 EVM.Types src/EVM/Types.hs:(510,1)-(518,67) 5092 1 0.0 0.0 0.0 0.0 - padLeft EVM.Types src/EVM/Types.hs:495:1-54 5093 1 0.0 0.0 0.0 0.0 - bytesRead Data.Serialize.Get src/Data/Serialize/Get.hs:838:1-45 5094 0 0.0 0.0 0.0 0.0 - rlpAddrFull EVM.RLP src/EVM/RLP.hs:85:1-38 5063 0 0.0 0.0 0.0 0.0 - octetsFull EVM.RLP src/EVM/RLP.hs:(70,1)-(71,67) 5064 1 0.0 0.0 0.0 0.0 - num EVM.Types src/EVM/Types.hs:492:1-18 5065 0 0.0 0.0 0.0 0.0 - readMemory EVM src/EVM.hs:2412:1-92 5115 1 0.0 0.0 0.0 0.0 - num EVM.Types src/EVM/Types.hs:492:1-18 5120 2 0.0 0.0 0.0 0.0 - sliceWithZero EVM.Symbolic src/EVM/Symbolic.hs:(169,1)-(170,103) 5116 1 0.0 0.0 0.0 0.0 - byteStringSliceWithDefaultZeroes EVM.Concrete src/EVM/Concrete.hs:(27,1)-(35,51) 5122 1 0.0 0.0 0.0 0.0 - wordValue EVM.Concrete src/EVM/Concrete.hs:39:1-21 5068 1 0.0 0.0 0.0 0.0 - create EVM src/EVM.hs:(2123,1)-(2184,30) 5109 0 0.0 0.0 0.0 0.0 - next EVM src/EVM.hs:543:1-46 5110 1 0.0 0.0 0.0 0.0 - opSize EVM src/EVM.hs:(2542,1)-(2543,37) 5114 1 0.0 0.0 0.0 0.0 - next EVM src/EVM.hs:543:1-46 4613 0 0.0 0.0 0.0 0.0 - writeStorage EVM src/EVM.hs:(1666,1)-(1667,78) 4634 0 0.0 0.0 0.0 0.0 - forceLit EVM.Symbolic src/EVM/Symbolic.hs:(40,1)-(42,49) 4635 3 0.0 0.0 0.0 0.0 - genFromCV Data.SBV.Core.Model Data/SBV/Core/Model.hs:(103,1)-(104,95) 4636 3 0.0 0.0 0.0 0.0 - svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 4637 3 0.0 0.0 0.0 0.0 - svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 4638 3 0.0 0.0 0.0 0.0 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 4639 3 0.0 0.0 0.0 0.0 - accessStorage EVM src/EVM.hs:(1674,1)-(1702,35) 4509 3 0.0 0.0 0.0 0.0 - accessStorageForGas EVM src/EVM.hs:(1919,1)-(1927,21) 4504 3 0.0 0.0 0.0 0.0 - maybeLitWord EVM.Types src/EVM/Types.hs:324:1-68 4505 3 0.0 0.0 0.0 0.0 - genFromCV Data.SBV.Core.Model Data/SBV/Core/Model.hs:(103,1)-(104,95) 4552 3 0.0 0.0 0.0 0.0 - svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 4553 3 0.0 0.0 0.0 0.0 - svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 4554 3 0.0 0.0 0.0 0.0 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 4555 3 0.0 0.0 0.0 0.0 - wordValue EVM.Concrete src/EVM/Concrete.hs:39:1-21 4551 3 0.0 0.0 0.0 0.0 - forceConcrete3 EVM src/EVM.hs:(1856,1)-(1858,36) 4643 3 0.0 0.0 0.0 0.0 - maybeLitWord EVM.Types src/EVM/Types.hs:324:1-68 4644 9 0.0 0.0 0.0 0.0 - genFromCV Data.SBV.Core.Model Data/SBV/Core/Model.hs:(103,1)-(104,95) 4646 9 0.0 0.0 0.0 0.0 - svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 4647 9 0.0 0.0 0.0 0.0 - svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 4648 9 0.0 0.0 0.0 0.0 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 4649 9 0.0 0.0 0.0 0.0 - burn EVM src/EVM.hs:(1826,1)-(1838,38) 4651 6 0.0 0.0 0.0 0.0 - num EVM.Types src/EVM/Types.hs:492:1-18 4652 6 0.0 0.0 0.0 0.0 - accessUnboundedMemoryRange EVM src/EVM.hs:(2368,1)-(2375,14) 4654 0 0.0 0.0 0.0 0.0 - memoryCost EVM src/EVM.hs:(2824,1)-(2830,30) 4658 6 0.0 0.0 0.0 0.0 - ceilDiv EVM src/EVM.hs:2835:1-31 4659 6 0.0 0.0 0.0 0.0 - ceilDiv EVM src/EVM.hs:2835:1-31 4657 3 0.0 0.0 0.0 0.0 - num EVM.Types src/EVM/Types.hs:492:1-18 4655 3 0.0 0.0 0.0 0.0 - copyBytesToMemory EVM src/EVM.hs:(2395,1)-(2400,45) 4662 0 0.0 0.0 0.0 0.0 - writeMemory EVM.Symbolic src/EVM/Symbolic.hs:(173,1)-(180,49) 4663 3 0.0 0.0 0.0 0.0 - writeMemory EVM.Concrete src/EVM/Concrete.hs:(46,1)-(59,22) 4686 3 0.0 0.0 0.0 0.0 - num EVM.Types src/EVM/Types.hs:492:1-18 4703 12 0.0 0.0 0.0 0.0 - sliceMemory EVM.Concrete src/EVM/Concrete.hs:(42,1)-(43,50) 4704 3 0.0 0.0 0.0 0.0 - num EVM.Types src/EVM/Types.hs:492:1-18 4705 6 0.0 0.0 0.0 0.0 - byteStringSliceWithDefaultZeroes EVM.Concrete src/EVM/Concrete.hs:(27,1)-(35,51) 4706 3 0.0 0.0 0.0 0.0 - accessUnboundedMemoryRange EVM src/EVM.hs:(2368,1)-(2375,14) 4653 3 0.0 0.0 0.0 0.0 - num EVM.Types src/EVM/Types.hs:492:1-18 4656 6 0.0 0.0 0.0 0.0 - ceilDiv EVM src/EVM.hs:2835:1-31 4650 3 0.0 0.0 0.0 0.0 - copyBytesToMemory EVM src/EVM.hs:(2395,1)-(2400,45) 4660 3 0.0 0.0 0.0 0.0 - num EVM.Types src/EVM/Types.hs:492:1-18 4645 3 0.0 0.0 0.0 0.0 - forceConcrete2 EVM src/EVM.hs:(1851,1)-(1853,36) 4664 2 0.0 0.0 0.1 0.1 - maybeLitWord EVM.Types src/EVM/Types.hs:324:1-68 4665 4 0.0 0.0 0.0 0.0 - genFromCV Data.SBV.Core.Model Data/SBV/Core/Model.hs:(103,1)-(104,95) 4666 4 0.0 0.0 0.0 0.0 - svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 4667 4 0.0 0.0 0.0 0.0 - svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 4668 4 0.0 0.0 0.0 0.0 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 4669 4 0.0 0.0 0.0 0.0 - num EVM.Types src/EVM/Types.hs:492:1-18 4679 4 0.0 0.0 0.0 0.0 - accessMemoryRange EVM src/EVM.hs:(2383,1)-(2387,53) 4670 2 0.0 0.0 0.1 0.1 - accessUnboundedMemoryRange EVM src/EVM.hs:(2368,1)-(2375,14) 4671 2 0.0 0.0 0.1 0.1 - num EVM.Types src/EVM/Types.hs:492:1-18 4672 6 0.0 0.0 0.0 0.0 - memoryCost EVM src/EVM.hs:(2824,1)-(2830,30) 4674 4 0.0 0.0 0.0 0.0 - ceilDiv EVM src/EVM.hs:2835:1-31 4675 4 0.0 0.0 0.0 0.0 - burn EVM src/EVM.hs:(1826,1)-(1838,38) 4676 2 0.0 0.0 0.1 0.1 - num EVM.Types src/EVM/Types.hs:492:1-18 4677 2 0.0 0.0 0.0 0.0 - finishFrame EVM src/EVM.hs:(2237,1)-(2357,20) 4711 0 0.0 0.0 0.1 0.1 - insertTrace EVM src/EVM.hs:(2444,1)-(2447,60) 5193 1 0.0 0.0 0.0 0.0 - insert Data.Tree.Zipper Data/Tree/Zipper.hs:275:1-37 5198 1 0.0 0.0 0.0 0.0 - nextSpace Data.Tree.Zipper Data/Tree/Zipper.hs:153:1-69 5197 1 0.0 0.0 0.0 0.0 - withTraceLocation EVM src/EVM.hs:(2426,1)-(2435,5) 5194 1 0.0 0.0 0.0 0.0 - num EVM.Types src/EVM/Types.hs:492:1-18 5214 1 0.0 0.0 0.0 0.0 - replaceCode EVM src/EVM.hs:(2189,1)-(2202,74) 5195 1 0.0 0.0 0.0 0.0 - initialContract EVM src/EVM.hs:(516,1)-(533,39) 5243 1 0.0 0.0 0.0 0.0 - mkCodeOps EVM src/EVM.hs:(2721,1)-(2739,79) 5278 1 0.0 0.0 0.0 0.0 - marray# Data.Primitive.Array Data/Primitive/Array.hs:92:5-11 5285 1824 0.0 0.0 0.0 0.0 - unId Data.Vector.Fusion.Util Data/Vector/Fusion/Util.hs:25:21-24 5284 1824 0.0 0.0 0.0 0.0 - opSize EVM src/EVM.hs:(2542,1)-(2543,37) 5282 1823 0.0 0.0 0.0 0.0 - num EVM.Types src/EVM/Types.hs:492:1-18 5283 481 0.0 0.0 0.0 0.0 - readOp EVM src/EVM.hs:(2636,1)-(2718,21) 6106 66 0.0 0.0 0.0 0.0 - sChunks Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:122:30-36 5281 1 0.0 0.0 0.0 0.0 - sSize Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:124:30-34 5280 1 0.0 0.0 0.0 0.0 - upperBound Data.Vector.Fusion.Bundle.Size Data/Vector/Fusion/Bundle/Size.hs:(126,1)-(128,30) 5279 1 0.0 0.0 0.0 0.0 - mkOpIxMap EVM src/EVM.hs:(2549,1)-(2586,83) 5276 1 0.0 0.0 0.0 0.0 - len EVM.Symbolic src/EVM/Symbolic.hs:(161,1)-(162,38) 5277 1 0.0 0.0 0.0 0.0 - stripBytecodeMetadata EVM.Solidity src/EVM/Solidity.hs:(569,1)-(573,22) 5251 1 0.0 0.0 0.0 0.0 - keccak EVM.Types src/EVM/Types.hs:(580,1)-(583,12) 5244 0 0.0 0.0 0.0 0.0 - keccakBytes EVM.Types src/EVM/Types.hs:(570,1)-(573,15) 5246 0 0.0 0.0 0.0 0.0 - hash Crypto.Hash Crypto/Hash.hs:58:1-47 5247 1 0.0 0.0 0.0 0.0 - hashFinalize Crypto.Hash Crypto/Hash.hs:(92,1)-(95,17) 5248 1 0.0 0.0 0.0 0.0 - allocAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:74:1-45 5257 1 0.0 0.0 0.0 0.0 - new Basement.Block.Base Basement/Block/Base.hs:304:1-76 5258 1 0.0 0.0 0.0 0.0 - unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 5259 1 0.0 0.0 0.0 0.0 - withMutablePtrHint Basement.Block.Base Basement/Block/Base.hs:(475,1)-(489,39) 5260 1 0.0 0.0 0.0 0.0 - copy Data.ByteArray.Methods Data/ByteArray/Methods.hs:(223,1)-(226,21) 5265 1 0.0 0.0 0.0 0.0 - isMutablePinned Basement.Block.Base Basement/Block/Base.hs:100:1-90 5261 1 0.0 0.0 0.0 0.0 - compatIsMutableByteArrayPinned# Basement.Compat.Primitive Basement/Compat/Primitive.hs:70:1-65 5262 1 0.0 0.0 0.0 0.0 - toPinnedStatus# Basement.Compat.Primitive Basement/Compat/Primitive.hs:(47,1)-(48,27) 5263 1 0.0 0.0 0.0 0.0 - unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 5264 1 0.0 0.0 0.0 0.0 - hashInit Crypto.Hash Crypto/Hash.hs:(66,1)-(67,24) 5255 1 0.0 0.0 0.0 0.0 - allocAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:74:1-45 5256 1 0.0 0.0 0.0 0.0 - hashUpdate Crypto.Hash Crypto/Hash.hs:(71,1)-(73,37) 5249 1 0.0 0.0 0.0 0.0 - hashUpdates Crypto.Hash Crypto/Hash.hs:(81,1)-(86,32) 5252 1 0.0 0.0 0.0 0.0 - copyAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:(237,1)-(240,21) 5254 1 0.0 0.0 0.0 0.0 - null Data.ByteArray.Methods Data/ByteArray/Methods.hs:92:1-22 5253 1 0.0 0.0 0.0 0.0 - null Data.ByteArray.Methods Data/ByteArray/Methods.hs:92:1-22 5250 1 0.0 0.0 0.0 0.0 - unpack Data.ByteArray.Methods Data/ByteArray/Methods.hs:(104,1)-(110,34) 5266 1 0.0 0.0 0.0 0.0 - unsafeCast Basement.Block Basement/Block.hs:421:1-32 5267 33 0.0 0.0 0.0 0.0 - withPtr Basement.Block.Base Basement/Block/Base.hs:(402,1)-(411,31) 5268 32 0.0 0.0 0.0 0.0 - isPinned Basement.Block.Base Basement/Block/Base.hs:97:1-67 5269 32 0.0 0.0 0.0 0.0 - compatIsByteArrayPinned# Basement.Compat.Primitive Basement/Compat/Primitive.hs:67:1-51 5270 32 0.0 0.0 0.0 0.0 - toPinnedStatus# Basement.Compat.Primitive Basement/Compat/Primitive.hs:(47,1)-(48,27) 5271 32 0.0 0.0 0.0 0.0 - unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 5272 32 0.0 0.0 0.0 0.0 - word EVM.Types src/EVM/Types.hs:521:1-21 5245 0 0.0 0.0 0.0 0.0 - word256 EVM.Types src/EVM/Types.hs:(510,1)-(518,67) 5273 1 0.0 0.0 0.0 0.0 - padLeft EVM.Types src/EVM/Types.hs:495:1-54 5274 1 0.0 0.0 0.0 0.0 - bytesRead Data.Serialize.Get src/Data/Serialize/Get.hs:838:1-45 5275 0 0.0 0.0 0.0 0.0 - finalize EVM src/EVM.hs:(1721,1)-(1790,66) 4713 0 0.0 0.0 0.1 0.1 - accountEmpty EVM src/EVM.hs:(1712,1)-(1717,26) 4797 2 0.0 0.0 0.0 0.0 - len EVM.Symbolic src/EVM/Symbolic.hs:(161,1)-(162,38) 4798 2 0.0 0.0 0.0 0.0 - num EVM.Types src/EVM/Types.hs:492:1-18 4758 2 0.0 0.0 0.0 0.0 - r_block EVM.FeeSchedule src/EVM/FeeSchedule.hs:47:5-11 4801 1 0.0 0.0 0.0 0.0 - replaceCode EVM src/EVM.hs:(2189,1)-(2202,74) 4714 1 0.0 0.0 0.1 0.1 - initialContract EVM src/EVM.hs:(516,1)-(533,39) 4844 1 0.0 0.0 0.1 0.1 - mkCodeOps EVM src/EVM.hs:(2721,1)-(2739,79) 4879 1 0.0 0.1 0.0 0.1 - marray# Data.Primitive.Array Data/Primitive/Array.hs:92:5-11 4886 4303 0.0 0.0 0.0 0.0 - unId Data.Vector.Fusion.Util Data/Vector/Fusion/Util.hs:25:21-24 4885 4303 0.0 0.0 0.0 0.0 - opSize EVM src/EVM.hs:(2542,1)-(2543,37) 4883 4302 0.0 0.0 0.0 0.0 - num EVM.Types src/EVM/Types.hs:492:1-18 4884 1124 0.0 0.0 0.0 0.0 - readOp EVM src/EVM.hs:(2636,1)-(2718,21) 4911 138 0.0 0.0 0.0 0.0 - sChunks Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:122:30-36 4882 1 0.0 0.0 0.0 0.0 - sSize Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:124:30-34 4881 1 0.0 0.0 0.0 0.0 - upperBound Data.Vector.Fusion.Bundle.Size Data/Vector/Fusion/Bundle/Size.hs:(126,1)-(128,30) 4880 1 0.0 0.0 0.0 0.0 - mkOpIxMap EVM src/EVM.hs:(2549,1)-(2586,83) 4877 1 0.1 0.0 0.1 0.0 - len EVM.Symbolic src/EVM/Symbolic.hs:(161,1)-(162,38) 4878 1 0.0 0.0 0.0 0.0 - stripBytecodeMetadata EVM.Solidity src/EVM/Solidity.hs:(569,1)-(573,22) 4852 1 0.0 0.0 0.0 0.0 - keccak EVM.Types src/EVM/Types.hs:(580,1)-(583,12) 4845 0 0.0 0.0 0.0 0.0 - keccakBytes EVM.Types src/EVM/Types.hs:(570,1)-(573,15) 4847 0 0.0 0.0 0.0 0.0 - hash Crypto.Hash Crypto/Hash.hs:58:1-47 4848 1 0.0 0.0 0.0 0.0 - hashFinalize Crypto.Hash Crypto/Hash.hs:(92,1)-(95,17) 4849 1 0.0 0.0 0.0 0.0 - allocAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:74:1-45 4858 1 0.0 0.0 0.0 0.0 - new Basement.Block.Base Basement/Block/Base.hs:304:1-76 4859 1 0.0 0.0 0.0 0.0 - unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 4860 1 0.0 0.0 0.0 0.0 - withMutablePtrHint Basement.Block.Base Basement/Block/Base.hs:(475,1)-(489,39) 4861 1 0.0 0.0 0.0 0.0 - copy Data.ByteArray.Methods Data/ByteArray/Methods.hs:(223,1)-(226,21) 4866 1 0.0 0.0 0.0 0.0 - isMutablePinned Basement.Block.Base Basement/Block/Base.hs:100:1-90 4862 1 0.0 0.0 0.0 0.0 - compatIsMutableByteArrayPinned# Basement.Compat.Primitive Basement/Compat/Primitive.hs:70:1-65 4863 1 0.0 0.0 0.0 0.0 - toPinnedStatus# Basement.Compat.Primitive Basement/Compat/Primitive.hs:(47,1)-(48,27) 4864 1 0.0 0.0 0.0 0.0 - unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 4865 1 0.0 0.0 0.0 0.0 - hashInit Crypto.Hash Crypto/Hash.hs:(66,1)-(67,24) 4856 1 0.0 0.0 0.0 0.0 - allocAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:74:1-45 4857 1 0.0 0.0 0.0 0.0 - hashUpdate Crypto.Hash Crypto/Hash.hs:(71,1)-(73,37) 4850 1 0.0 0.0 0.0 0.0 - hashUpdates Crypto.Hash Crypto/Hash.hs:(81,1)-(86,32) 4853 1 0.0 0.0 0.0 0.0 - copyAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:(237,1)-(240,21) 4855 1 0.0 0.0 0.0 0.0 - null Data.ByteArray.Methods Data/ByteArray/Methods.hs:92:1-22 4854 1 0.0 0.0 0.0 0.0 - null Data.ByteArray.Methods Data/ByteArray/Methods.hs:92:1-22 4851 1 0.0 0.0 0.0 0.0 - unpack Data.ByteArray.Methods Data/ByteArray/Methods.hs:(104,1)-(110,34) 4867 1 0.0 0.0 0.0 0.0 - unsafeCast Basement.Block Basement/Block.hs:421:1-32 4868 33 0.0 0.0 0.0 0.0 - withPtr Basement.Block.Base Basement/Block/Base.hs:(402,1)-(411,31) 4869 32 0.0 0.0 0.0 0.0 - isPinned Basement.Block.Base Basement/Block/Base.hs:97:1-67 4870 32 0.0 0.0 0.0 0.0 - compatIsByteArrayPinned# Basement.Compat.Primitive Basement/Compat/Primitive.hs:67:1-51 4871 32 0.0 0.0 0.0 0.0 - toPinnedStatus# Basement.Compat.Primitive Basement/Compat/Primitive.hs:(47,1)-(48,27) 4872 32 0.0 0.0 0.0 0.0 - unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 4873 32 0.0 0.0 0.0 0.0 - word EVM.Types src/EVM/Types.hs:521:1-21 4846 0 0.0 0.0 0.0 0.0 - word256 EVM.Types src/EVM/Types.hs:(510,1)-(518,67) 4874 1 0.0 0.0 0.0 0.0 - padLeft EVM.Types src/EVM/Types.hs:495:1-54 4875 1 0.0 0.0 0.0 0.0 - bytesRead Data.Serialize.Get src/Data/Serialize/Get.hs:838:1-45 4876 0 0.0 0.0 0.0 0.0 - w256 EVM.Types src/EVM/Types.hs:90:1-24 4756 1 0.0 0.0 0.0 0.0 - touchAccount EVM src/EVM.hs:1895:1-57 4716 0 0.0 0.0 0.0 0.0 - pushTo EVM src/EVM.hs:1582:1-23 4717 1 0.0 0.0 0.0 0.0 - popTrace EVM src/EVM.hs:(2450,1)-(2454,42) 5196 0 0.0 0.0 0.0 0.0 - nextSpace Data.Tree.Zipper Data/Tree/Zipper.hs:153:1-69 5201 1 0.0 0.0 0.0 0.0 - parent Data.Tree.Zipper Data/Tree/Zipper.hs:(124,1)-(132,17) 5199 1 0.0 0.0 0.0 0.0 - parents Data.Tree.Zipper Data/Tree/Zipper.hs:71:1-26 5200 1 0.0 0.0 0.0 0.0 - push EVM src/EVM.hs:2474:1-30 5204 0 0.0 0.0 0.0 0.0 - pushSym EVM src/EVM.hs:2477:1-34 5205 1 0.0 0.0 0.0 0.0 - w256lit EVM.Types src/EVM/Types.hs:346:1-48 5206 1 0.0 0.0 0.0 0.0 - genLiteral Data.SBV.Core.Model Data/SBV/Core/Model.hs:99:1-48 5207 1 0.0 0.0 0.0 0.0 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 5208 1 0.0 0.0 0.0 0.0 - svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 5209 1 0.0 0.0 0.0 0.0 - svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 5210 1 0.0 0.0 0.0 0.0 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 5211 1 0.0 0.0 0.0 0.0 - num EVM.Types src/EVM/Types.hs:492:1-18 5213 0 0.0 0.0 0.0 0.0 - ceilDiv EVM src/EVM.hs:2835:1-31 4673 2 0.0 0.0 0.0 0.0 - burn EVM src/EVM.hs:(1826,1)-(1838,38) 4708 2 0.0 0.0 0.0 0.0 - num EVM.Types src/EVM/Types.hs:492:1-18 4709 2 0.0 0.0 0.0 0.0 - finishFrame EVM src/EVM.hs:(2237,1)-(2357,20) 4710 2 0.0 0.0 0.0 0.0 - len EVM.Symbolic src/EVM/Symbolic.hs:(161,1)-(162,38) 4680 2 0.0 0.0 0.0 0.0 - readMemory EVM src/EVM.hs:2412:1-92 4681 2 0.0 0.0 0.0 0.0 - num EVM.Types src/EVM/Types.hs:492:1-18 4684 4 0.0 0.0 0.0 0.0 - sliceWithZero EVM.Symbolic src/EVM/Symbolic.hs:(169,1)-(170,103) 4683 2 0.0 0.0 0.0 0.0 - byteStringSliceWithDefaultZeroes EVM.Concrete src/EVM/Concrete.hs:(27,1)-(35,51) 4685 2 0.0 0.0 0.0 0.0 - finishFrame EVM src/EVM.hs:(2237,1)-(2357,20) 5236 0 0.0 0.0 0.0 0.0 - finalize EVM src/EVM.hs:(1721,1)-(1790,66) 5237 0 0.0 0.0 0.0 0.0 - accountEmpty EVM src/EVM.hs:(1712,1)-(1717,26) 5286 4 0.0 0.0 0.0 0.0 - len EVM.Symbolic src/EVM/Symbolic.hs:(161,1)-(162,38) 5287 4 0.0 0.0 0.0 0.0 - num EVM.Types src/EVM/Types.hs:492:1-18 5241 2 0.0 0.0 0.0 0.0 - noop EVM src/EVM.hs:1579:1-14 5242 1 0.0 0.0 0.0 0.0 - r_block EVM.FeeSchedule src/EVM/FeeSchedule.hs:47:5-11 5288 1 0.0 0.0 0.0 0.0 - w256 EVM.Types src/EVM/Types.hs:90:1-24 5240 1 0.0 0.0 0.0 0.0 - touchAccount EVM src/EVM.hs:1895:1-57 5238 0 0.0 0.0 0.0 0.0 - pushTo EVM src/EVM.hs:1582:1-23 5239 1 0.0 0.0 0.0 0.0 - word EVM.Types src/EVM/Types.hs:521:1-21 4464 0 0.0 0.0 0.0 0.0 - word256 EVM.Types src/EVM/Types.hs:(510,1)-(518,67) 4466 46 0.0 0.0 0.0 0.0 - padLeft EVM.Types src/EVM/Types.hs:495:1-54 4467 46 0.0 0.0 0.0 0.0 - bytesRead Data.Serialize.Get src/Data/Serialize/Get.hs:838:1-45 4468 0 0.0 0.0 0.0 0.0 - initializeUnitTest EVM.UnitTest src/EVM/UnitTest.hs:(142,1)-(172,17) 4286 0 0.0 0.0 0.0 0.0 - abiCall EVM.UnitTest src/EVM/UnitTest.hs:(842,1)-(845,53) 4835 0 0.0 0.0 0.0 0.0 - makeTxCall EVM.UnitTest src/EVM/UnitTest.hs:(848,1)-(859,17) 4836 0 0.0 0.0 0.0 0.0 - w256 EVM.Types src/EVM/Types.hs:90:1-24 4893 2 0.0 0.0 0.0 0.0 - initTx EVM.Transaction src/EVM/Transaction.hs:(182,1)-(205,47) 4897 1 0.0 0.0 0.0 0.0 - forceLit EVM.Symbolic src/EVM/Symbolic.hs:(40,1)-(42,49) 4910 2 0.0 0.0 0.0 0.0 - genFromCV Data.SBV.Core.Model Data/SBV/Core/Model.hs:(103,1)-(104,95) 5098 2 0.0 0.0 0.0 0.0 - svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 5099 2 0.0 0.0 0.0 0.0 - svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 5100 2 0.0 0.0 0.0 0.0 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 5101 2 0.0 0.0 0.0 0.0 - maybeLitWord EVM.Types src/EVM/Types.hs:324:1-68 4902 1 0.0 0.0 0.0 0.0 - setupTx EVM.Transaction src/EVM/Transaction.hs:(171,1)-(176,38) 4899 1 0.0 0.0 0.0 0.0 - touchAccount EVM.Transaction src/EVM/Transaction.hs:164:1-57 4900 2 0.0 0.0 0.0 0.0 - touchAccount EVM.Transaction src/EVM/Transaction.hs:164:1-57 4901 1 0.0 0.0 0.0 0.0 - loadContract EVM src/EVM.hs:(1794,1)-(1806,44) 4839 0 0.0 0.0 0.0 0.0 - resetState EVM src/EVM.hs:(2210,1)-(2213,26) 4840 0 0.0 0.0 0.0 0.0 - popTrace EVM src/EVM.hs:(2450,1)-(2454,42) 4896 0 0.0 0.0 0.0 0.0 - nextSpace Data.Tree.Zipper Data/Tree/Zipper.hs:153:1-69 4905 1 0.0 0.0 0.0 0.0 - parent Data.Tree.Zipper Data/Tree/Zipper.hs:(124,1)-(132,17) 4903 1 0.0 0.0 0.0 0.0 - parents Data.Tree.Zipper Data/Tree/Zipper.hs:71:1-26 4904 1 0.0 0.0 0.0 0.0 - pushTrace EVM src/EVM.hs:(2438,1)-(2441,59) 4289 0 0.0 0.0 0.0 0.0 - children Data.Tree.Zipper Data/Tree/Zipper.hs:(166,1)-(172,7) 4426 2 0.0 0.0 0.0 0.0 - view Control.Monad.Operational src/Control/Monad/Operational.hs:138:1-26 4274 0 0.0 0.0 0.0 0.0 - viewT Control.Monad.Operational src/Control/Monad/Operational.hs:(239,1)-(243,54) 4275 13 0.0 0.0 0.0 0.0 - execFully EVM.Stepper src/EVM/Stepper.hs:(82,1)-(91,20) 4802 0 0.0 0.0 0.0 0.0 - initializeUnitTest EVM.UnitTest src/EVM/UnitTest.hs:(142,1)-(172,17) 4803 0 0.0 0.0 0.0 0.0 - evm EVM.Stepper src/EVM/Stepper.hs:78:1-21 5290 0 0.0 0.0 0.0 0.0 - popTrace EVM src/EVM.hs:(2450,1)-(2454,42) 5291 0 0.0 0.0 0.0 0.0 - nextSpace Data.Tree.Zipper Data/Tree/Zipper.hs:153:1-69 5296 1 0.0 0.0 0.0 0.0 - parent Data.Tree.Zipper Data/Tree/Zipper.hs:(124,1)-(132,17) 5292 1 0.0 0.0 0.0 0.0 - parents Data.Tree.Zipper Data/Tree/Zipper.hs:71:1-26 5293 1 0.0 0.0 0.0 0.0 - runTest EVM.UnitTest src/EVM/UnitTest.hs:(532,1)-(545,41) 5297 5 0.0 0.0 88.5 82.7 - fuzzRun EVM.UnitTest src/EVM/UnitTest.hs:(586,1)-(615,40) 5299 5 0.0 0.0 88.5 82.7 - fuzzTest EVM.UnitTest src/EVM/UnitTest.hs:(228,1)-(241,53) 5301 405 2.6 0.0 88.4 82.7 - interpretWithTraceId EVM.UnitTest src/EVM/UnitTest.hs:(256,1)-(279,78) 5310 2024 0.1 0.0 77.8 72.7 - execWithTraceId EVM.UnitTest src/EVM/UnitTest.hs:(282,1)-(283,51) 5336 0 0.0 0.0 76.4 71.8 - runWithTraceId EVM.UnitTest src/EVM/UnitTest.hs:(286,1)-(301,90) 5338 0 5.9 7.5 76.4 71.8 - currentContract EVM src/EVM.hs:(443,1)-(444,65) 5935 414891 1.8 0.6 1.8 0.6 - vmOpIx EVM src/EVM.hs:(2603,1)-(2605,57) 5936 414891 3.1 2.1 4.0 2.7 - unId Data.Vector.Fusion.Util Data/Vector/Fusion/Util.hs:25:21-24 5939 829782 0.0 0.0 0.0 0.0 - currentContract EVM src/EVM.hs:(443,1)-(444,65) 5937 414891 1.0 0.6 1.0 0.6 - exec1 EVM src/EVM.hs:(547,1)-(1323,42) 5345 0 18.8 14.4 64.7 61.1 - len EVM.Symbolic src/EVM/Symbolic.hs:(161,1)-(162,38) 5346 428143 0.1 0.3 0.1 0.3 - genFromCV Data.SBV.Core.Model Data/SBV/Core/Model.hs:(103,1)-(104,95) 5350 428142 0.1 0.0 0.1 0.0 - index EVM.Symbolic src/EVM/Symbolic.hs:(207,1)-(208,47) 5347 428142 0.6 2.0 3.5 3.9 - genLiteral Data.SBV.Core.Model Data/SBV/Core/Model.hs:99:1-48 5348 0 0.9 0.7 2.9 1.9 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 5349 428142 2.0 1.2 2.0 1.2 - num EVM.Types src/EVM/Types.hs:492:1-18 5351 218370 0.0 0.0 0.0 0.0 - burn EVM src/EVM.hs:(1826,1)-(1838,38) 5423 184668 3.6 6.7 8.2 10.7 - num EVM.Types src/EVM/Types.hs:492:1-18 5424 184668 1.1 1.1 1.1 1.1 - accessStorage EVM src/EVM.hs:(1674,1)-(1702,35) 5799 0 0.2 0.0 0.3 0.1 - readStorage EVM src/EVM.hs:(1662,1)-(1663,58) 5800 2266 0.0 0.0 0.1 0.1 - forceLit EVM.Symbolic src/EVM/Symbolic.hs:(40,1)-(42,49) 5801 2266 0.1 0.0 0.1 0.1 - genFromCV Data.SBV.Core.Model Data/SBV/Core/Model.hs:(103,1)-(104,95) 5802 2266 0.1 0.0 0.1 0.0 - svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 5803 2266 0.0 0.0 0.0 0.0 - svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 5804 2266 0.0 0.0 0.0 0.0 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 5805 2266 0.0 0.0 0.0 0.0 - writeStorage EVM src/EVM.hs:(1666,1)-(1667,78) 6187 496 0.0 0.0 0.0 0.0 - forceLit EVM.Symbolic src/EVM/Symbolic.hs:(40,1)-(42,49) 6188 496 0.0 0.0 0.0 0.0 - genFromCV Data.SBV.Core.Model Data/SBV/Core/Model.hs:(103,1)-(104,95) 6189 496 0.0 0.0 0.0 0.0 - svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 6190 496 0.0 0.0 0.0 0.0 - svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 6191 496 0.0 0.0 0.0 0.0 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 6192 496 0.0 0.0 0.0 0.0 - forceConcrete EVM src/EVM.hs:(1846,1)-(1848,22) 5666 0 0.0 0.0 3.1 1.7 - checkJump EVM src/EVM.hs:(2526,1)-(2539,35) 5667 0 1.9 0.9 3.1 1.7 - unId Data.Vector.Fusion.Util Data/Vector/Fusion/Util.hs:25:21-24 5674 139936 0.0 0.0 0.0 0.0 - num EVM.Types src/EVM/Types.hs:492:1-18 5668 69968 0.7 0.5 0.7 0.5 - array# Data.Primitive.Array Data/Primitive/Array.hs:87:5-10 5675 34984 0.0 0.0 0.0 0.0 - genFromCV Data.SBV.Core.Model Data/SBV/Core/Model.hs:(103,1)-(104,95) 5673 34984 0.1 0.0 0.1 0.0 - index EVM.Symbolic src/EVM/Symbolic.hs:(207,1)-(208,47) 5670 34984 0.1 0.2 0.5 0.3 - genLiteral Data.SBV.Core.Model Data/SBV/Core/Model.hs:99:1-48 5671 0 0.1 0.1 0.4 0.2 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 5672 34984 0.3 0.1 0.3 0.1 - len EVM.Symbolic src/EVM/Symbolic.hs:(161,1)-(162,38) 5669 34984 0.0 0.0 0.0 0.0 - next EVM src/EVM.hs:543:1-46 5426 0 0.2 1.1 0.2 1.1 - limitStack EVM src/EVM.hs:(1809,1)-(1813,17) 5353 169111 3.4 0.8 8.7 10.5 - burn EVM src/EVM.hs:(1826,1)-(1838,38) 5354 169111 2.6 4.7 5.0 9.3 - num EVM.Types src/EVM/Types.hs:492:1-18 5355 169111 1.6 1.0 1.6 1.0 - next EVM src/EVM.hs:543:1-46 5357 0 0.3 1.9 0.3 1.9 - push EVM src/EVM.hs:2474:1-30 6012 0 0.0 0.0 0.0 0.0 - pushSym EVM src/EVM.hs:2477:1-34 6013 0 0.0 0.0 0.0 0.0 - pushSym EVM src/EVM.hs:2477:1-34 5359 0 0.5 1.7 0.5 1.7 - pushSym EVM src/EVM.hs:2477:1-34 5358 168120 0.0 0.0 0.0 0.0 - next EVM src/EVM.hs:543:1-46 5356 164029 0.0 0.3 0.1 0.4 - opSize EVM src/EVM.hs:(2542,1)-(2543,37) 5360 164029 0.1 0.1 0.1 0.1 - num EVM.Types src/EVM/Types.hs:492:1-18 5361 103603 0.0 0.0 0.0 0.0 - num EVM.Types src/EVM/Types.hs:492:1-18 6081 1284 0.1 0.0 0.1 0.0 - len EVM.Symbolic src/EVM/Symbolic.hs:(161,1)-(162,38) 6315 350 0.0 0.0 0.0 0.0 - genFromCV Data.SBV.Core.Model Data/SBV/Core/Model.hs:(103,1)-(104,95) 6128 293 0.0 0.0 0.0 0.0 - svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 6129 293 0.0 0.0 0.0 0.0 - svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 6130 293 0.0 0.0 0.0 0.0 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 6131 293 0.0 0.0 0.0 0.0 - litWord EVM.Symbolic src/EVM/Symbolic.hs:24:1-52 6118 293 0.0 0.0 0.1 0.0 - genLiteral Data.SBV.Core.Model Data/SBV/Core/Model.hs:99:1-48 6119 293 0.0 0.0 0.1 0.0 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 6120 293 0.1 0.0 0.1 0.0 - svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 6121 293 0.0 0.0 0.0 0.0 - svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 6122 293 0.0 0.0 0.0 0.0 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 6123 293 0.0 0.0 0.0 0.0 - push EVM src/EVM.hs:2474:1-30 6010 0 0.0 0.0 0.1 0.0 - pushSym EVM src/EVM.hs:2477:1-34 6011 991 0.0 0.0 0.0 0.0 - w256lit EVM.Types src/EVM/Types.hs:346:1-48 6014 991 0.0 0.0 0.1 0.0 - genLiteral Data.SBV.Core.Model Data/SBV/Core/Model.hs:99:1-48 6015 991 0.0 0.0 0.0 0.0 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 6076 991 0.0 0.0 0.0 0.0 - svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 6077 991 0.0 0.0 0.0 0.0 - svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 6078 991 0.0 0.0 0.1 0.0 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 6079 991 0.1 0.0 0.1 0.0 - num EVM.Types src/EVM/Types.hs:492:1-18 6080 0 0.0 0.0 0.0 0.0 - w256lit EVM.Types src/EVM/Types.hs:346:1-48 5352 103603 1.0 0.5 4.1 3.0 - genLiteral Data.SBV.Core.Model Data/SBV/Core/Model.hs:99:1-48 5363 90338 0.4 0.4 1.6 1.4 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 5369 85334 1.2 1.0 1.2 1.0 - svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 5370 85334 0.0 0.0 0.0 0.0 - svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 5371 85334 0.2 0.1 1.6 1.1 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 5372 85334 1.3 1.0 1.3 1.0 - next EVM src/EVM.hs:543:1-46 5425 99148 0.1 0.7 0.1 0.7 - opSize EVM src/EVM.hs:(2542,1)-(2543,37) 5427 99148 0.0 0.0 0.0 0.0 - padRight EVM.Types src/EVM/Types.hs:498:1-55 5374 85334 0.1 0.1 0.1 0.1 - forceConcrete EVM src/EVM.hs:(1846,1)-(1848,22) 5362 59931 0.5 0.4 10.2 8.5 - maybeLitWord EVM.Types src/EVM/Types.hs:324:1-68 5364 74557 0.5 0.5 1.9 1.5 - genFromCV Data.SBV.Core.Model Data/SBV/Core/Model.hs:(103,1)-(104,95) 5378 69711 0.2 0.1 1.3 1.0 - svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 5379 69711 0.0 0.0 0.0 0.0 - svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 5380 69711 0.3 0.0 1.2 0.9 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 5381 69711 0.9 0.8 0.9 0.8 - checkJump EVM src/EVM.hs:(2526,1)-(2539,35) 5411 44764 0.0 0.0 0.2 0.2 - num EVM.Types src/EVM/Types.hs:492:1-18 5418 44764 0.2 0.2 0.2 0.2 - burn EVM src/EVM.hs:(1826,1)-(1838,38) 5365 34276 0.6 0.7 4.1 3.9 - num EVM.Types src/EVM/Types.hs:492:1-18 5366 34276 0.3 0.2 0.3 0.2 - accessMemoryRange EVM src/EVM.hs:(2383,1)-(2387,53) 6135 0 0.0 0.0 0.0 0.0 - accessUnboundedMemoryRange EVM src/EVM.hs:(2368,1)-(2375,14) 6136 0 0.0 0.0 0.0 0.0 - memoryCost EVM src/EVM.hs:(2824,1)-(2830,30) 6140 992 0.0 0.0 0.0 0.0 - ceilDiv EVM src/EVM.hs:2835:1-31 6141 992 0.0 0.0 0.0 0.0 - ceilDiv EVM src/EVM.hs:2835:1-31 6139 496 0.0 0.0 0.0 0.0 - next EVM src/EVM.hs:543:1-46 6146 496 0.0 0.0 0.0 0.0 - opSize EVM src/EVM.hs:(2542,1)-(2543,37) 6147 496 0.0 0.0 0.0 0.0 - num EVM.Types src/EVM/Types.hs:492:1-18 6137 496 0.0 0.0 0.0 0.0 - accessMemoryWord EVM src/EVM.hs:2391:1-53 5383 0 0.0 0.0 2.4 2.5 - accessMemoryRange EVM src/EVM.hs:(2383,1)-(2387,53) 5384 0 0.0 0.0 2.4 2.5 - accessUnboundedMemoryRange EVM src/EVM.hs:(2368,1)-(2375,14) 5385 0 0.3 0.4 2.4 2.5 - memoryCost EVM src/EVM.hs:(2824,1)-(2830,30) 5389 18658 0.1 0.0 0.1 0.1 - ceilDiv EVM src/EVM.hs:2835:1-31 5390 18658 0.0 0.0 0.0 0.0 - ceilDiv EVM src/EVM.hs:2835:1-31 5388 9329 0.2 0.0 0.2 0.0 - num EVM.Types src/EVM/Types.hs:492:1-18 5386 9329 0.0 0.0 0.0 0.0 - word256At EVM src/EVM.hs:(2418,1)-(2420,34) 5393 0 0.2 0.0 1.8 1.9 - setMemoryWord EVM.Symbolic src/EVM/Symbolic.hs:(191,1)-(194,61) 5394 5265 0.2 0.0 1.7 1.9 - maybeLitWord EVM.Types src/EVM/Types.hs:324:1-68 5395 5265 0.1 0.1 0.1 0.1 - genFromCV Data.SBV.Core.Model Data/SBV/Core/Model.hs:(103,1)-(104,95) 5825 5107 0.0 0.0 0.1 0.1 - svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 5826 5107 0.0 0.0 0.0 0.0 - svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 5827 5107 0.0 0.0 0.1 0.1 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 5828 5107 0.1 0.1 0.1 0.1 - setMemoryWord EVM.Concrete src/EVM/Concrete.hs:(82,1)-(83,43) 5818 5107 0.0 0.0 1.4 1.7 - num EVM.Types src/EVM/Types.hs:492:1-18 5820 5107 0.0 0.1 0.0 0.1 - word256Bytes EVM.Types src/EVM/Types.hs:537:1-59 5822 5107 0.1 0.6 1.0 1.5 - byteAt EVM.Types src/EVM/Types.hs:524:1-46 5823 163424 0.4 0.1 0.9 0.8 - num EVM.Types src/EVM/Types.hs:492:1-18 5824 163424 0.5 0.7 0.5 0.7 - writeMemory EVM.Concrete src/EVM/Concrete.hs:(46,1)-(59,22) 5819 5107 0.1 0.1 0.4 0.2 - num EVM.Types src/EVM/Types.hs:492:1-18 5821 20428 0.2 0.1 0.2 0.1 - sliceMemory EVM.Concrete src/EVM/Concrete.hs:(42,1)-(43,50) 5829 5107 0.1 0.0 0.1 0.1 - num EVM.Types src/EVM/Types.hs:492:1-18 5830 10214 0.1 0.0 0.1 0.0 - byteStringSliceWithDefaultZeroes EVM.Concrete src/EVM/Concrete.hs:(27,1)-(35,51) 5831 5107 0.0 0.0 0.0 0.0 - checkJump EVM src/EVM.hs:(2526,1)-(2539,35) 5412 0 0.5 0.2 0.8 0.5 - unId Data.Vector.Fusion.Util Data/Vector/Fusion/Util.hs:25:21-24 5421 39120 0.0 0.0 0.0 0.0 - num EVM.Types src/EVM/Types.hs:492:1-18 5413 19560 0.2 0.1 0.2 0.1 - array# Data.Primitive.Array Data/Primitive/Array.hs:87:5-10 5422 9780 0.0 0.0 0.0 0.0 - genFromCV Data.SBV.Core.Model Data/SBV/Core/Model.hs:(103,1)-(104,95) 5419 9780 0.0 0.0 0.0 0.0 - index EVM.Symbolic src/EVM/Symbolic.hs:(207,1)-(208,47) 5415 9780 0.1 0.0 0.1 0.1 - genLiteral Data.SBV.Core.Model Data/SBV/Core/Model.hs:99:1-48 5416 0 0.0 0.0 0.0 0.0 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 5417 9780 0.0 0.0 0.0 0.0 - len EVM.Symbolic src/EVM/Symbolic.hs:(161,1)-(162,38) 5414 9780 0.0 0.0 0.0 0.0 - num EVM.Types src/EVM/Types.hs:492:1-18 5814 9667 0.3 0.1 0.3 0.1 - accessMemoryWord EVM src/EVM.hs:2391:1-53 5367 9329 0.1 0.0 0.3 0.1 - accessMemoryRange EVM src/EVM.hs:(2383,1)-(2387,53) 5368 9329 0.0 0.0 0.3 0.1 - accessUnboundedMemoryRange EVM src/EVM.hs:(2368,1)-(2375,14) 5382 9329 0.2 0.0 0.3 0.1 - num EVM.Types src/EVM/Types.hs:492:1-18 5387 18658 0.1 0.1 0.1 0.1 - word256At EVM src/EVM.hs:(2418,1)-(2420,34) 5392 9329 0.3 0.1 1.9 1.0 - readMemoryWord EVM.Symbolic src/EVM/Symbolic.hs:(183,1)-(184,75) 5815 4064 0.0 0.0 1.6 1.0 - litWord EVM.Symbolic src/EVM/Symbolic.hs:24:1-52 5833 4064 0.2 0.0 0.3 0.1 - genLiteral Data.SBV.Core.Model Data/SBV/Core/Model.hs:99:1-48 5834 4064 0.1 0.0 0.1 0.1 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 5835 4064 0.1 0.0 0.1 0.0 - svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 5836 4064 0.0 0.0 0.0 0.0 - svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 5837 4064 0.0 0.0 0.0 0.1 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 5838 4064 0.0 0.0 0.0 0.0 - readMemoryWord EVM.Concrete src/EVM/Concrete.hs:(62,1)-(70,19) 5816 4064 0.6 0.0 1.3 0.8 - num EVM.Types src/EVM/Types.hs:492:1-18 5817 138176 0.7 0.8 0.7 0.8 - readByteOrZero EVM.Concrete src/EVM/Concrete.hs:24:1-46 5839 130048 0.0 0.0 0.0 0.0 - readMemoryWord EVM.Concrete src/EVM/Concrete.hs:70:5-19 5832 4064 0.0 0.0 0.0 0.0 - keccakBlob EVM.Concrete src/EVM/Concrete.hs:90:1-59 6144 992 0.0 0.0 0.9 1.1 - keccak EVM.Types src/EVM/Types.hs:(580,1)-(583,12) 6156 0 0.0 0.0 0.9 1.1 - keccakBytes EVM.Types src/EVM/Types.hs:(570,1)-(573,15) 6158 0 0.0 0.0 0.9 1.1 - hash Crypto.Hash Crypto/Hash.hs:58:1-47 6159 891 0.1 0.0 0.2 0.1 - hashFinalize Crypto.Hash Crypto/Hash.hs:(92,1)-(95,17) 6160 891 0.0 0.0 0.2 0.0 - allocAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:74:1-45 6168 891 0.0 0.0 0.2 0.0 - new Basement.Block.Base Basement/Block/Base.hs:304:1-76 6169 891 0.0 0.0 0.0 0.0 - unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 6170 891 0.0 0.0 0.0 0.0 - withMutablePtrHint Basement.Block.Base Basement/Block/Base.hs:(475,1)-(489,39) 6171 891 0.0 0.0 0.2 0.0 - copy Data.ByteArray.Methods Data/ByteArray/Methods.hs:(223,1)-(226,21) 6176 891 0.2 0.0 0.2 0.0 - isMutablePinned Basement.Block.Base Basement/Block/Base.hs:100:1-90 6172 891 0.0 0.0 0.0 0.0 - compatIsMutableByteArrayPinned# Basement.Compat.Primitive Basement/Compat/Primitive.hs:70:1-65 6173 891 0.0 0.0 0.0 0.0 - toPinnedStatus# Basement.Compat.Primitive Basement/Compat/Primitive.hs:(47,1)-(48,27) 6174 891 0.0 0.0 0.0 0.0 - unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 6175 891 0.0 0.0 0.0 0.0 - hashInit Crypto.Hash Crypto/Hash.hs:(66,1)-(67,24) 6166 891 0.0 0.0 0.0 0.0 - allocAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:74:1-45 6167 891 0.0 0.0 0.0 0.0 - hashUpdate Crypto.Hash Crypto/Hash.hs:(71,1)-(73,37) 6161 891 0.0 0.0 0.0 0.0 - hashUpdates Crypto.Hash Crypto/Hash.hs:(81,1)-(86,32) 6163 891 0.0 0.0 0.0 0.0 - copyAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:(237,1)-(240,21) 6165 891 0.0 0.0 0.0 0.0 - null Data.ByteArray.Methods Data/ByteArray/Methods.hs:92:1-22 6164 891 0.0 0.0 0.0 0.0 - null Data.ByteArray.Methods Data/ByteArray/Methods.hs:92:1-22 6162 891 0.0 0.0 0.0 0.0 - unpack Data.ByteArray.Methods Data/ByteArray/Methods.hs:(104,1)-(110,34) 6177 891 0.0 0.2 0.7 1.0 - unsafeCast Basement.Block Basement/Block.hs:421:1-32 6178 29403 0.0 0.0 0.0 0.0 - withPtr Basement.Block.Base Basement/Block/Base.hs:(402,1)-(411,31) 6179 28512 0.6 0.8 0.7 0.8 - isPinned Basement.Block.Base Basement/Block/Base.hs:97:1-67 6180 28512 0.1 0.0 0.1 0.0 - compatIsByteArrayPinned# Basement.Compat.Primitive Basement/Compat/Primitive.hs:67:1-51 6181 28512 0.0 0.0 0.0 0.0 - toPinnedStatus# Basement.Compat.Primitive Basement/Compat/Primitive.hs:(47,1)-(48,27) 6182 28512 0.0 0.0 0.0 0.0 - unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 6183 28512 0.1 0.1 0.1 0.1 - word EVM.Types src/EVM/Types.hs:521:1-21 6157 0 0.0 0.0 0.0 0.0 - word256 EVM.Types src/EVM/Types.hs:(510,1)-(518,67) 6184 891 0.0 0.0 0.0 0.0 - padLeft EVM.Types src/EVM/Types.hs:495:1-54 6185 891 0.0 0.0 0.0 0.0 - bytesRead Data.Serialize.Get src/Data/Serialize/Get.hs:838:1-45 6186 0 0.0 0.0 0.0 0.0 - accessMemoryRange EVM src/EVM.hs:(2383,1)-(2387,53) 6133 496 0.0 0.0 0.0 0.0 - accessUnboundedMemoryRange EVM src/EVM.hs:(2368,1)-(2375,14) 6134 496 0.0 0.0 0.0 0.0 - num EVM.Types src/EVM/Types.hs:492:1-18 6138 992 0.0 0.0 0.0 0.0 - ceilDiv EVM src/EVM.hs:2835:1-31 6132 496 0.0 0.0 0.0 0.0 - litWord EVM.Symbolic src/EVM/Symbolic.hs:24:1-52 6145 496 0.0 0.0 0.1 0.0 - genLiteral Data.SBV.Core.Model Data/SBV/Core/Model.hs:99:1-48 6151 496 0.1 0.0 0.1 0.0 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 6152 496 0.0 0.0 0.0 0.0 - svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 6153 496 0.0 0.0 0.0 0.0 - svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 6154 496 0.0 0.0 0.0 0.0 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 6155 496 0.0 0.0 0.0 0.0 - readMemory EVM src/EVM.hs:2412:1-92 6142 496 0.0 0.0 0.0 0.0 - num EVM.Types src/EVM/Types.hs:492:1-18 6148 992 0.0 0.0 0.0 0.0 - sliceWithZero EVM.Symbolic src/EVM/Symbolic.hs:(169,1)-(170,103) 6143 496 0.0 0.0 0.0 0.0 - byteStringSliceWithDefaultZeroes EVM.Concrete src/EVM/Concrete.hs:(27,1)-(35,51) 6149 496 0.0 0.0 0.0 0.0 - next EVM src/EVM.hs:543:1-46 5391 0 0.1 0.1 0.1 0.1 - stackOp2 EVM src/EVM.hs:(2500,1)-(2507,14) 5428 36018 1.0 0.3 3.9 3.2 - burn EVM src/EVM.hs:(1826,1)-(1838,38) 5429 36018 0.8 1.3 1.1 1.9 - num EVM.Types src/EVM/Types.hs:492:1-18 5430 36018 0.2 0.2 0.2 0.2 - next EVM src/EVM.hs:543:1-46 5432 0 0.1 0.4 0.1 0.4 - next EVM src/EVM.hs:543:1-46 5431 36018 0.1 0.1 0.1 0.1 - opSize EVM src/EVM.hs:(2542,1)-(2543,37) 5433 36018 0.1 0.0 0.1 0.0 - svPlus Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(148,1)-(151,80) 5684 13443 0.1 0.0 0.2 0.2 - cvVal Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:155:16-20 5685 9868 0.0 0.0 0.0 0.0 - mapCV2 Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(359,1)-(371,141) 5686 9868 0.2 0.2 0.2 0.2 - cvVal Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:155:16-20 5688 19736 0.0 0.0 0.0 0.0 - cvSameType Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:231:1-37 5687 9868 0.0 0.0 0.0 0.0 - iteWhiff EVM.Types src/EVM/Types.hs:211:1-34 5435 10548 0.1 0.0 0.1 0.0 - ite Data.SBV.Core.Model Data/SBV/Core/Model.hs:(1817,1)-(1819,52) 5635 10548 0.0 0.0 0.0 0.0 - cvToBool Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:235:1-34 5636 10548 0.0 0.0 0.0 0.0 - cvVal Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:155:16-20 5637 10548 0.0 0.0 0.0 0.0 - svEqual Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(288,1)-(292,129) 5661 6673 0.0 0.0 0.1 0.0 - cvVal Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:155:16-20 5662 6673 0.0 0.0 0.0 0.0 - liftCV2 Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(310,1)-(322,148) 5663 6673 0.1 0.0 0.1 0.0 - cvVal Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:155:16-20 5664 13346 0.0 0.0 0.0 0.0 - svBool Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:81:1-40 5665 6673 0.0 0.0 0.0 0.0 - svAnd Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(373,1)-(383,50) 5711 5729 0.3 0.1 0.3 0.2 - mapCV2 Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(359,1)-(371,141) 5712 5729 0.0 0.1 0.0 0.1 - cvVal Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:155:16-20 5714 11458 0.0 0.0 0.0 0.0 - cvSameType Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:231:1-37 5713 5729 0.0 0.0 0.0 0.0 - svGreaterThan Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(352,1)-(355,147) 5656 2293 0.0 0.0 0.1 0.0 - cvVal Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:155:16-20 5657 1799 0.0 0.0 0.0 0.0 - liftCV2 Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(310,1)-(322,148) 5658 1799 0.1 0.0 0.1 0.0 - cvVal Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:155:16-20 5659 3598 0.0 0.0 0.0 0.0 - svBool Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:81:1-40 5660 1799 0.0 0.0 0.0 0.0 - svLessThan Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(345,1)-(348,143) 5437 1582 0.0 0.0 0.0 0.0 - cvVal Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:155:16-20 5631 1582 0.0 0.0 0.0 0.0 - liftCV2 Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(310,1)-(322,148) 5632 1582 0.0 0.0 0.0 0.0 - cvVal Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:155:16-20 5633 3164 0.0 0.0 0.0 0.0 - svBool Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:81:1-40 5634 1582 0.0 0.0 0.0 0.0 - sShiftRight Data.SBV.Core.Model Data/SBV/Core/Model.hs:1464:1-38 5648 1449 0.1 0.0 0.1 0.0 - svShiftRight Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:726:1-28 5649 0 0.1 0.0 0.1 0.0 - .^ Data.SBV.Core.Model Data/SBV/Core/Model.hs:(1262,1)-(1280,49) 5841 1335 0.1 0.0 0.2 0.0 - svTimes Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(155,1)-(160,81) 5849 1684 0.1 0.0 0.1 0.0 - cvVal Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:155:16-20 5946 640 0.0 0.0 0.0 0.0 - mapCV2 Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(359,1)-(371,141) 5947 640 0.0 0.0 0.0 0.0 - cvVal Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:155:16-20 5949 1280 0.0 0.0 0.0 0.0 - cvSameType Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:231:1-37 5948 640 0.0 0.0 0.0 0.0 - genFromCV Data.SBV.Core.Model Data/SBV/Core/Model.hs:(103,1)-(104,95) 5843 1335 0.0 0.0 0.0 0.0 - sFromIntegral Data.SBV.Core.Model Data/SBV/Core/Model.hs:(1428,1)-(1441,70) 5842 1335 0.0 0.0 0.0 0.0 - genFromCV Data.SBV.Core.Model Data/SBV/Core/Model.hs:(103,1)-(104,95) 5845 1335 0.0 0.0 0.0 0.0 - svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 5846 1335 0.0 0.0 0.0 0.0 - svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 5847 1335 0.0 0.0 0.0 0.0 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 5848 1335 0.0 0.0 0.0 0.0 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 5844 1335 0.0 0.0 0.0 0.0 - forceLit EVM.Symbolic src/EVM/Symbolic.hs:(40,1)-(42,49) 5806 1335 0.0 0.0 0.1 0.0 - genFromCV Data.SBV.Core.Model Data/SBV/Core/Model.hs:(103,1)-(104,95) 5807 1335 0.0 0.0 0.1 0.0 - svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 5808 1335 0.0 0.0 0.0 0.0 - svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 5809 1335 0.0 0.0 0.1 0.0 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 5810 1335 0.1 0.0 0.1 0.0 - liftQRem Data.SBV.Core.Model Data/SBV/Core/Model.hs:(1702,1)-(1720,46) 5840 1335 0.1 0.0 0.3 0.1 - cvVal Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:155:16-20 5860 2088 0.0 0.0 0.0 0.0 - genLiteral Data.SBV.Core.Model Data/SBV/Core/Model.hs:99:1-48 5851 1044 0.1 0.0 0.1 0.0 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 5855 1044 0.1 0.0 0.1 0.0 - ite Data.SBV.Core.Model Data/SBV/Core/Model.hs:(1817,1)-(1819,52) 5857 1044 0.0 0.0 0.0 0.0 - cvToBool Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:235:1-34 5858 1044 0.0 0.0 0.0 0.0 - cvVal Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:155:16-20 5859 1044 0.0 0.0 0.0 0.0 - svEqual Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(288,1)-(292,129) 5850 1044 0.1 0.0 0.1 0.0 - cvVal Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:155:16-20 5852 1044 0.0 0.0 0.0 0.0 - liftCV2 Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(310,1)-(322,148) 5853 1044 0.0 0.0 0.0 0.0 - cvVal Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:155:16-20 5854 2088 0.0 0.0 0.0 0.0 - svBool Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:81:1-40 5856 1044 0.0 0.0 0.0 0.0 - slt EVM.Symbolic src/EVM/Symbolic.hs:(75,1)-(76,79) 5676 1248 0.1 0.0 0.3 0.2 - sFromIntegral Data.SBV.Core.Model Data/SBV/Core/Model.hs:(1428,1)-(1441,70) 5679 2496 0.1 0.0 0.2 0.2 - genFromCV Data.SBV.Core.Model Data/SBV/Core/Model.hs:(103,1)-(104,95) 5695 2496 0.0 0.0 0.1 0.0 - svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 5696 2496 0.0 0.0 0.0 0.0 - svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 5697 2496 0.0 0.0 0.1 0.0 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 5698 2496 0.1 0.0 0.1 0.0 - genLiteral Data.SBV.Core.Model Data/SBV/Core/Model.hs:99:1-48 5689 2496 0.0 0.0 0.1 0.1 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 5691 2496 0.1 0.1 0.1 0.1 - svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 5692 2496 0.0 0.0 0.0 0.0 - svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 5693 2496 0.0 0.0 0.0 0.1 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 5694 2496 0.0 0.1 0.0 0.1 - iteWhiff EVM.Types src/EVM/Types.hs:211:1-34 5677 1248 0.0 0.0 0.1 0.0 - ite Data.SBV.Core.Model Data/SBV/Core/Model.hs:(1817,1)-(1819,52) 5703 1248 0.0 0.0 0.1 0.0 - cvToBool Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:235:1-34 5704 1248 0.0 0.0 0.1 0.0 - cvVal Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:155:16-20 5705 1248 0.1 0.0 0.1 0.0 - svLessThan Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(345,1)-(348,143) 5690 1248 0.0 0.0 0.0 0.0 - cvVal Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:155:16-20 5699 1248 0.0 0.0 0.0 0.0 - liftCV2 Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(310,1)-(322,148) 5700 1248 0.0 0.0 0.0 0.0 - cvVal Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:155:16-20 5701 2496 0.0 0.0 0.0 0.0 - svBool Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:81:1-40 5702 1248 0.0 0.0 0.0 0.0 - ceilDiv EVM src/EVM.hs:2835:1-31 5813 1044 0.0 0.0 0.0 0.0 - log2 EVM src/EVM.hs:2841:1-50 5812 1044 0.0 0.0 0.0 0.0 - num EVM.Types src/EVM/Types.hs:492:1-18 5811 1044 0.0 0.0 0.0 0.0 - sShiftLeft Data.SBV.Core.Model Data/SBV/Core/Model.hs:1454:1-36 5943 640 0.0 0.0 0.0 0.0 - svShiftLeft Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:719:1-26 5945 0 0.0 0.0 0.0 0.0 - svUNeg Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:170:1-61 5681 0 0.1 0.0 0.2 0.1 - mapCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(334,1)-(346,133) 5682 4459 0.1 0.1 0.1 0.1 - cvVal Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:155:16-20 5683 4459 0.0 0.0 0.0 0.0 - stackOp1 EVM src/EVM.hs:(2485,1)-(2493,14) 5396 10290 0.4 0.1 2.9 1.5 - burn EVM src/EVM.hs:(1826,1)-(1838,38) 5397 10290 0.5 0.4 0.6 0.6 - num EVM.Types src/EVM/Types.hs:492:1-18 5398 10290 0.1 0.1 0.1 0.1 - next EVM src/EVM.hs:543:1-46 5400 0 0.0 0.1 0.0 0.1 - next EVM src/EVM.hs:543:1-46 5399 10290 0.0 0.0 0.0 0.0 - opSize EVM src/EVM.hs:(2542,1)-(2543,37) 5402 10290 0.0 0.0 0.0 0.0 - iteWhiff EVM.Types src/EVM/Types.hs:211:1-34 5401 6895 0.0 0.0 0.2 0.0 - ite Data.SBV.Core.Model Data/SBV/Core/Model.hs:(1817,1)-(1819,52) 5408 6895 0.1 0.0 0.2 0.0 - cvToBool Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:235:1-34 5409 6895 0.0 0.0 0.1 0.0 - cvVal Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:155:16-20 5410 6895 0.1 0.0 0.1 0.0 - svEqual Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(288,1)-(292,129) 5403 6895 0.0 0.0 0.1 0.0 - cvVal Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:155:16-20 5404 6895 0.0 0.0 0.0 0.0 - liftCV2 Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(310,1)-(322,148) 5405 6895 0.1 0.0 0.1 0.0 - cvVal Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:155:16-20 5406 13790 0.0 0.0 0.0 0.0 - svBool Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:81:1-40 5407 6895 0.0 0.0 0.0 0.0 - readSWordWithBound EVM.Symbolic src/EVM/Symbolic.hs:(136,1)-(157,48) 5638 3047 0.1 0.0 1.7 0.8 - litWord EVM.Symbolic src/EVM/Symbolic.hs:24:1-52 5647 3047 0.2 0.0 0.3 0.1 - genLiteral Data.SBV.Core.Model Data/SBV/Core/Model.hs:99:1-48 5650 3047 0.0 0.0 0.0 0.0 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 5651 3047 0.0 0.0 0.0 0.0 - svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 5652 3047 0.0 0.0 0.0 0.0 - svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 5653 3047 0.0 0.0 0.1 0.0 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 5654 3047 0.1 0.0 0.1 0.0 - maybeLitWord EVM.Types src/EVM/Types.hs:324:1-68 5639 3047 0.0 0.0 0.0 0.1 - genFromCV Data.SBV.Core.Model Data/SBV/Core/Model.hs:(103,1)-(104,95) 5640 3047 0.0 0.0 0.0 0.0 - svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 5641 3047 0.0 0.0 0.0 0.0 - svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 5642 3047 0.0 0.0 0.0 0.0 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 5643 3047 0.0 0.0 0.0 0.0 - readMemoryWord EVM.Concrete src/EVM/Concrete.hs:(62,1)-(70,19) 5644 3047 0.3 0.0 1.3 0.6 - num EVM.Types src/EVM/Types.hs:492:1-18 5645 103598 1.0 0.6 1.0 0.6 - readByteOrZero EVM.Concrete src/EVM/Concrete.hs:24:1-46 5655 97504 0.0 0.0 0.0 0.0 - readMemoryWord EVM.Concrete src/EVM/Concrete.hs:70:5-19 5646 3047 0.0 0.0 0.0 0.0 - svNot Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(417,1)-(423,34) 6316 0 0.0 0.0 0.0 0.0 - mapCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(334,1)-(346,133) 6317 348 0.0 0.0 0.0 0.0 - cvVal Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:155:16-20 6318 348 0.0 0.0 0.0 0.0 - accessStorage EVM src/EVM.hs:(1674,1)-(1702,35) 5798 2266 0.0 0.0 0.0 0.0 - accessStorageForGas EVM src/EVM.hs:(1919,1)-(1927,21) 5791 2266 0.1 0.0 0.2 0.1 - maybeLitWord EVM.Types src/EVM/Types.hs:324:1-68 5792 2266 0.1 0.0 0.1 0.1 - genFromCV Data.SBV.Core.Model Data/SBV/Core/Model.hs:(103,1)-(104,95) 5794 2266 0.0 0.0 0.1 0.0 - svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 5795 2266 0.0 0.0 0.0 0.0 - svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 5796 2266 0.0 0.0 0.1 0.0 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 5797 2266 0.1 0.0 0.1 0.0 - wordValue EVM.Concrete src/EVM/Concrete.hs:39:1-21 5793 2266 0.0 0.0 0.0 0.0 - notStatic EVM src/EVM.hs:(1816,1)-(1820,17) 6193 874 0.0 0.0 0.4 0.3 - accessStorage EVM src/EVM.hs:(1674,1)-(1702,35) 6194 582 0.1 0.0 0.3 0.1 - maybeLitWord EVM.Types src/EVM/Types.hs:324:1-68 6209 1164 0.0 0.0 0.0 0.0 - genFromCV Data.SBV.Core.Model Data/SBV/Core/Model.hs:(103,1)-(104,95) 6211 1164 0.0 0.0 0.0 0.0 - svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 6212 1164 0.0 0.0 0.0 0.0 - svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 6213 1164 0.0 0.0 0.0 0.0 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 6214 1164 0.0 0.0 0.0 0.0 - accessStorageForGas EVM src/EVM.hs:(1919,1)-(1927,21) 6202 582 0.1 0.0 0.1 0.0 - maybeLitWord EVM.Types src/EVM/Types.hs:324:1-68 6203 582 0.0 0.0 0.0 0.0 - genFromCV Data.SBV.Core.Model Data/SBV/Core/Model.hs:(103,1)-(104,95) 6205 582 0.0 0.0 0.0 0.0 - svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 6206 582 0.0 0.0 0.0 0.0 - svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 6207 582 0.0 0.0 0.0 0.0 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 6208 582 0.0 0.0 0.0 0.0 - wordValue EVM.Concrete src/EVM/Concrete.hs:39:1-21 6204 582 0.0 0.0 0.0 0.0 - burn EVM src/EVM.hs:(1826,1)-(1838,38) 6220 582 0.0 0.0 0.0 0.0 - num EVM.Types src/EVM/Types.hs:492:1-18 6221 582 0.0 0.0 0.0 0.0 - writeStorage EVM src/EVM.hs:(1666,1)-(1667,78) 6223 582 0.0 0.0 0.0 0.0 - num EVM.Types src/EVM/Types.hs:492:1-18 6201 582 0.0 0.0 0.0 0.0 - readStorage EVM src/EVM.hs:(1662,1)-(1663,58) 6195 582 0.0 0.0 0.2 0.0 - forceLit EVM.Symbolic src/EVM/Symbolic.hs:(40,1)-(42,49) 6196 582 0.1 0.0 0.2 0.0 - genFromCV Data.SBV.Core.Model Data/SBV/Core/Model.hs:(103,1)-(104,95) 6197 582 0.1 0.0 0.1 0.0 - svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 6198 582 0.0 0.0 0.0 0.0 - svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 6199 582 0.0 0.0 0.0 0.0 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 6200 582 0.0 0.0 0.0 0.0 - forceLit EVM.Symbolic src/EVM/Symbolic.hs:(40,1)-(42,49) 6219 582 0.0 0.0 0.0 0.0 - maybeLitWord EVM.Types src/EVM/Types.hs:324:1-68 6210 582 0.1 0.0 0.1 0.0 - genFromCV Data.SBV.Core.Model Data/SBV/Core/Model.hs:(103,1)-(104,95) 6215 582 0.0 0.0 0.0 0.0 - svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 6216 582 0.0 0.0 0.0 0.0 - svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 6217 582 0.0 0.0 0.0 0.0 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 6218 582 0.0 0.0 0.0 0.0 - forceConcrete2 EVM src/EVM.hs:(1851,1)-(1853,36) 6231 292 0.1 0.0 0.1 0.1 - num EVM.Types src/EVM/Types.hs:492:1-18 6237 586 0.0 0.0 0.0 0.0 - burn EVM src/EVM.hs:(1826,1)-(1838,38) 6238 584 0.0 0.0 0.0 0.0 - num EVM.Types src/EVM/Types.hs:492:1-18 6239 584 0.0 0.0 0.0 0.0 - accessMemoryRange EVM src/EVM.hs:(2383,1)-(2387,53) 6242 0 0.0 0.0 0.0 0.0 - accessUnboundedMemoryRange EVM src/EVM.hs:(2368,1)-(2375,14) 6243 0 0.0 0.0 0.0 0.0 - memoryCost EVM src/EVM.hs:(2824,1)-(2830,30) 6247 584 0.0 0.0 0.0 0.0 - ceilDiv EVM src/EVM.hs:2835:1-31 6248 584 0.0 0.0 0.0 0.0 - ceilDiv EVM src/EVM.hs:2835:1-31 6246 292 0.0 0.0 0.0 0.0 - num EVM.Types src/EVM/Types.hs:492:1-18 6244 292 0.0 0.0 0.0 0.0 - next EVM src/EVM.hs:543:1-46 6253 0 0.0 0.0 0.0 0.0 - pushToSequence EVM src/EVM.hs:1585:1-36 6255 0 0.0 0.0 0.0 0.0 - traceLog EVM src/EVM.hs:(2466,1)-(2469,60) 6250 0 0.0 0.0 0.0 0.0 - insert Data.Tree.Zipper Data/Tree/Zipper.hs:275:1-37 6257 292 0.0 0.0 0.0 0.0 - nextSpace Data.Tree.Zipper Data/Tree/Zipper.hs:153:1-69 6256 292 0.0 0.0 0.0 0.0 - maybeLitWord EVM.Types src/EVM/Types.hs:324:1-68 6232 584 0.0 0.0 0.0 0.0 - genFromCV Data.SBV.Core.Model Data/SBV/Core/Model.hs:(103,1)-(104,95) 6233 584 0.0 0.0 0.0 0.0 - svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 6234 584 0.0 0.0 0.0 0.0 - svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 6235 584 0.0 0.0 0.0 0.0 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 6236 584 0.0 0.0 0.0 0.0 - accessMemoryRange EVM src/EVM.hs:(2383,1)-(2387,53) 6240 292 0.0 0.0 0.0 0.0 - accessUnboundedMemoryRange EVM src/EVM.hs:(2368,1)-(2375,14) 6241 292 0.0 0.0 0.0 0.0 - num EVM.Types src/EVM/Types.hs:492:1-18 6245 584 0.0 0.0 0.0 0.0 - next EVM src/EVM.hs:543:1-46 6252 292 0.0 0.0 0.0 0.0 - opSize EVM src/EVM.hs:(2542,1)-(2543,37) 6258 292 0.0 0.0 0.0 0.0 - pushToSequence EVM src/EVM.hs:1585:1-36 6254 292 0.0 0.0 0.0 0.0 - traceLog EVM src/EVM.hs:(2466,1)-(2469,60) 6249 292 0.0 0.0 0.0 0.0 - withTraceLocation EVM src/EVM.hs:(2426,1)-(2435,5) 6251 292 0.0 0.0 0.0 0.0 - readMemory EVM src/EVM.hs:2412:1-92 6426 2 0.0 0.0 0.0 0.0 - num EVM.Types src/EVM/Types.hs:492:1-18 6455 2 0.0 0.0 0.0 0.0 - sliceWithZero EVM.Symbolic src/EVM/Symbolic.hs:(169,1)-(170,103) 6427 2 0.0 0.0 0.0 0.0 - byteStringSliceWithDefaultZeroes EVM.Concrete src/EVM/Concrete.hs:(27,1)-(35,51) 6456 1 0.0 0.0 0.0 0.0 - num EVM.Types src/EVM/Types.hs:492:1-18 6230 292 0.0 0.0 0.0 0.0 - next EVM src/EVM.hs:543:1-46 6222 0 0.0 0.0 0.0 0.0 - writeStorage EVM src/EVM.hs:(1666,1)-(1667,78) 6224 0 0.0 0.0 0.1 0.0 - forceLit EVM.Symbolic src/EVM/Symbolic.hs:(40,1)-(42,49) 6225 582 0.1 0.0 0.1 0.0 - genFromCV Data.SBV.Core.Model Data/SBV/Core/Model.hs:(103,1)-(104,95) 6226 582 0.0 0.0 0.0 0.0 - svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 6227 582 0.0 0.0 0.0 0.0 - svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 6228 582 0.0 0.0 0.0 0.0 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 6229 582 0.0 0.0 0.0 0.0 - forceConcrete2 EVM src/EVM.hs:(1851,1)-(1853,36) 5861 754 0.2 0.0 0.5 0.3 - maybeLitWord EVM.Types src/EVM/Types.hs:324:1-68 5862 1508 0.0 0.0 0.1 0.0 - genFromCV Data.SBV.Core.Model Data/SBV/Core/Model.hs:(103,1)-(104,95) 5863 1508 0.1 0.0 0.1 0.0 - svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 5864 1508 0.0 0.0 0.0 0.0 - svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 5865 1508 0.0 0.0 0.1 0.0 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 5866 1508 0.1 0.0 0.1 0.0 - accessMemoryRange EVM src/EVM.hs:(2383,1)-(2387,53) 5867 754 0.0 0.0 0.3 0.2 - accessUnboundedMemoryRange EVM src/EVM.hs:(2368,1)-(2375,14) 5868 754 0.0 0.0 0.3 0.2 - num EVM.Types src/EVM/Types.hs:492:1-18 5869 2262 0.0 0.0 0.0 0.0 - memoryCost EVM src/EVM.hs:(2824,1)-(2830,30) 5871 1508 0.0 0.0 0.0 0.0 - ceilDiv EVM src/EVM.hs:2835:1-31 5872 1508 0.0 0.0 0.0 0.0 - burn EVM src/EVM.hs:(1826,1)-(1838,38) 5873 754 0.0 0.0 0.3 0.2 - num EVM.Types src/EVM/Types.hs:492:1-18 5874 754 0.0 0.0 0.0 0.0 - finishFrame EVM src/EVM.hs:(2237,1)-(2357,20) 5876 0 0.1 0.0 0.3 0.2 - num EVM.Types src/EVM/Types.hs:492:1-18 6290 698 0.0 0.0 0.0 0.0 - copyCallBytesToMemory EVM src/EVM.hs:(2404,1)-(2409,66) 6291 349 0.1 0.0 0.1 0.0 - len EVM.Symbolic src/EVM/Symbolic.hs:(161,1)-(162,38) 6310 349 0.0 0.0 0.0 0.0 - num EVM.Types src/EVM/Types.hs:492:1-18 6309 349 0.0 0.0 0.0 0.0 - writeMemory EVM.Symbolic src/EVM/Symbolic.hs:(173,1)-(180,49) 6300 349 0.0 0.0 0.0 0.0 - writeMemory EVM.Concrete src/EVM/Concrete.hs:(46,1)-(59,22) 6308 349 0.0 0.0 0.0 0.0 - num EVM.Types src/EVM/Types.hs:492:1-18 6311 1396 0.0 0.0 0.0 0.0 - sliceMemory EVM.Concrete src/EVM/Concrete.hs:(42,1)-(43,50) 6312 349 0.0 0.0 0.0 0.0 - num EVM.Types src/EVM/Types.hs:492:1-18 6313 698 0.0 0.0 0.0 0.0 - byteStringSliceWithDefaultZeroes EVM.Concrete src/EVM/Concrete.hs:(27,1)-(35,51) 6314 349 0.0 0.0 0.0 0.0 - insertTrace EVM src/EVM.hs:(2444,1)-(2447,60) 6288 349 0.0 0.0 0.0 0.0 - insert Data.Tree.Zipper Data/Tree/Zipper.hs:275:1-37 6296 349 0.0 0.0 0.0 0.0 - nextSpace Data.Tree.Zipper Data/Tree/Zipper.hs:153:1-69 6295 349 0.0 0.0 0.0 0.0 - withTraceLocation EVM src/EVM.hs:(2426,1)-(2435,5) 6289 349 0.0 0.0 0.0 0.0 - forceConcreteBuffer EVM src/EVM.hs:(1876,1)-(1879,60) 6352 1 0.0 0.0 0.0 0.0 - finalize EVM src/EVM.hs:(1721,1)-(1790,66) 5879 0 0.0 0.1 0.1 0.1 - accountEmpty EVM src/EVM.hs:(1712,1)-(1717,26) 5885 1617 0.0 0.0 0.0 0.0 - len EVM.Symbolic src/EVM/Symbolic.hs:(161,1)-(162,38) 5886 1617 0.0 0.0 0.0 0.0 - num EVM.Types src/EVM/Types.hs:492:1-18 5883 810 0.1 0.0 0.1 0.0 - noop EVM src/EVM.hs:1579:1-14 5884 405 0.0 0.0 0.0 0.0 - r_block EVM.FeeSchedule src/EVM/FeeSchedule.hs:47:5-11 5887 405 0.0 0.0 0.0 0.0 - w256 EVM.Types src/EVM/Types.hs:90:1-24 5882 405 0.0 0.0 0.0 0.0 - touchAccount EVM src/EVM.hs:1895:1-57 5880 0 0.0 0.0 0.0 0.0 - pushTo EVM src/EVM.hs:1582:1-23 5881 405 0.0 0.0 0.0 0.0 - popTrace EVM src/EVM.hs:(2450,1)-(2454,42) 6294 0 0.0 0.0 0.0 0.0 - nextSpace Data.Tree.Zipper Data/Tree/Zipper.hs:153:1-69 6299 349 0.0 0.0 0.0 0.0 - parent Data.Tree.Zipper Data/Tree/Zipper.hs:(124,1)-(132,17) 6297 349 0.0 0.0 0.0 0.0 - parents Data.Tree.Zipper Data/Tree/Zipper.hs:71:1-26 6298 349 0.0 0.0 0.0 0.0 - push EVM src/EVM.hs:2474:1-30 6292 0 0.0 0.0 0.1 0.0 - pushSym EVM src/EVM.hs:2477:1-34 6293 349 0.0 0.0 0.0 0.0 - w256lit EVM.Types src/EVM/Types.hs:346:1-48 6301 349 0.0 0.0 0.1 0.0 - genLiteral Data.SBV.Core.Model Data/SBV/Core/Model.hs:99:1-48 6302 349 0.0 0.0 0.0 0.0 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 6303 349 0.0 0.0 0.0 0.0 - svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 6304 349 0.0 0.0 0.0 0.0 - svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 6305 349 0.0 0.0 0.1 0.0 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 6306 349 0.1 0.0 0.1 0.0 - num EVM.Types src/EVM/Types.hs:492:1-18 6307 0 0.0 0.0 0.0 0.0 - ceilDiv EVM src/EVM.hs:2835:1-31 5870 754 0.0 0.0 0.0 0.0 - finishFrame EVM src/EVM.hs:(2237,1)-(2357,20) 5875 754 0.0 0.0 0.0 0.0 - readMemory EVM src/EVM.hs:2412:1-92 5877 754 0.0 0.0 0.0 0.0 - num EVM.Types src/EVM/Types.hs:492:1-18 5892 1508 0.0 0.0 0.0 0.0 - sliceWithZero EVM.Symbolic src/EVM/Symbolic.hs:(169,1)-(170,103) 5878 754 0.0 0.0 0.0 0.0 - byteStringSliceWithDefaultZeroes EVM.Concrete src/EVM/Concrete.hs:(27,1)-(35,51) 5893 754 0.0 0.0 0.0 0.0 - forceConcrete5 EVM src/EVM.hs:(1866,1)-(1868,36) 6016 640 0.1 0.0 1.0 0.6 - maybeLitWord EVM.Types src/EVM/Types.hs:324:1-68 6017 3200 0.0 0.0 0.0 0.1 - genFromCV Data.SBV.Core.Model Data/SBV/Core/Model.hs:(103,1)-(104,95) 6055 2909 0.0 0.0 0.0 0.0 - svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 6056 2909 0.0 0.0 0.0 0.0 - svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 6057 2909 0.0 0.0 0.0 0.0 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 6058 2909 0.0 0.0 0.0 0.0 - delegateCall EVM src/EVM.hs:(2052,1)-(2108,31) 6023 640 0.1 0.0 0.8 0.5 - num EVM.Types src/EVM/Types.hs:492:1-18 6113 1920 0.0 0.0 0.0 0.0 - makeUnique EVM src/EVM.hs:(1592,1)-(1602,18) 6031 1280 0.0 0.0 0.6 0.4 - num EVM.Types src/EVM/Types.hs:492:1-18 6033 1920 0.1 0.1 0.1 0.1 - maybeLitWord EVM.Types src/EVM/Types.hs:324:1-68 6032 1280 0.0 0.0 0.0 0.0 - genFromCV Data.SBV.Core.Model Data/SBV/Core/Model.hs:(103,1)-(104,95) 6050 1280 0.0 0.0 0.0 0.0 - svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 6051 1280 0.0 0.0 0.0 0.0 - svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 6052 1280 0.0 0.0 0.0 0.0 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 6053 1280 0.0 0.0 0.0 0.0 - callChecks EVM src/EVM.hs:(1338,1)-(1359,31) 6054 640 0.1 0.0 0.6 0.3 - accessMemoryRange EVM src/EVM.hs:(2383,1)-(2387,53) 6059 1280 0.1 0.0 0.5 0.3 - accessUnboundedMemoryRange EVM src/EVM.hs:(2368,1)-(2375,14) 6060 989 0.0 0.0 0.5 0.3 - num EVM.Types src/EVM/Types.hs:492:1-18 6061 2618 0.0 0.0 0.0 0.0 - burn EVM src/EVM.hs:(1826,1)-(1838,38) 6066 2269 0.1 0.1 0.5 0.3 - num EVM.Types src/EVM/Types.hs:492:1-18 6067 3258 0.1 0.0 0.1 0.0 - readMemory EVM src/EVM.hs:2412:1-92 6114 1280 0.0 0.0 0.0 0.0 - num EVM.Types src/EVM/Types.hs:492:1-18 6116 1280 0.0 0.0 0.0 0.0 - sliceWithZero EVM.Symbolic src/EVM/Symbolic.hs:(169,1)-(170,103) 6115 1280 0.0 0.0 0.0 0.0 - byteStringSliceWithDefaultZeroes EVM.Concrete src/EVM/Concrete.hs:(27,1)-(35,51) 6117 640 0.0 0.0 0.0 0.0 - memoryCost EVM src/EVM.hs:(2824,1)-(2830,30) 6286 698 0.0 0.0 0.0 0.0 - ceilDiv EVM src/EVM.hs:2835:1-31 6287 698 0.0 0.0 0.0 0.0 - costOfCall EVM src/EVM.hs:(2748,1)-(2762,40) 6068 640 0.1 0.0 0.1 0.0 - num EVM.Types src/EVM/Types.hs:492:1-18 6071 1920 0.0 0.0 0.0 0.0 - accessAccountForGas EVM src/EVM.hs:(1910,1)-(1914,17) 6069 640 0.0 0.0 0.0 0.0 - allButOne64th EVM src/EVM.hs:2838:1-30 6075 640 0.0 0.0 0.0 0.0 - fetchAccount EVM src/EVM.hs:(1639,1)-(1659,23) 6082 640 0.1 0.1 0.2 0.1 - bytecode EVM src/EVM.hs:(415,1)-(417,29) 6090 640 0.1 0.0 0.1 0.0 - pushTo EVM src/EVM.hs:1582:1-23 6087 640 0.0 0.0 0.0 0.0 - pushTrace EVM src/EVM.hs:(2438,1)-(2441,59) 6083 640 0.0 0.0 0.0 0.0 - children Data.Tree.Zipper Data/Tree/Zipper.hs:(166,1)-(172,7) 6088 640 0.0 0.0 0.0 0.0 - parents Data.Tree.Zipper Data/Tree/Zipper.hs:71:1-26 6319 637 0.0 0.0 0.0 0.0 - withTraceLocation EVM src/EVM.hs:(2426,1)-(2435,5) 6084 640 0.0 0.0 0.0 0.0 - insert Data.Tree.Zipper Data/Tree/Zipper.hs:275:1-37 6320 637 0.0 0.0 0.0 0.0 - transfer EVM src/EVM.hs:(1326,1)-(1329,31) 6091 292 0.0 0.0 0.0 0.0 - next EVM src/EVM.hs:543:1-46 6086 0 0.0 0.0 0.0 0.0 - touchAccount EVM src/EVM.hs:1895:1-57 6097 0 0.0 0.0 0.0 0.0 - pushTo EVM src/EVM.hs:1582:1-23 6098 640 0.0 0.0 0.0 0.0 - readMemoryWord32 EVM.Symbolic src/EVM/Symbolic.hs:(187,1)-(188,75) 6261 640 0.1 0.0 0.1 0.0 - num EVM.Types src/EVM/Types.hs:492:1-18 6262 640 0.0 0.0 0.0 0.0 - genLiteral Data.SBV.Core.Model Data/SBV/Core/Model.hs:99:1-48 6265 640 0.0 0.0 0.0 0.0 - ceilDiv EVM src/EVM.hs:2835:1-31 6285 349 0.0 0.0 0.0 0.0 - memoryCost EVM src/EVM.hs:(2824,1)-(2830,30) 6064 1280 0.0 0.0 0.0 0.0 - ceilDiv EVM src/EVM.hs:2835:1-31 6065 1280 0.0 0.0 0.0 0.0 - ceilDiv EVM src/EVM.hs:2835:1-31 6063 640 0.0 0.0 0.0 0.0 - accountExists EVM src/EVM.hs:(1705,1)-(1708,20) 6072 640 0.0 0.0 0.0 0.0 - accountEmpty EVM src/EVM.hs:(1712,1)-(1717,26) 6073 640 0.0 0.0 0.0 0.0 - len EVM.Symbolic src/EVM/Symbolic.hs:(161,1)-(162,38) 6074 640 0.0 0.0 0.0 0.0 - sFromIntegral Data.SBV.Core.Model Data/SBV/Core/Model.hs:(1428,1)-(1441,70) 6025 1280 0.1 0.0 0.1 0.1 - genFromCV Data.SBV.Core.Model Data/SBV/Core/Model.hs:(103,1)-(104,95) 6046 1280 0.0 0.0 0.0 0.0 - svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 6047 1280 0.0 0.0 0.0 0.0 - svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 6048 1280 0.0 0.0 0.0 0.0 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 6049 1280 0.0 0.0 0.0 0.0 - genLiteral Data.SBV.Core.Model Data/SBV/Core/Model.hs:99:1-48 6030 1280 0.0 0.0 0.0 0.0 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 6034 1280 0.0 0.0 0.0 0.0 - svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 6035 1280 0.0 0.0 0.0 0.0 - svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 6036 1280 0.0 0.0 0.0 0.0 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 6037 1280 0.0 0.0 0.0 0.0 - next EVM src/EVM.hs:543:1-46 6085 640 0.0 0.0 0.0 0.0 - opSize EVM src/EVM.hs:(2542,1)-(2543,37) 6089 640 0.0 0.0 0.0 0.0 - w256lit EVM.Types src/EVM/Types.hs:346:1-48 6107 640 0.0 0.0 0.0 0.0 - genLiteral Data.SBV.Core.Model Data/SBV/Core/Model.hs:99:1-48 6108 640 0.0 0.0 0.0 0.0 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 6109 640 0.0 0.0 0.0 0.0 - svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 6110 640 0.0 0.0 0.0 0.0 - svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 6111 640 0.0 0.0 0.0 0.0 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 6112 640 0.0 0.0 0.0 0.0 - forceLit EVM.Symbolic src/EVM/Symbolic.hs:(40,1)-(42,49) 6018 292 0.0 0.0 0.1 0.0 - genFromCV Data.SBV.Core.Model Data/SBV/Core/Model.hs:(103,1)-(104,95) 6019 292 0.0 0.0 0.1 0.0 - svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 6020 292 0.0 0.0 0.0 0.0 - svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 6021 292 0.0 0.0 0.1 0.0 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 6022 292 0.1 0.0 0.1 0.0 - litWord EVM.Symbolic src/EVM/Symbolic.hs:24:1-52 6092 292 0.0 0.0 0.1 0.0 - svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 6103 292 0.0 0.0 0.0 0.0 - svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 6104 292 0.0 0.0 0.1 0.0 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 6105 292 0.1 0.0 0.1 0.0 - litAddr EVM.Symbolic src/EVM/Symbolic.hs:27:1-36 6093 0 0.1 0.0 0.1 0.0 - genLiteral Data.SBV.Core.Model Data/SBV/Core/Model.hs:99:1-48 6094 640 0.0 0.0 0.0 0.0 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 6124 292 0.0 0.0 0.0 0.0 - svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 6125 292 0.0 0.0 0.0 0.0 - svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 6126 292 0.0 0.0 0.0 0.0 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 6127 292 0.0 0.0 0.0 0.0 - touchAccount EVM src/EVM.hs:1895:1-57 6095 0 0.0 0.0 0.0 0.0 - pushTo EVM src/EVM.hs:1582:1-23 6096 640 0.0 0.0 0.0 0.0 - makeUnique EVM src/EVM.hs:(1592,1)-(1602,18) 5950 640 0.0 0.0 0.4 0.2 - num EVM.Types src/EVM/Types.hs:492:1-18 5993 1280 0.1 0.0 0.1 0.0 - accessAndBurn EVM src/EVM.hs:(1901,1)-(1905,16) 5990 640 0.0 0.0 0.3 0.1 - accessAccountForGas EVM src/EVM.hs:(1910,1)-(1914,17) 5992 640 0.1 0.0 0.1 0.0 - burn EVM src/EVM.hs:(1826,1)-(1838,38) 5994 640 0.1 0.0 0.2 0.1 - num EVM.Types src/EVM/Types.hs:492:1-18 5995 640 0.0 0.0 0.0 0.0 - fetchAccount EVM src/EVM.hs:(1639,1)-(1659,23) 5997 0 0.1 0.0 0.1 0.1 - bytecode EVM src/EVM.hs:(415,1)-(417,29) 6009 640 0.0 0.0 0.0 0.0 - len EVM.Symbolic src/EVM/Symbolic.hs:(161,1)-(162,38) 6008 640 0.0 0.0 0.0 0.0 - num EVM.Types src/EVM/Types.hs:492:1-18 6007 640 0.0 0.0 0.0 0.0 - push EVM src/EVM.hs:2474:1-30 5998 0 0.0 0.0 0.1 0.0 - pushSym EVM src/EVM.hs:2477:1-34 5999 640 0.1 0.0 0.1 0.0 - w256lit EVM.Types src/EVM/Types.hs:346:1-48 6000 640 0.0 0.0 0.0 0.0 - genLiteral Data.SBV.Core.Model Data/SBV/Core/Model.hs:99:1-48 6001 640 0.0 0.0 0.0 0.0 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 6002 640 0.0 0.0 0.0 0.0 - svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 6003 640 0.0 0.0 0.0 0.0 - svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 6004 640 0.0 0.0 0.0 0.0 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 6005 640 0.0 0.0 0.0 0.0 - num EVM.Types src/EVM/Types.hs:492:1-18 6006 0 0.0 0.0 0.0 0.0 - fetchAccount EVM src/EVM.hs:(1639,1)-(1659,23) 5996 640 0.0 0.0 0.0 0.0 - maybeLitWord EVM.Types src/EVM/Types.hs:324:1-68 5951 640 0.0 0.0 0.0 0.0 - genFromCV Data.SBV.Core.Model Data/SBV/Core/Model.hs:(103,1)-(104,95) 5953 640 0.0 0.0 0.0 0.0 - svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 5954 640 0.0 0.0 0.0 0.0 - svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 5955 640 0.0 0.0 0.0 0.0 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 5956 640 0.0 0.0 0.0 0.0 - sFromIntegral Data.SBV.Core.Model Data/SBV/Core/Model.hs:(1428,1)-(1441,70) 6027 640 0.1 0.0 0.2 0.0 - genFromCV Data.SBV.Core.Model Data/SBV/Core/Model.hs:(103,1)-(104,95) 6042 640 0.0 0.0 0.1 0.0 - svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 6043 640 0.0 0.0 0.0 0.0 - svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 6044 640 0.0 0.0 0.1 0.0 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 6045 640 0.1 0.0 0.1 0.0 - genLiteral Data.SBV.Core.Model Data/SBV/Core/Model.hs:99:1-48 6029 640 0.0 0.0 0.0 0.0 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 6038 640 0.0 0.0 0.0 0.0 - svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 6039 640 0.0 0.0 0.0 0.0 - svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 6040 640 0.0 0.0 0.1 0.0 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 6041 640 0.1 0.0 0.1 0.0 - forceConcrete3 EVM src/EVM.hs:(1856,1)-(1858,36) 6332 1 0.0 0.0 0.0 0.0 - maybeLitWord EVM.Types src/EVM/Types.hs:324:1-68 6333 3 0.0 0.0 0.0 0.0 - genFromCV Data.SBV.Core.Model Data/SBV/Core/Model.hs:(103,1)-(104,95) 6335 3 0.0 0.0 0.0 0.0 - svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 6336 3 0.0 0.0 0.0 0.0 - svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 6337 3 0.0 0.0 0.0 0.0 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 6338 3 0.0 0.0 0.0 0.0 - burn EVM src/EVM.hs:(1826,1)-(1838,38) 6340 2 0.0 0.0 0.0 0.0 - num EVM.Types src/EVM/Types.hs:492:1-18 6341 2 0.0 0.0 0.0 0.0 - accessUnboundedMemoryRange EVM src/EVM.hs:(2368,1)-(2375,14) 6343 0 0.0 0.0 0.0 0.0 - memoryCost EVM src/EVM.hs:(2824,1)-(2830,30) 6347 2 0.0 0.0 0.0 0.0 - ceilDiv EVM src/EVM.hs:2835:1-31 6348 2 0.0 0.0 0.0 0.0 - ceilDiv EVM src/EVM.hs:2835:1-31 6346 1 0.0 0.0 0.0 0.0 - num EVM.Types src/EVM/Types.hs:492:1-18 6344 1 0.0 0.0 0.0 0.0 - copyBytesToMemory EVM src/EVM.hs:(2395,1)-(2400,45) 6350 0 0.0 0.0 0.0 0.0 - writeMemory EVM.Symbolic src/EVM/Symbolic.hs:(173,1)-(180,49) 6351 1 0.0 0.0 0.0 0.0 - writeMemory EVM.Concrete src/EVM/Concrete.hs:(46,1)-(59,22) 6353 1 0.0 0.0 0.0 0.0 - num EVM.Types src/EVM/Types.hs:492:1-18 6354 4 0.0 0.0 0.0 0.0 - sliceMemory EVM.Concrete src/EVM/Concrete.hs:(42,1)-(43,50) 6355 1 0.0 0.0 0.0 0.0 - num EVM.Types src/EVM/Types.hs:492:1-18 6356 2 0.0 0.0 0.0 0.0 - byteStringSliceWithDefaultZeroes EVM.Concrete src/EVM/Concrete.hs:(27,1)-(35,51) 6357 1 0.0 0.0 0.0 0.0 - accessUnboundedMemoryRange EVM src/EVM.hs:(2368,1)-(2375,14) 6342 1 0.0 0.0 0.0 0.0 - num EVM.Types src/EVM/Types.hs:492:1-18 6345 2 0.0 0.0 0.0 0.0 - ceilDiv EVM src/EVM.hs:2835:1-31 6339 1 0.0 0.0 0.0 0.0 - copyBytesToMemory EVM src/EVM.hs:(2395,1)-(2400,45) 6349 1 0.0 0.0 0.0 0.0 - num EVM.Types src/EVM/Types.hs:492:1-18 6334 1 0.0 0.0 0.0 0.0 - finishFrame EVM src/EVM.hs:(2237,1)-(2357,20) 5715 0 0.0 0.0 0.3 0.1 - copyCallBytesToMemory EVM src/EVM.hs:(2404,1)-(2409,66) 6267 291 0.0 0.0 0.0 0.0 - noop EVM src/EVM.hs:1579:1-14 6269 291 0.0 0.0 0.0 0.0 - insertTrace EVM src/EVM.hs:(2444,1)-(2447,60) 6259 291 0.0 0.0 0.0 0.0 - insert Data.Tree.Zipper Data/Tree/Zipper.hs:275:1-37 6274 291 0.0 0.0 0.0 0.0 - nextSpace Data.Tree.Zipper Data/Tree/Zipper.hs:153:1-69 6273 291 0.0 0.0 0.0 0.0 - withTraceLocation EVM src/EVM.hs:(2426,1)-(2435,5) 6260 291 0.0 0.0 0.0 0.0 - num EVM.Types src/EVM/Types.hs:492:1-18 6266 291 0.0 0.0 0.0 0.0 - finalize EVM src/EVM.hs:(1721,1)-(1790,66) 5716 0 0.1 0.1 0.3 0.1 - accountEmpty EVM src/EVM.hs:(1712,1)-(1717,26) 5722 1616 0.1 0.0 0.1 0.0 - len EVM.Symbolic src/EVM/Symbolic.hs:(161,1)-(162,38) 5723 1616 0.0 0.0 0.0 0.0 - num EVM.Types src/EVM/Types.hs:492:1-18 5720 808 0.1 0.0 0.1 0.0 - noop EVM src/EVM.hs:1579:1-14 5721 404 0.0 0.0 0.0 0.0 - r_block EVM.FeeSchedule src/EVM/FeeSchedule.hs:47:5-11 5724 404 0.0 0.0 0.0 0.0 - w256 EVM.Types src/EVM/Types.hs:90:1-24 5719 404 0.0 0.0 0.0 0.0 - touchAccount EVM src/EVM.hs:1895:1-57 5717 0 0.0 0.0 0.1 0.0 - pushTo EVM src/EVM.hs:1582:1-23 5718 404 0.1 0.0 0.1 0.0 - popTrace EVM src/EVM.hs:(2450,1)-(2454,42) 6272 0 0.0 0.0 0.0 0.0 - nextSpace Data.Tree.Zipper Data/Tree/Zipper.hs:153:1-69 6277 291 0.0 0.0 0.0 0.0 - parent Data.Tree.Zipper Data/Tree/Zipper.hs:(124,1)-(132,17) 6275 291 0.0 0.0 0.0 0.0 - parents Data.Tree.Zipper Data/Tree/Zipper.hs:71:1-26 6276 291 0.0 0.0 0.0 0.0 - push EVM src/EVM.hs:2474:1-30 6270 0 0.0 0.0 0.0 0.0 - pushSym EVM src/EVM.hs:2477:1-34 6271 291 0.0 0.0 0.0 0.0 - w256lit EVM.Types src/EVM/Types.hs:346:1-48 6278 291 0.0 0.0 0.0 0.0 - genLiteral Data.SBV.Core.Model Data/SBV/Core/Model.hs:99:1-48 6279 291 0.0 0.0 0.0 0.0 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 6280 291 0.0 0.0 0.0 0.0 - svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 6281 291 0.0 0.0 0.0 0.0 - svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 6282 291 0.0 0.0 0.0 0.0 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 6283 291 0.0 0.0 0.0 0.0 - num EVM.Types src/EVM/Types.hs:492:1-18 6284 0 0.0 0.0 0.0 0.0 - litWord EVM.Symbolic src/EVM/Symbolic.hs:24:1-52 6100 0 0.0 0.0 0.0 0.0 - genLiteral Data.SBV.Core.Model Data/SBV/Core/Model.hs:99:1-48 6101 292 0.0 0.0 0.0 0.0 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 6102 292 0.0 0.0 0.0 0.0 - word EVM.Types src/EVM/Types.hs:521:1-21 5373 0 0.1 0.0 1.2 2.7 - word256 EVM.Types src/EVM/Types.hs:(510,1)-(518,67) 5375 85334 0.5 0.3 1.1 2.7 - padLeft EVM.Types src/EVM/Types.hs:495:1-54 5376 85334 0.4 0.9 0.4 0.9 - bytesRead Data.Serialize.Get src/Data/Serialize/Get.hs:838:1-45 5377 0 0.3 1.5 0.3 1.5 - runUnitTest EVM.UnitTest src/EVM/UnitTest.hs:(178,1)-(180,26) 5316 0 0.0 0.0 0.2 0.1 - execTest EVM.UnitTest src/EVM/UnitTest.hs:(183,1)-(192,19) 5317 0 0.0 0.0 0.2 0.1 - abiCall EVM.UnitTest src/EVM/UnitTest.hs:(842,1)-(845,53) 5321 0 0.0 0.0 0.1 0.1 - makeTxCall EVM.UnitTest src/EVM/UnitTest.hs:(848,1)-(859,17) 5322 0 0.0 0.0 0.1 0.1 - w256 EVM.Types src/EVM/Types.hs:90:1-24 5329 810 0.0 0.0 0.0 0.0 - initTx EVM.Transaction src/EVM/Transaction.hs:(182,1)-(205,47) 5339 405 0.0 0.0 0.1 0.1 - forceLit EVM.Symbolic src/EVM/Symbolic.hs:(40,1)-(42,49) 5420 809 0.0 0.0 0.1 0.0 - genFromCV Data.SBV.Core.Model Data/SBV/Core/Model.hs:(103,1)-(104,95) 5742 651 0.0 0.0 0.1 0.0 - svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 5743 651 0.0 0.0 0.0 0.0 - svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 5744 651 0.0 0.0 0.1 0.0 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 5745 651 0.1 0.0 0.1 0.0 - maybeLitWord EVM.Types src/EVM/Types.hs:324:1-68 5343 405 0.0 0.0 0.0 0.0 - setupTx EVM.Transaction src/EVM/Transaction.hs:(171,1)-(176,38) 5340 405 0.1 0.0 0.1 0.0 - touchAccount EVM.Transaction src/EVM/Transaction.hs:164:1-57 5341 810 0.0 0.0 0.0 0.0 - touchAccount EVM.Transaction src/EVM/Transaction.hs:164:1-57 5342 405 0.0 0.0 0.0 0.0 - loadContract EVM src/EVM.hs:(1794,1)-(1806,44) 5324 0 0.0 0.0 0.0 0.0 - resetState EVM src/EVM.hs:(2210,1)-(2213,26) 5325 0 0.0 0.0 0.0 0.0 - pushTrace EVM src/EVM.hs:(2438,1)-(2441,59) 5331 0 0.1 0.0 0.1 0.0 - children Data.Tree.Zipper Data/Tree/Zipper.hs:(166,1)-(172,7) 5344 405 0.0 0.0 0.0 0.0 - view Control.Monad.Operational src/Control/Monad/Operational.hs:138:1-26 5311 0 0.0 0.0 1.1 0.8 - viewT Control.Monad.Operational src/Control/Monad/Operational.hs:(239,1)-(243,54) 5312 4858 0.0 0.0 1.1 0.8 - execFully EVM.Stepper src/EVM/Stepper.hs:(82,1)-(91,20) 5725 0 0.0 0.0 0.0 0.0 - execTest EVM.UnitTest src/EVM/UnitTest.hs:(183,1)-(192,19) 5727 0 0.0 0.0 0.0 0.0 - pushTrace EVM src/EVM.hs:(2438,1)-(2441,59) 6359 1 0.0 0.0 0.0 0.0 - children Data.Tree.Zipper Data/Tree/Zipper.hs:(166,1)-(172,7) 6424 1 0.0 0.0 0.0 0.0 - withTraceLocation EVM src/EVM.hs:(2426,1)-(2435,5) 6360 1 0.0 0.0 0.0 0.0 - evm EVM.Stepper src/EVM/Stepper.hs:78:1-21 6358 0 0.0 0.0 0.0 0.0 - runUnitTest EVM.UnitTest src/EVM/UnitTest.hs:(178,1)-(180,26) 5333 0 0.0 0.0 1.1 0.8 - checkFailures EVM.UnitTest src/EVM/UnitTest.hs:(195,1)-(210,58) 5728 405 0.1 0.0 1.1 0.8 - abiCall EVM.UnitTest src/EVM/UnitTest.hs:(842,1)-(845,53) 5730 404 0.0 0.0 1.0 0.7 - abiMethod EVM.ABI src/EVM/ABI.hs:(370,1)-(372,13) 5758 404 0.1 0.1 0.8 0.6 - abiKeccak EVM.Types src/EVM/Types.hs:(586,1)-(590,14) 5759 0 0.0 0.0 0.7 0.5 - word32 EVM.Types src/EVM/Types.hs:(576,1)-(577,52) 5787 404 0.0 0.0 0.0 0.0 - keccakBytes EVM.Types src/EVM/Types.hs:(570,1)-(573,15) 5760 0 0.0 0.0 0.7 0.5 - hash Crypto.Hash Crypto/Hash.hs:58:1-47 5761 404 0.0 0.0 0.2 0.0 - hashFinalize Crypto.Hash Crypto/Hash.hs:(92,1)-(95,17) 5762 404 0.0 0.0 0.1 0.0 - allocAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:74:1-45 5771 404 0.1 0.0 0.1 0.0 - new Basement.Block.Base Basement/Block/Base.hs:304:1-76 5772 404 0.0 0.0 0.0 0.0 - unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 5773 404 0.0 0.0 0.0 0.0 - withMutablePtrHint Basement.Block.Base Basement/Block/Base.hs:(475,1)-(489,39) 5774 404 0.0 0.0 0.0 0.0 - copy Data.ByteArray.Methods Data/ByteArray/Methods.hs:(223,1)-(226,21) 5779 404 0.0 0.0 0.0 0.0 - isMutablePinned Basement.Block.Base Basement/Block/Base.hs:100:1-90 5775 404 0.0 0.0 0.0 0.0 - compatIsMutableByteArrayPinned# Basement.Compat.Primitive Basement/Compat/Primitive.hs:70:1-65 5776 404 0.0 0.0 0.0 0.0 - toPinnedStatus# Basement.Compat.Primitive Basement/Compat/Primitive.hs:(47,1)-(48,27) 5777 404 0.0 0.0 0.0 0.0 - unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 5778 404 0.0 0.0 0.0 0.0 - hashInit Crypto.Hash Crypto/Hash.hs:(66,1)-(67,24) 5769 404 0.0 0.0 0.1 0.0 - allocAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:74:1-45 5770 404 0.1 0.0 0.1 0.0 - hashUpdate Crypto.Hash Crypto/Hash.hs:(71,1)-(73,37) 5763 404 0.0 0.0 0.1 0.0 - hashUpdates Crypto.Hash Crypto/Hash.hs:(81,1)-(86,32) 5766 404 0.0 0.0 0.1 0.0 - copyAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:(237,1)-(240,21) 5768 404 0.1 0.0 0.1 0.0 - null Data.ByteArray.Methods Data/ByteArray/Methods.hs:92:1-22 5767 404 0.0 0.0 0.0 0.0 - null Data.ByteArray.Methods Data/ByteArray/Methods.hs:92:1-22 5764 404 0.0 0.0 0.0 0.0 - unpack Data.ByteArray.Methods Data/ByteArray/Methods.hs:(104,1)-(110,34) 5780 404 0.2 0.1 0.5 0.5 - unsafeCast Basement.Block Basement/Block.hs:421:1-32 5781 13332 0.0 0.0 0.0 0.0 - withPtr Basement.Block.Base Basement/Block/Base.hs:(402,1)-(411,31) 5782 12928 0.3 0.3 0.3 0.4 - isPinned Basement.Block.Base Basement/Block/Base.hs:97:1-67 5783 12928 0.0 0.0 0.0 0.0 - compatIsByteArrayPinned# Basement.Compat.Primitive Basement/Compat/Primitive.hs:67:1-51 5784 12928 0.0 0.0 0.0 0.0 - toPinnedStatus# Basement.Compat.Primitive Basement/Compat/Primitive.hs:(47,1)-(48,27) 5785 12928 0.0 0.0 0.0 0.0 - unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 5786 12928 0.0 0.0 0.0 0.0 - putAbi EVM.ABI src/EVM/ABI.hs:(262,1)-(291,15) 5788 0 0.1 0.0 0.1 0.0 - sElems Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:121:30-35 5790 808 0.0 0.0 0.0 0.0 - unId Data.Vector.Fusion.Util Data/Vector/Fusion/Util.hs:25:21-24 5789 808 0.0 0.0 0.0 0.0 - litWord EVM.Symbolic src/EVM/Symbolic.hs:24:1-52 5752 404 0.0 0.0 0.0 0.0 - genLiteral Data.SBV.Core.Model Data/SBV/Core/Model.hs:99:1-48 5753 404 0.0 0.0 0.0 0.0 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 5754 404 0.0 0.0 0.0 0.0 - svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 5755 404 0.0 0.0 0.0 0.0 - svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 5756 404 0.0 0.0 0.0 0.0 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 5757 404 0.0 0.0 0.0 0.0 - makeTxCall EVM.UnitTest src/EVM/UnitTest.hs:(848,1)-(859,17) 5732 404 0.1 0.0 0.3 0.1 - w256 EVM.Types src/EVM/Types.hs:90:1-24 5741 1212 0.0 0.0 0.0 0.0 - initTx EVM.Transaction src/EVM/Transaction.hs:(182,1)-(205,47) 5746 404 0.2 0.0 0.2 0.0 - forceLit EVM.Symbolic src/EVM/Symbolic.hs:(40,1)-(42,49) 5751 808 0.0 0.0 0.0 0.0 - maybeLitWord EVM.Types src/EVM/Types.hs:324:1-68 5750 404 0.0 0.0 0.0 0.0 - setupTx EVM.Transaction src/EVM/Transaction.hs:(171,1)-(176,38) 5747 404 0.0 0.0 0.1 0.0 - touchAccount EVM.Transaction src/EVM/Transaction.hs:164:1-57 5748 808 0.1 0.0 0.1 0.0 - touchAccount EVM.Transaction src/EVM/Transaction.hs:164:1-57 5749 404 0.0 0.0 0.0 0.0 - loadContract EVM src/EVM.hs:(1794,1)-(1806,44) 5733 404 0.0 0.0 0.0 0.0 - litAddr EVM.Symbolic src/EVM/Symbolic.hs:27:1-36 5739 0 0.0 0.0 0.0 0.0 - genLiteral Data.SBV.Core.Model Data/SBV/Core/Model.hs:99:1-48 5740 404 0.0 0.0 0.0 0.0 - resetState EVM src/EVM.hs:(2210,1)-(2213,26) 5734 0 0.0 0.0 0.0 0.0 - num EVM.Types src/EVM/Types.hs:492:1-18 5731 404 0.0 0.0 0.0 0.0 - decodeAbiValue EVM.ABI src/EVM/ABI.hs:364:1-32 5889 0 0.0 0.0 0.0 0.1 - getAbi EVM.ABI src/EVM/ABI.hs:(226,1)-(259,66) 5890 404 0.0 0.0 0.0 0.0 - evm EVM.Stepper src/EVM/Stepper.hs:78:1-21 5729 0 0.0 0.0 0.0 0.0 - popTrace EVM src/EVM.hs:(2450,1)-(2454,42) 5735 0 0.0 0.0 0.0 0.0 - nextSpace Data.Tree.Zipper Data/Tree/Zipper.hs:153:1-69 5738 404 0.0 0.0 0.0 0.0 - parent Data.Tree.Zipper Data/Tree/Zipper.hs:(124,1)-(132,17) 5736 404 0.0 0.0 0.0 0.0 - parents Data.Tree.Zipper Data/Tree/Zipper.hs:71:1-26 5737 404 0.0 0.0 0.0 0.0 - _contractcode EVM src/EVM.hs:331:5-17 5477 405 0.0 0.0 0.0 0.0 - currentContract EVM src/EVM.hs:(443,1)-(444,65) 5475 405 0.0 0.0 0.0 0.0 - dapp EVM.UnitTest src/EVM/UnitTest.hs:87:5-8 5479 405 0.0 0.0 0.0 0.0 - generate Test.QuickCheck.Gen Test/QuickCheck/Gen.hs:(139,1)-(141,20) 5302 405 0.0 0.0 3.2 4.6 - genWithCorpus EVM.UnitTest src/EVM/UnitTest.hs:(217,1)-(224,7) 5472 405 0.0 0.0 3.2 4.6 - mutations EVM.UnitTest src/EVM/UnitTest.hs:89:5-13 5899 800 0.0 0.0 0.0 0.0 - marray# Data.Primitive.Array Data/Primitive/Array.hs:92:5-11 5590 649 0.0 0.0 0.0 0.0 - unId Data.Vector.Fusion.Util Data/Vector/Fusion/Util.hs:25:21-24 5589 649 0.0 0.0 0.0 0.0 - frequency Test.QuickCheck.Gen Test/QuickCheck/Gen.hs:(191,1)-(204,58) 5898 593 0.1 0.0 0.7 0.4 - choose Test.QuickCheck.Gen Test/QuickCheck/Gen.hs:130:1-59 5902 593 0.2 0.0 0.2 0.0 - nextInt System.Random.SplitMix src/System/Random/SplitMix.hs:(160,1)-(164,39) 5903 400 0.0 0.0 0.0 0.0 - nextWord64 System.Random.SplitMix src/System/Random/SplitMix.hs:(128,1)-(130,29) 5904 400 0.0 0.0 0.0 0.0 - splitSMGen System.Random.SplitMix src/System/Random/SplitMix.hs:(232,1)-(236,31) 5901 587 0.0 0.0 0.0 0.0 - mutateAbiValue EVM.Mutate src/EVM/Mutate.hs:(21,1)-(37,86) 5911 567 0.1 0.0 0.2 0.0 - unId Data.Vector.Fusion.Util Data/Vector/Fusion/Util.hs:25:21-24 5912 1134 0.0 0.0 0.0 0.0 - splitSMGen System.Random.SplitMix src/System/Random/SplitMix.hs:(232,1)-(236,31) 5917 573 0.0 0.0 0.0 0.0 - marray# Data.Primitive.Array Data/Primitive/Array.hs:92:5-11 5918 567 0.0 0.0 0.0 0.0 - array# Data.Primitive.Array Data/Primitive/Array.hs:87:5-10 5916 380 0.0 0.0 0.0 0.0 - sChunks Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:122:30-36 5915 187 0.0 0.0 0.0 0.0 - sSize Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:124:30-34 5914 187 0.0 0.0 0.0 0.0 - upperBound Data.Vector.Fusion.Bundle.Size Data/Vector/Fusion/Bundle/Size.hs:(126,1)-(128,30) 5913 187 0.0 0.0 0.0 0.0 - fixAbiUInt EVM.Mutate src/EVM/Mutate.hs:112:1-50 6330 16 0.0 0.0 0.0 0.0 - mutateNum EVM.Mutate src/EVM/Mutate.hs:108:1-92 6324 16 0.0 0.0 0.1 0.0 - choose Test.QuickCheck.Gen Test/QuickCheck/Gen.hs:130:1-59 6327 16 0.1 0.0 0.1 0.0 - nextInt System.Random.SplitMix src/System/Random/SplitMix.hs:(160,1)-(164,39) 6328 81 0.0 0.0 0.0 0.0 - nextWord64 System.Random.SplitMix src/System/Random/SplitMix.hs:(128,1)-(130,29) 6329 81 0.0 0.0 0.0 0.0 - splitSMGen System.Random.SplitMix src/System/Random/SplitMix.hs:(232,1)-(236,31) 6325 16 0.0 0.0 0.0 0.0 - choose Test.QuickCheck.Gen Test/QuickCheck/Gen.hs:130:1-59 6321 0 0.1 0.0 0.1 0.0 - nextInt System.Random.SplitMix src/System/Random/SplitMix.hs:(160,1)-(164,39) 6322 193 0.0 0.0 0.0 0.0 - nextWord64 System.Random.SplitMix src/System/Random/SplitMix.hs:(128,1)-(130,29) 6323 193 0.0 0.0 0.0 0.0 - elements Test.QuickCheck.Gen Test/QuickCheck/Gen.hs:(208,1)-(209,54) 5906 0 0.0 0.0 0.0 0.0 - choose Test.QuickCheck.Gen Test/QuickCheck/Gen.hs:130:1-59 5908 0 0.0 0.0 0.0 0.0 - nextInt System.Random.SplitMix src/System/Random/SplitMix.hs:(160,1)-(164,39) 5909 187 0.0 0.0 0.0 0.0 - nextWord64 System.Random.SplitMix src/System/Random/SplitMix.hs:(128,1)-(130,29) 5910 187 0.0 0.0 0.0 0.0 - genAbiValue EVM.ABI src/EVM/ABI.hs:(440,1)-(466,62) 5919 0 0.0 0.0 0.4 0.3 - splitSMGen System.Random.SplitMix src/System/Random/SplitMix.hs:(232,1)-(236,31) 5920 2319 0.0 0.0 0.0 0.0 - unId Data.Vector.Fusion.Util Data/Vector/Fusion/Util.hs:25:21-24 5924 1053 0.0 0.0 0.0 0.0 - marray# Data.Primitive.Array Data/Primitive/Array.hs:92:5-11 5925 633 0.0 0.0 0.0 0.0 - sSize Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:124:30-34 5922 426 0.0 0.0 0.0 0.0 - sChunks Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:122:30-36 5923 213 0.0 0.0 0.0 0.0 - upperBound Data.Vector.Fusion.Bundle.Size Data/Vector/Fusion/Bundle/Size.hs:(126,1)-(128,30) 5921 213 0.0 0.0 0.0 0.0 - array# Data.Primitive.Array Data/Primitive/Array.hs:87:5-10 5942 207 0.0 0.0 0.0 0.0 - sized Test.QuickCheck.Gen Test/QuickCheck/Gen.hs:99:1-52 5926 207 0.3 0.3 0.4 0.3 - splitSMGen System.Random.SplitMix src/System/Random/SplitMix.hs:(232,1)-(236,31) 5927 840 0.1 0.0 0.1 0.0 - choose Test.QuickCheck.Gen Test/QuickCheck/Gen.hs:130:1-59 5932 420 0.0 0.0 0.0 0.0 - nextInt System.Random.SplitMix src/System/Random/SplitMix.hs:(160,1)-(164,39) 5933 828 0.0 0.0 0.0 0.0 - nextWord64 System.Random.SplitMix src/System/Random/SplitMix.hs:(128,1)-(130,29) 5934 828 0.0 0.0 0.0 0.0 - elements Test.QuickCheck.Gen Test/QuickCheck/Gen.hs:(208,1)-(209,54) 5928 420 0.1 0.0 0.1 0.0 - choose Test.QuickCheck.Gen Test/QuickCheck/Gen.hs:130:1-59 5929 420 0.0 0.0 0.0 0.0 - nextInt System.Random.SplitMix src/System/Random/SplitMix.hs:(160,1)-(164,39) 5930 420 0.0 0.0 0.0 0.0 - nextWord64 System.Random.SplitMix src/System/Random/SplitMix.hs:(128,1)-(130,29) 5931 420 0.0 0.0 0.0 0.0 - hashCall EVM.UnitTest src/EVM/UnitTest.hs:(244,1)-(245,127) 5473 405 2.3 4.2 2.4 4.2 - _creationCodehash EVM.Solidity src/EVM/Solidity.hs:139:5-21 5582 405 0.0 0.0 0.0 0.0 - _runtimeCodehash EVM.Solidity src/EVM/Solidity.hs:138:5-20 5474 405 0.0 0.0 0.0 0.0 - xxhash EVM.UnitTest src/EVM/UnitTest.hs:213:1-26 5583 405 0.1 0.0 0.1 0.0 - sChunks Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:122:30-36 5588 218 0.0 0.0 0.0 0.0 - sSize Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:124:30-34 5587 218 0.0 0.0 0.0 0.0 - upperBound Data.Vector.Fusion.Bundle.Size Data/Vector/Fusion/Bundle/Size.hs:(126,1)-(128,30) 5586 218 0.0 0.0 0.0 0.0 - elements Test.QuickCheck.Gen Test/QuickCheck/Gen.hs:(208,1)-(209,54) 5905 187 0.0 0.0 0.0 0.0 - choose Test.QuickCheck.Gen Test/QuickCheck/Gen.hs:130:1-59 5907 187 0.0 0.0 0.0 0.0 - genAbiValue EVM.ABI src/EVM/ABI.hs:(440,1)-(466,62) 5585 0 0.1 0.0 0.1 0.0 - unId Data.Vector.Fusion.Util Data/Vector/Fusion/Util.hs:25:21-24 5596 245 0.0 0.0 0.0 0.0 - array# Data.Primitive.Array Data/Primitive/Array.hs:87:5-10 5597 224 0.0 0.0 0.0 0.0 - sElems Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:121:30-35 5595 218 0.0 0.0 0.0 0.0 - splitSMGen System.Random.SplitMix src/System/Random/SplitMix.hs:(232,1)-(236,31) 5591 59 0.0 0.0 0.0 0.0 - marray# Data.Primitive.Array Data/Primitive/Array.hs:92:5-11 5598 16 0.0 0.0 0.0 0.0 - sSize Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:124:30-34 5593 10 0.0 0.0 0.0 0.0 - sized Test.QuickCheck.Gen Test/QuickCheck/Gen.hs:99:1-52 5621 6 0.0 0.0 0.0 0.0 - splitSMGen System.Random.SplitMix src/System/Random/SplitMix.hs:(232,1)-(236,31) 5622 22 0.0 0.0 0.0 0.0 - choose Test.QuickCheck.Gen Test/QuickCheck/Gen.hs:130:1-59 5627 11 0.0 0.0 0.0 0.0 - nextInt System.Random.SplitMix src/System/Random/SplitMix.hs:(160,1)-(164,39) 5628 23 0.0 0.0 0.0 0.0 - nextWord64 System.Random.SplitMix src/System/Random/SplitMix.hs:(128,1)-(130,29) 5629 23 0.0 0.0 0.0 0.0 - elements Test.QuickCheck.Gen Test/QuickCheck/Gen.hs:(208,1)-(209,54) 5623 11 0.0 0.0 0.0 0.0 - choose Test.QuickCheck.Gen Test/QuickCheck/Gen.hs:130:1-59 5624 11 0.0 0.0 0.0 0.0 - nextInt System.Random.SplitMix src/System/Random/SplitMix.hs:(160,1)-(164,39) 5625 11 0.0 0.0 0.0 0.0 - nextWord64 System.Random.SplitMix src/System/Random/SplitMix.hs:(128,1)-(130,29) 5626 11 0.0 0.0 0.0 0.0 - sChunks Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:122:30-36 5594 5 0.0 0.0 0.0 0.0 - upperBound Data.Vector.Fusion.Bundle.Size Data/Vector/Fusion/Bundle/Size.hs:(126,1)-(128,30) 5592 5 0.0 0.0 0.0 0.0 - newQCGen Test.QuickCheck.Random Test/QuickCheck/Random.hs:42:1-30 5304 0 0.0 0.0 0.0 0.0 - newSMGen System.Random.SplitMix src/System/Random/SplitMix.hs:382:1-48 5306 0 0.0 0.0 0.0 0.0 - splitSMGen System.Random.SplitMix src/System/Random/SplitMix.hs:(232,1)-(236,31) 5309 405 0.0 0.0 0.0 0.0 - lookupCode EVM.Dapp src/EVM/Dapp.hs:(178,1)-(185,73) 5478 405 0.0 0.0 2.5 0.5 - stripBytecodeMetadata EVM.Solidity src/EVM/Solidity.hs:(569,1)-(573,22) 5487 405 1.8 0.0 1.8 0.0 - keccak EVM.Types src/EVM/Types.hs:(580,1)-(583,12) 5480 0 0.0 0.0 0.7 0.5 - keccakBytes EVM.Types src/EVM/Types.hs:(570,1)-(573,15) 5482 0 0.0 0.0 0.6 0.5 - hash Crypto.Hash Crypto/Hash.hs:58:1-47 5483 405 0.0 0.0 0.1 0.0 - hashFinalize Crypto.Hash Crypto/Hash.hs:(92,1)-(95,17) 5484 405 0.0 0.0 0.0 0.0 - allocAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:74:1-45 5493 405 0.0 0.0 0.0 0.0 - new Basement.Block.Base Basement/Block/Base.hs:304:1-76 5494 405 0.0 0.0 0.0 0.0 - unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 5495 405 0.0 0.0 0.0 0.0 - withMutablePtrHint Basement.Block.Base Basement/Block/Base.hs:(475,1)-(489,39) 5496 405 0.0 0.0 0.0 0.0 - copy Data.ByteArray.Methods Data/ByteArray/Methods.hs:(223,1)-(226,21) 5501 405 0.0 0.0 0.0 0.0 - isMutablePinned Basement.Block.Base Basement/Block/Base.hs:100:1-90 5497 405 0.0 0.0 0.0 0.0 - compatIsMutableByteArrayPinned# Basement.Compat.Primitive Basement/Compat/Primitive.hs:70:1-65 5498 405 0.0 0.0 0.0 0.0 - toPinnedStatus# Basement.Compat.Primitive Basement/Compat/Primitive.hs:(47,1)-(48,27) 5499 405 0.0 0.0 0.0 0.0 - unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 5500 405 0.0 0.0 0.0 0.0 - hashInit Crypto.Hash Crypto/Hash.hs:(66,1)-(67,24) 5491 405 0.0 0.0 0.0 0.0 - allocAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:74:1-45 5492 405 0.0 0.0 0.0 0.0 - hashUpdate Crypto.Hash Crypto/Hash.hs:(71,1)-(73,37) 5485 405 0.0 0.0 0.1 0.0 - hashUpdates Crypto.Hash Crypto/Hash.hs:(81,1)-(86,32) 5488 405 0.0 0.0 0.1 0.0 - copyAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:(237,1)-(240,21) 5490 405 0.1 0.0 0.1 0.0 - null Data.ByteArray.Methods Data/ByteArray/Methods.hs:92:1-22 5489 405 0.0 0.0 0.0 0.0 - null Data.ByteArray.Methods Data/ByteArray/Methods.hs:92:1-22 5486 405 0.0 0.0 0.0 0.0 - unpack Data.ByteArray.Methods Data/ByteArray/Methods.hs:(104,1)-(110,34) 5502 405 0.1 0.1 0.5 0.5 - unsafeCast Basement.Block Basement/Block.hs:421:1-32 5503 13365 0.0 0.0 0.0 0.0 - withPtr Basement.Block.Base Basement/Block/Base.hs:(402,1)-(411,31) 5504 12960 0.5 0.3 0.5 0.4 - isPinned Basement.Block.Base Basement/Block/Base.hs:97:1-67 5505 12960 0.0 0.0 0.0 0.0 - compatIsByteArrayPinned# Basement.Compat.Primitive Basement/Compat/Primitive.hs:67:1-51 5506 12960 0.0 0.0 0.0 0.0 - toPinnedStatus# Basement.Compat.Primitive Basement/Compat/Primitive.hs:(47,1)-(48,27) 5507 12960 0.0 0.0 0.0 0.0 - unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 5508 12960 0.0 0.0 0.0 0.0 - word EVM.Types src/EVM/Types.hs:521:1-21 5481 0 0.0 0.0 0.1 0.0 - word256 EVM.Types src/EVM/Types.hs:(510,1)-(518,67) 5509 405 0.1 0.0 0.1 0.0 - padLeft EVM.Types src/EVM/Types.hs:495:1-54 5510 405 0.0 0.0 0.0 0.0 - bytesRead Data.Serialize.Get src/Data/Serialize/Get.hs:838:1-45 5511 0 0.1 0.0 0.1 0.0 - runUnitTest EVM.UnitTest src/EVM/UnitTest.hs:(178,1)-(180,26) 5313 405 0.0 0.0 0.7 0.8 - execTest EVM.UnitTest src/EVM/UnitTest.hs:(183,1)-(192,19) 5314 405 0.0 0.0 0.7 0.8 - abiCall EVM.UnitTest src/EVM/UnitTest.hs:(842,1)-(845,53) 5318 405 0.0 0.0 0.7 0.8 - abiMethod EVM.ABI src/EVM/ABI.hs:(370,1)-(372,13) 5442 405 0.0 0.1 0.7 0.7 - abiKeccak EVM.Types src/EVM/Types.hs:(586,1)-(590,14) 5443 0 0.0 0.0 0.6 0.5 - word32 EVM.Types src/EVM/Types.hs:(576,1)-(577,52) 5470 405 0.0 0.0 0.0 0.0 - keccakBytes EVM.Types src/EVM/Types.hs:(570,1)-(573,15) 5444 0 0.1 0.0 0.6 0.5 - hash Crypto.Hash Crypto/Hash.hs:58:1-47 5445 405 0.0 0.0 0.2 0.0 - hashFinalize Crypto.Hash Crypto/Hash.hs:(92,1)-(95,17) 5446 405 0.0 0.0 0.2 0.0 - allocAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:74:1-45 5454 405 0.1 0.0 0.2 0.0 - new Basement.Block.Base Basement/Block/Base.hs:304:1-76 5455 405 0.0 0.0 0.0 0.0 - unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 5456 405 0.0 0.0 0.0 0.0 - withMutablePtrHint Basement.Block.Base Basement/Block/Base.hs:(475,1)-(489,39) 5457 405 0.1 0.0 0.1 0.0 - copy Data.ByteArray.Methods Data/ByteArray/Methods.hs:(223,1)-(226,21) 5462 405 0.1 0.0 0.1 0.0 - isMutablePinned Basement.Block.Base Basement/Block/Base.hs:100:1-90 5458 405 0.0 0.0 0.0 0.0 - compatIsMutableByteArrayPinned# Basement.Compat.Primitive Basement/Compat/Primitive.hs:70:1-65 5459 405 0.0 0.0 0.0 0.0 - toPinnedStatus# Basement.Compat.Primitive Basement/Compat/Primitive.hs:(47,1)-(48,27) 5460 405 0.0 0.0 0.0 0.0 - unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 5461 405 0.0 0.0 0.0 0.0 - hashInit Crypto.Hash Crypto/Hash.hs:(66,1)-(67,24) 5452 405 0.0 0.0 0.1 0.0 - allocAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:74:1-45 5453 405 0.1 0.0 0.1 0.0 - hashUpdate Crypto.Hash Crypto/Hash.hs:(71,1)-(73,37) 5447 405 0.0 0.0 0.0 0.0 - hashUpdates Crypto.Hash Crypto/Hash.hs:(81,1)-(86,32) 5449 405 0.0 0.0 0.0 0.0 - copyAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:(237,1)-(240,21) 5451 405 0.0 0.0 0.0 0.0 - null Data.ByteArray.Methods Data/ByteArray/Methods.hs:92:1-22 5450 405 0.0 0.0 0.0 0.0 - null Data.ByteArray.Methods Data/ByteArray/Methods.hs:92:1-22 5448 405 0.0 0.0 0.0 0.0 - unpack Data.ByteArray.Methods Data/ByteArray/Methods.hs:(104,1)-(110,34) 5463 405 0.0 0.1 0.3 0.5 - unsafeCast Basement.Block Basement/Block.hs:421:1-32 5464 13365 0.0 0.0 0.0 0.0 - withPtr Basement.Block.Base Basement/Block/Base.hs:(402,1)-(411,31) 5465 12960 0.3 0.3 0.3 0.4 - isPinned Basement.Block.Base Basement/Block/Base.hs:97:1-67 5466 12960 0.0 0.0 0.0 0.0 - compatIsByteArrayPinned# Basement.Compat.Primitive Basement/Compat/Primitive.hs:67:1-51 5467 12960 0.0 0.0 0.0 0.0 - toPinnedStatus# Basement.Compat.Primitive Basement/Compat/Primitive.hs:(47,1)-(48,27) 5468 12960 0.0 0.0 0.0 0.0 - unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 5469 12960 0.0 0.0 0.0 0.0 - putAbi EVM.ABI src/EVM/ABI.hs:(262,1)-(291,15) 5471 0 0.1 0.1 0.1 0.1 - unId Data.Vector.Fusion.Util Data/Vector/Fusion/Util.hs:25:21-24 5599 2432 0.0 0.0 0.0 0.0 - array# Data.Primitive.Array Data/Primitive/Array.hs:87:5-10 5600 1622 0.0 0.0 0.0 0.0 - sElems Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:121:30-35 5630 810 0.0 0.0 0.0 0.0 - abiValueType EVM.ABI src/EVM/ABI.hs:(200,1)-(210,58) 5604 0 0.0 0.0 0.0 0.0 - litWord EVM.Symbolic src/EVM/Symbolic.hs:24:1-52 5434 405 0.0 0.0 0.0 0.0 - genLiteral Data.SBV.Core.Model Data/SBV/Core/Model.hs:99:1-48 5436 405 0.0 0.0 0.0 0.0 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 5438 405 0.0 0.0 0.0 0.0 - svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 5439 405 0.0 0.0 0.0 0.0 - svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 5440 405 0.0 0.0 0.0 0.0 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 5441 405 0.0 0.0 0.0 0.0 - makeTxCall EVM.UnitTest src/EVM/UnitTest.hs:(848,1)-(859,17) 5320 405 0.0 0.0 0.0 0.0 - loadContract EVM src/EVM.hs:(1794,1)-(1806,44) 5323 405 0.0 0.0 0.0 0.0 - w256 EVM.Types src/EVM/Types.hs:90:1-24 5328 405 0.0 0.0 0.0 0.0 - litAddr EVM.Symbolic src/EVM/Symbolic.hs:27:1-36 5326 0 0.0 0.0 0.0 0.0 - genLiteral Data.SBV.Core.Model Data/SBV/Core/Model.hs:99:1-48 5327 405 0.0 0.0 0.0 0.0 - num EVM.Types src/EVM/Types.hs:492:1-18 5319 405 0.0 0.0 0.0 0.0 - pushTrace EVM src/EVM.hs:(2438,1)-(2441,59) 5330 405 0.0 0.0 0.0 0.0 - withTraceLocation EVM src/EVM.hs:(2426,1)-(2435,5) 5332 405 0.0 0.0 0.0 0.0 - evm EVM.Stepper src/EVM/Stepper.hs:78:1-21 5315 0 0.0 0.0 0.0 0.0 - hashCall EVM.UnitTest src/EVM/UnitTest.hs:(244,1)-(245,127) 5894 404 1.7 4.2 1.7 4.2 - _creationCodehash EVM.Solidity src/EVM/Solidity.hs:139:5-21 5896 404 0.0 0.0 0.0 0.0 - _runtimeCodehash EVM.Solidity src/EVM/Solidity.hs:138:5-20 5895 404 0.0 0.0 0.0 0.0 - xxhash EVM.UnitTest src/EVM/UnitTest.hs:213:1-26 5897 404 0.0 0.0 0.0 0.0 - encodeAbiValue EVM.ABI src/EVM/ABI.hs:361:1-50 6373 0 0.0 0.0 0.0 0.0 - putAbi EVM.ABI src/EVM/ABI.hs:(262,1)-(291,15) 6374 0 0.0 0.0 0.0 0.0 - unId Data.Vector.Fusion.Util Data/Vector/Fusion/Util.hs:25:21-24 6375 8 0.0 0.0 0.0 0.0 - array# Data.Primitive.Array Data/Primitive/Array.hs:87:5-10 6376 6 0.0 0.0 0.0 0.0 - sElems Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:121:30-35 6379 2 0.0 0.0 0.0 0.0 - abiValueType EVM.ABI src/EVM/ABI.hs:(200,1)-(210,58) 6378 0 0.0 0.0 0.0 0.0 - unId Data.Vector.Fusion.Util Data/Vector/Fusion/Util.hs:25:21-24 6366 8 0.0 0.0 0.0 0.0 - marray# Data.Primitive.Array Data/Primitive/Array.hs:92:5-11 6367 4 0.0 0.0 0.0 0.0 - passOutput EVM.UnitTest src/EVM/UnitTest.hs:(741,1)-(753,11) 6420 4 0.0 0.0 0.0 0.0 - array# Data.Primitive.Array Data/Primitive/Array.hs:87:5-10 6388 3 0.0 0.0 0.0 0.0 - failOutput EVM.UnitTest src/EVM/UnitTest.hs:(756,1)-(767,3) 6422 1 0.0 0.0 0.0 0.0 - formatTestLogs EVM.UnitTest src/EVM/UnitTest.hs:(770,1)-(773,47) 6425 1 0.0 0.0 0.0 0.0 - formatTestLog EVM.UnitTest src/EVM/UnitTest.hs:(779,1)-(835,61) 6428 2 0.0 0.0 0.0 0.0 - unindexed EVM.Format src/EVM/Format.hs:174:1-42 6436 3 0.0 0.0 0.0 0.0 - maybeLitWord EVM.Types src/EVM/Types.hs:324:1-68 6429 2 0.0 0.0 0.0 0.0 - genFromCV Data.SBV.Core.Model Data/SBV/Core/Model.hs:(103,1)-(104,95) 6431 2 0.0 0.0 0.0 0.0 - svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 6432 2 0.0 0.0 0.0 0.0 - svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 6433 2 0.0 0.0 0.0 0.0 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 6434 2 0.0 0.0 0.0 0.0 - parenthesise EVM.Format src/EVM/Format.hs:112:1-51 6437 2 0.0 0.0 0.0 0.0 - wordValue EVM.Concrete src/EVM/Concrete.hs:39:1-21 6430 2 0.0 0.0 0.0 0.0 - textValues EVM.Format src/EVM/Format.hs:(105,1)-(109,41) 6452 1 0.0 0.0 0.0 0.0 - getAbiSeq EVM.ABI src/EVM/ABI.hs:(294,1)-(297,56) 6453 1 0.0 0.0 0.0 0.0 - marray# Data.Primitive.Array Data/Primitive/Array.hs:92:5-11 6462 3 0.0 0.0 0.0 0.0 - unId Data.Vector.Fusion.Util Data/Vector/Fusion/Util.hs:25:21-24 6461 3 0.0 0.0 0.0 0.0 - getAbi EVM.ABI src/EVM/ABI.hs:(226,1)-(259,66) 6457 2 0.0 0.0 0.0 0.0 - sChunks Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:122:30-36 6460 1 0.0 0.0 0.0 0.0 - sSize Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:124:30-34 6459 1 0.0 0.0 0.0 0.0 - upperBound Data.Vector.Fusion.Bundle.Size Data/Vector/Fusion/Bundle/Size.hs:(126,1)-(128,30) 6458 1 0.0 0.0 0.0 0.0 - textAbiValues EVM.Format src/EVM/Format.hs:102:1-48 6463 1 0.0 0.0 0.0 0.0 - array# Data.Primitive.Array Data/Primitive/Array.hs:87:5-10 6466 2 0.0 0.0 0.0 0.0 - showAbiValue EVM.Format src/EVM/Format.hs:(83,1)-(96,30) 6467 2 0.0 0.0 0.0 0.0 - formatString EVM.ABI src/EVM/ABI.hs:(146,1)-(149,65) 6468 1 0.0 0.0 0.0 0.0 - toChecksumAddress EVM.Types src/EVM/Types.hs:(412,1)-(415,58) 6470 1 0.0 0.0 0.0 0.0 - unpackNibbles EVM.Types src/EVM/Types.hs:(558,1)-(559,35) 6497 1 0.0 0.0 0.0 0.0 - hi EVM.Types src/EVM/Types.hs:551:1-28 6498 20 0.0 0.0 0.0 0.0 - lo EVM.Types src/EVM/Types.hs:552:1-26 6499 20 0.0 0.0 0.0 0.0 - keccakBytes EVM.Types src/EVM/Types.hs:(570,1)-(573,15) 6471 0 0.0 0.0 0.0 0.0 - hash Crypto.Hash Crypto/Hash.hs:58:1-47 6472 1 0.0 0.0 0.0 0.0 - hashFinalize Crypto.Hash Crypto/Hash.hs:(92,1)-(95,17) 6473 1 0.0 0.0 0.0 0.0 - allocAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:74:1-45 6481 1 0.0 0.0 0.0 0.0 - new Basement.Block.Base Basement/Block/Base.hs:304:1-76 6482 1 0.0 0.0 0.0 0.0 - unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 6483 1 0.0 0.0 0.0 0.0 - withMutablePtrHint Basement.Block.Base Basement/Block/Base.hs:(475,1)-(489,39) 6484 1 0.0 0.0 0.0 0.0 - copy Data.ByteArray.Methods Data/ByteArray/Methods.hs:(223,1)-(226,21) 6489 1 0.0 0.0 0.0 0.0 - isMutablePinned Basement.Block.Base Basement/Block/Base.hs:100:1-90 6485 1 0.0 0.0 0.0 0.0 - compatIsMutableByteArrayPinned# Basement.Compat.Primitive Basement/Compat/Primitive.hs:70:1-65 6486 1 0.0 0.0 0.0 0.0 - toPinnedStatus# Basement.Compat.Primitive Basement/Compat/Primitive.hs:(47,1)-(48,27) 6487 1 0.0 0.0 0.0 0.0 - unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 6488 1 0.0 0.0 0.0 0.0 - hashInit Crypto.Hash Crypto/Hash.hs:(66,1)-(67,24) 6479 1 0.0 0.0 0.0 0.0 - allocAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:74:1-45 6480 1 0.0 0.0 0.0 0.0 - hashUpdate Crypto.Hash Crypto/Hash.hs:(71,1)-(73,37) 6474 1 0.0 0.0 0.0 0.0 - hashUpdates Crypto.Hash Crypto/Hash.hs:(81,1)-(86,32) 6476 1 0.0 0.0 0.0 0.0 - copyAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:(237,1)-(240,21) 6478 1 0.0 0.0 0.0 0.0 - null Data.ByteArray.Methods Data/ByteArray/Methods.hs:92:1-22 6477 1 0.0 0.0 0.0 0.0 - null Data.ByteArray.Methods Data/ByteArray/Methods.hs:92:1-22 6475 1 0.0 0.0 0.0 0.0 - unpack Data.ByteArray.Methods Data/ByteArray/Methods.hs:(104,1)-(110,34) 6490 1 0.0 0.0 0.0 0.0 - unsafeCast Basement.Block Basement/Block.hs:421:1-32 6491 33 0.0 0.0 0.0 0.0 - withPtr Basement.Block.Base Basement/Block/Base.hs:(402,1)-(411,31) 6492 32 0.0 0.0 0.0 0.0 - isPinned Basement.Block.Base Basement/Block/Base.hs:97:1-67 6493 32 0.0 0.0 0.0 0.0 - compatIsByteArrayPinned# Basement.Compat.Primitive Basement/Compat/Primitive.hs:67:1-51 6494 32 0.0 0.0 0.0 0.0 - toPinnedStatus# Basement.Compat.Primitive Basement/Compat/Primitive.hs:(47,1)-(48,27) 6495 32 0.0 0.0 0.0 0.0 - unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 6496 32 0.0 0.0 0.0 0.0 - unId Data.Vector.Fusion.Util Data/Vector/Fusion/Util.hs:25:21-24 6465 2 0.0 0.0 0.0 0.0 - sElems Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:121:30-35 6464 1 0.0 0.0 0.0 0.0 - abiTypeSolidity EVM.ABI src/EVM/ABI.hs:(213,1)-(223,104) 6440 0 0.0 0.0 0.0 0.0 - indentLines EVM.UnitTest src/EVM/UnitTest.hs:(736,1)-(738,45) 6500 1 0.0 0.0 0.0 0.0 - hexText EVM.Types src/EVM/Types.hs:(460,1)-(463,52) 6380 1 0.0 0.0 0.0 0.0 - decode Data.ByteString.Base16 Data/ByteString/Base16.hs:(100,1)-(136,75) 6381 1 0.0 0.0 0.0 0.0 - sChunks Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:122:30-36 6365 1 0.0 0.0 0.0 0.0 - sSize Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:124:30-34 6364 1 0.0 0.0 0.0 0.0 - toChecksumAddress EVM.Types src/EVM/Types.hs:(412,1)-(415,58) 6389 1 0.0 0.0 0.0 0.0 - unpackNibbles EVM.Types src/EVM/Types.hs:(558,1)-(559,35) 6416 1 0.0 0.0 0.0 0.0 - hi EVM.Types src/EVM/Types.hs:551:1-28 6417 20 0.0 0.0 0.0 0.0 - lo EVM.Types src/EVM/Types.hs:552:1-26 6418 20 0.0 0.0 0.0 0.0 - keccakBytes EVM.Types src/EVM/Types.hs:(570,1)-(573,15) 6390 0 0.0 0.0 0.0 0.0 - hash Crypto.Hash Crypto/Hash.hs:58:1-47 6391 1 0.0 0.0 0.0 0.0 - hashFinalize Crypto.Hash Crypto/Hash.hs:(92,1)-(95,17) 6392 1 0.0 0.0 0.0 0.0 - allocAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:74:1-45 6400 1 0.0 0.0 0.0 0.0 - new Basement.Block.Base Basement/Block/Base.hs:304:1-76 6401 1 0.0 0.0 0.0 0.0 - unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 6402 1 0.0 0.0 0.0 0.0 - withMutablePtrHint Basement.Block.Base Basement/Block/Base.hs:(475,1)-(489,39) 6403 1 0.0 0.0 0.0 0.0 - copy Data.ByteArray.Methods Data/ByteArray/Methods.hs:(223,1)-(226,21) 6408 1 0.0 0.0 0.0 0.0 - isMutablePinned Basement.Block.Base Basement/Block/Base.hs:100:1-90 6404 1 0.0 0.0 0.0 0.0 - compatIsMutableByteArrayPinned# Basement.Compat.Primitive Basement/Compat/Primitive.hs:70:1-65 6405 1 0.0 0.0 0.0 0.0 - toPinnedStatus# Basement.Compat.Primitive Basement/Compat/Primitive.hs:(47,1)-(48,27) 6406 1 0.0 0.0 0.0 0.0 - unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 6407 1 0.0 0.0 0.0 0.0 - hashInit Crypto.Hash Crypto/Hash.hs:(66,1)-(67,24) 6398 1 0.0 0.0 0.0 0.0 - allocAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:74:1-45 6399 1 0.0 0.0 0.0 0.0 - hashUpdate Crypto.Hash Crypto/Hash.hs:(71,1)-(73,37) 6393 1 0.0 0.0 0.0 0.0 - hashUpdates Crypto.Hash Crypto/Hash.hs:(81,1)-(86,32) 6395 1 0.0 0.0 0.0 0.0 - copyAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:(237,1)-(240,21) 6397 1 0.0 0.0 0.0 0.0 - null Data.ByteArray.Methods Data/ByteArray/Methods.hs:92:1-22 6396 1 0.0 0.0 0.0 0.0 - null Data.ByteArray.Methods Data/ByteArray/Methods.hs:92:1-22 6394 1 0.0 0.0 0.0 0.0 - unpack Data.ByteArray.Methods Data/ByteArray/Methods.hs:(104,1)-(110,34) 6409 1 0.0 0.0 0.0 0.0 - unsafeCast Basement.Block Basement/Block.hs:421:1-32 6410 33 0.0 0.0 0.0 0.0 - withPtr Basement.Block.Base Basement/Block/Base.hs:(402,1)-(411,31) 6411 32 0.0 0.0 0.0 0.0 - isPinned Basement.Block.Base Basement/Block/Base.hs:97:1-67 6412 32 0.0 0.0 0.0 0.0 - compatIsByteArrayPinned# Basement.Compat.Primitive Basement/Compat/Primitive.hs:67:1-51 6413 32 0.0 0.0 0.0 0.0 - toPinnedStatus# Basement.Compat.Primitive Basement/Compat/Primitive.hs:(47,1)-(48,27) 6414 32 0.0 0.0 0.0 0.0 - unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 6415 32 0.0 0.0 0.0 0.0 - upperBound Data.Vector.Fusion.Bundle.Size Data/Vector/Fusion/Bundle/Size.hs:(126,1)-(128,30) 6363 1 0.0 0.0 0.0 0.0 - decodeAbiValue EVM.ABI src/EVM/ABI.hs:364:1-32 6361 0 0.0 0.0 0.1 0.0 - getAbi EVM.ABI src/EVM/ABI.hs:(226,1)-(259,66) 6362 4 0.0 0.0 0.1 0.0 - unId Data.Vector.Fusion.Util Data/Vector/Fusion/Util.hs:25:21-24 6369 4 0.0 0.0 0.0 0.0 - array# Data.Primitive.Array Data/Primitive/Array.hs:87:5-10 6370 3 0.0 0.0 0.0 0.0 - getAbiSeq EVM.ABI src/EVM/ABI.hs:(294,1)-(297,56) 6368 1 0.1 0.0 0.1 0.0 - marray# Data.Primitive.Array Data/Primitive/Array.hs:92:5-11 6387 4 0.0 0.0 0.0 0.0 - unId Data.Vector.Fusion.Util Data/Vector/Fusion/Util.hs:25:21-24 6386 4 0.0 0.0 0.0 0.0 - sChunks Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:122:30-36 6385 1 0.0 0.0 0.0 0.0 - sSize Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:124:30-34 6384 1 0.0 0.0 0.0 0.0 - upperBound Data.Vector.Fusion.Bundle.Size Data/Vector/Fusion/Bundle/Size.hs:(126,1)-(128,30) 6383 1 0.0 0.0 0.0 0.0 - tick EVM.UnitTest src/EVM/UnitTest.hs:304:1-39 6419 3 0.0 0.0 0.0 0.0 - enter EVM.Stepper src/EVM/Stepper.hs:114:1-48 4276 1 0.0 0.0 0.0 0.0 - pushTrace EVM src/EVM.hs:(2438,1)-(2441,59) 4280 1 0.0 0.0 0.0 0.0 - withTraceLocation EVM src/EVM.hs:(2426,1)-(2435,5) 4283 1 0.0 0.0 0.0 0.0 - evm EVM.Stepper src/EVM/Stepper.hs:78:1-21 4278 0 0.0 0.0 0.0 0.0 - initialUnitTestVm EVM.UnitTest src/EVM/UnitTest.hs:(862,1)-(892,61) 4296 1 0.0 0.0 0.1 0.1 - w256 EVM.Types src/EVM/Types.hs:90:1-24 4394 2 0.0 0.0 0.0 0.0 - berlin EVM.FeeSchedule src/EVM/FeeSchedule.hs:185:1-25 4396 1 0.0 0.0 0.0 0.0 - initialContract EVM src/EVM.hs:(516,1)-(533,39) 4297 1 0.0 0.0 0.1 0.1 - mkCodeOps EVM src/EVM.hs:(2721,1)-(2739,79) 4332 1 0.1 0.1 0.1 0.1 - marray# Data.Primitive.Array Data/Primitive/Array.hs:92:5-11 4339 4345 0.0 0.0 0.0 0.0 - unId Data.Vector.Fusion.Util Data/Vector/Fusion/Util.hs:25:21-24 4338 4345 0.0 0.0 0.0 0.0 - opSize EVM src/EVM.hs:(2542,1)-(2543,37) 4336 4344 0.0 0.0 0.0 0.0 - num EVM.Types src/EVM/Types.hs:492:1-18 4337 1136 0.0 0.0 0.0 0.0 - readOp EVM src/EVM.hs:(2636,1)-(2718,21) 4642 1 0.0 0.0 0.0 0.0 - sChunks Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:122:30-36 4335 1 0.0 0.0 0.0 0.0 - sSize Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:124:30-34 4334 1 0.0 0.0 0.0 0.0 - upperBound Data.Vector.Fusion.Bundle.Size Data/Vector/Fusion/Bundle/Size.hs:(126,1)-(128,30) 4333 1 0.0 0.0 0.0 0.0 - mkOpIxMap EVM src/EVM.hs:(2549,1)-(2586,83) 4330 1 0.0 0.0 0.0 0.0 - len EVM.Symbolic src/EVM/Symbolic.hs:(161,1)-(162,38) 4331 1 0.0 0.0 0.0 0.0 - stripBytecodeMetadata EVM.Solidity src/EVM/Solidity.hs:(569,1)-(573,22) 4305 1 0.0 0.0 0.0 0.0 - keccak EVM.Types src/EVM/Types.hs:(580,1)-(583,12) 4298 0 0.0 0.0 0.0 0.0 - keccakBytes EVM.Types src/EVM/Types.hs:(570,1)-(573,15) 4300 0 0.0 0.0 0.0 0.0 - hash Crypto.Hash Crypto/Hash.hs:58:1-47 4301 1 0.0 0.0 0.0 0.0 - hashFinalize Crypto.Hash Crypto/Hash.hs:(92,1)-(95,17) 4302 1 0.0 0.0 0.0 0.0 - allocAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:74:1-45 4311 1 0.0 0.0 0.0 0.0 - new Basement.Block.Base Basement/Block/Base.hs:304:1-76 4312 1 0.0 0.0 0.0 0.0 - unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 4313 1 0.0 0.0 0.0 0.0 - withMutablePtrHint Basement.Block.Base Basement/Block/Base.hs:(475,1)-(489,39) 4314 1 0.0 0.0 0.0 0.0 - copy Data.ByteArray.Methods Data/ByteArray/Methods.hs:(223,1)-(226,21) 4319 1 0.0 0.0 0.0 0.0 - isMutablePinned Basement.Block.Base Basement/Block/Base.hs:100:1-90 4315 1 0.0 0.0 0.0 0.0 - compatIsMutableByteArrayPinned# Basement.Compat.Primitive Basement/Compat/Primitive.hs:70:1-65 4316 1 0.0 0.0 0.0 0.0 - toPinnedStatus# Basement.Compat.Primitive Basement/Compat/Primitive.hs:(47,1)-(48,27) 4317 1 0.0 0.0 0.0 0.0 - unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 4318 1 0.0 0.0 0.0 0.0 - hashInit Crypto.Hash Crypto/Hash.hs:(66,1)-(67,24) 4309 1 0.0 0.0 0.0 0.0 - allocAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:74:1-45 4310 1 0.0 0.0 0.0 0.0 - hashUpdate Crypto.Hash Crypto/Hash.hs:(71,1)-(73,37) 4303 1 0.0 0.0 0.0 0.0 - hashUpdates Crypto.Hash Crypto/Hash.hs:(81,1)-(86,32) 4306 1 0.0 0.0 0.0 0.0 - copyAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:(237,1)-(240,21) 4308 1 0.0 0.0 0.0 0.0 - null Data.ByteArray.Methods Data/ByteArray/Methods.hs:92:1-22 4307 1 0.0 0.0 0.0 0.0 - null Data.ByteArray.Methods Data/ByteArray/Methods.hs:92:1-22 4304 1 0.0 0.0 0.0 0.0 - unpack Data.ByteArray.Methods Data/ByteArray/Methods.hs:(104,1)-(110,34) 4320 1 0.0 0.0 0.0 0.0 - unsafeCast Basement.Block Basement/Block.hs:421:1-32 4321 33 0.0 0.0 0.0 0.0 - withPtr Basement.Block.Base Basement/Block/Base.hs:(402,1)-(411,31) 4322 32 0.0 0.0 0.0 0.0 - isPinned Basement.Block.Base Basement/Block/Base.hs:97:1-67 4323 32 0.0 0.0 0.0 0.0 - compatIsByteArrayPinned# Basement.Compat.Primitive Basement/Compat/Primitive.hs:67:1-51 4324 32 0.0 0.0 0.0 0.0 - toPinnedStatus# Basement.Compat.Primitive Basement/Compat/Primitive.hs:(47,1)-(48,27) 4325 32 0.0 0.0 0.0 0.0 - unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 4326 32 0.0 0.0 0.0 0.0 - word EVM.Types src/EVM/Types.hs:521:1-21 4299 0 0.0 0.0 0.0 0.0 - word256 EVM.Types src/EVM/Types.hs:(510,1)-(518,67) 4327 1 0.0 0.0 0.0 0.0 - padLeft EVM.Types src/EVM/Types.hs:495:1-54 4328 1 0.0 0.0 0.0 0.0 - bytesRead Data.Serialize.Get src/Data/Serialize/Get.hs:838:1-45 4329 0 0.0 0.0 0.0 0.0 - litWord EVM.Symbolic src/EVM/Symbolic.hs:24:1-52 4393 1 0.0 0.0 0.0 0.0 - makeVm EVM src/EVM.hs:(449,1)-(512,30) 4408 1 0.0 0.0 0.0 0.0 - w256 EVM.Types src/EVM/Types.hs:90:1-24 4415 8 0.0 0.0 0.0 0.0 - vmoptAddress EVM src/EVM.hs:191:5-16 4409 4 0.0 0.0 0.0 0.0 - vmoptContract EVM src/EVM.hs:188:5-17 4411 2 0.0 0.0 0.0 0.0 - vmoptCreate EVM src/EVM.hs:205:5-15 4421 2 0.0 0.0 0.0 0.0 - vmoptValue EVM src/EVM.hs:190:5-14 4413 2 0.0 0.0 0.0 0.0 - _contractcode EVM src/EVM.hs:331:5-17 4410 1 0.0 0.0 0.0 0.0 - fromForest Data.Tree.Zipper Data/Tree/Zipper.hs:222:1-78 4424 1 0.0 0.0 0.0 0.0 - vmoptCalldata EVM src/EVM.hs:189:5-17 4412 1 0.0 0.0 0.0 0.0 - vmoptCaller EVM src/EVM.hs:192:5-15 4414 1 0.0 0.0 0.0 0.0 - vmoptCoinbase EVM src/EVM.hs:198:5-17 4417 1 0.0 0.0 0.0 0.0 - vmoptGas EVM src/EVM.hs:194:5-12 4443 1 0.0 0.0 0.0 0.0 - vmoptGaslimit EVM src/EVM.hs:195:5-17 4757 1 0.0 0.0 0.0 0.0 - vmoptGasprice EVM src/EVM.hs:202:5-17 4892 1 0.0 0.0 0.0 0.0 - vmoptMaxCodeSize EVM src/EVM.hs:200:5-20 4707 1 0.0 0.0 0.0 0.0 - vmoptOrigin EVM src/EVM.hs:193:5-15 4420 1 0.0 0.0 0.0 0.0 - vmoptSchedule EVM src/EVM.hs:203:5-17 4419 1 0.0 0.0 0.0 0.0 - vmoptStorageModel EVM src/EVM.hs:206:5-21 4416 1 0.0 0.0 0.0 0.0 - vmoptTimestamp EVM src/EVM.hs:197:5-18 4418 1 0.0 0.0 0.0 0.0 - vmoptTxAccessList EVM src/EVM.hs:207:5-21 4422 1 0.0 0.0 0.0 0.0 - litAddr EVM.Symbolic src/EVM/Symbolic.hs:27:1-36 4390 0 0.0 0.0 0.0 0.0 - genLiteral Data.SBV.Core.Model Data/SBV/Core/Model.hs:99:1-48 4391 1 0.0 0.0 0.0 0.0 - initializeUnitTest EVM.UnitTest src/EVM/UnitTest.hs:(142,1)-(172,17) 4284 1 0.0 0.0 0.0 0.0 - abiCall EVM.UnitTest src/EVM/UnitTest.hs:(842,1)-(845,53) 4832 1 0.0 0.0 0.0 0.0 - abiMethod EVM.ABI src/EVM/ABI.hs:(370,1)-(372,13) 4922 1 0.0 0.0 0.0 0.0 - abiKeccak EVM.Types src/EVM/Types.hs:(586,1)-(590,14) 4923 0 0.0 0.0 0.0 0.0 - word32 EVM.Types src/EVM/Types.hs:(576,1)-(577,52) 4950 1 0.0 0.0 0.0 0.0 - keccakBytes EVM.Types src/EVM/Types.hs:(570,1)-(573,15) 4924 0 0.0 0.0 0.0 0.0 - hash Crypto.Hash Crypto/Hash.hs:58:1-47 4925 1 0.0 0.0 0.0 0.0 - hashFinalize Crypto.Hash Crypto/Hash.hs:(92,1)-(95,17) 4926 1 0.0 0.0 0.0 0.0 - allocAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:74:1-45 4934 1 0.0 0.0 0.0 0.0 - new Basement.Block.Base Basement/Block/Base.hs:304:1-76 4935 1 0.0 0.0 0.0 0.0 - unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 4936 1 0.0 0.0 0.0 0.0 - withMutablePtrHint Basement.Block.Base Basement/Block/Base.hs:(475,1)-(489,39) 4937 1 0.0 0.0 0.0 0.0 - copy Data.ByteArray.Methods Data/ByteArray/Methods.hs:(223,1)-(226,21) 4942 1 0.0 0.0 0.0 0.0 - isMutablePinned Basement.Block.Base Basement/Block/Base.hs:100:1-90 4938 1 0.0 0.0 0.0 0.0 - compatIsMutableByteArrayPinned# Basement.Compat.Primitive Basement/Compat/Primitive.hs:70:1-65 4939 1 0.0 0.0 0.0 0.0 - toPinnedStatus# Basement.Compat.Primitive Basement/Compat/Primitive.hs:(47,1)-(48,27) 4940 1 0.0 0.0 0.0 0.0 - unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 4941 1 0.0 0.0 0.0 0.0 - hashInit Crypto.Hash Crypto/Hash.hs:(66,1)-(67,24) 4932 1 0.0 0.0 0.0 0.0 - allocAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:74:1-45 4933 1 0.0 0.0 0.0 0.0 - hashUpdate Crypto.Hash Crypto/Hash.hs:(71,1)-(73,37) 4927 1 0.0 0.0 0.0 0.0 - hashUpdates Crypto.Hash Crypto/Hash.hs:(81,1)-(86,32) 4929 1 0.0 0.0 0.0 0.0 - copyAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:(237,1)-(240,21) 4931 1 0.0 0.0 0.0 0.0 - null Data.ByteArray.Methods Data/ByteArray/Methods.hs:92:1-22 4930 1 0.0 0.0 0.0 0.0 - null Data.ByteArray.Methods Data/ByteArray/Methods.hs:92:1-22 4928 1 0.0 0.0 0.0 0.0 - unpack Data.ByteArray.Methods Data/ByteArray/Methods.hs:(104,1)-(110,34) 4943 1 0.0 0.0 0.0 0.0 - unsafeCast Basement.Block Basement/Block.hs:421:1-32 4944 33 0.0 0.0 0.0 0.0 - withPtr Basement.Block.Base Basement/Block/Base.hs:(402,1)-(411,31) 4945 32 0.0 0.0 0.0 0.0 - isPinned Basement.Block.Base Basement/Block/Base.hs:97:1-67 4946 32 0.0 0.0 0.0 0.0 - compatIsByteArrayPinned# Basement.Compat.Primitive Basement/Compat/Primitive.hs:67:1-51 4947 32 0.0 0.0 0.0 0.0 - toPinnedStatus# Basement.Compat.Primitive Basement/Compat/Primitive.hs:(47,1)-(48,27) 4948 32 0.0 0.0 0.0 0.0 - unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 4949 32 0.0 0.0 0.0 0.0 - putAbi EVM.ABI src/EVM/ABI.hs:(262,1)-(291,15) 4952 0 0.0 0.0 0.0 0.0 - sElems Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:121:30-35 4960 2 0.0 0.0 0.0 0.0 - unId Data.Vector.Fusion.Util Data/Vector/Fusion/Util.hs:25:21-24 4959 2 0.0 0.0 0.0 0.0 - litWord EVM.Symbolic src/EVM/Symbolic.hs:24:1-52 4912 1 0.0 0.0 0.0 0.0 - genLiteral Data.SBV.Core.Model Data/SBV/Core/Model.hs:99:1-48 4916 1 0.0 0.0 0.0 0.0 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 4918 1 0.0 0.0 0.0 0.0 - svAsInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:(117,1)-(118,57) 4919 1 0.0 0.0 0.0 0.0 - svInteger Data.SBV.Core.Operations Data/SBV/Core/Operations.hs:85:1-46 4920 1 0.0 0.0 0.0 0.0 - mkConstCV Data.SBV.Core.Concrete Data/SBV/Core/Concrete.hs:(436,1)-(449,122) 4921 1 0.0 0.0 0.0 0.0 - makeTxCall EVM.UnitTest src/EVM/UnitTest.hs:(848,1)-(859,17) 4834 1 0.0 0.0 0.0 0.0 - loadContract EVM src/EVM.hs:(1794,1)-(1806,44) 4838 1 0.0 0.0 0.0 0.0 - w256 EVM.Types src/EVM/Types.hs:90:1-24 4890 1 0.0 0.0 0.0 0.0 - litAddr EVM.Symbolic src/EVM/Symbolic.hs:27:1-36 4888 0 0.0 0.0 0.0 0.0 - genLiteral Data.SBV.Core.Model Data/SBV/Core/Model.hs:99:1-48 4889 1 0.0 0.0 0.0 0.0 - num EVM.Types src/EVM/Types.hs:492:1-18 4833 1 0.0 0.0 0.0 0.0 - testAddress EVM.UnitTest src/EVM/UnitTest.hs:94:5-15 4841 1 0.0 0.0 0.0 0.0 - testBalanceCreate EVM.UnitTest src/EVM/UnitTest.hs:99:5-21 5097 1 0.0 0.0 0.0 0.0 - w256 EVM.Types src/EVM/Types.hs:90:1-24 4887 1 0.0 0.0 0.0 0.0 - evm EVM.Stepper src/EVM/Stepper.hs:78:1-21 4285 0 0.0 0.0 0.0 0.0 - dsatPrecision Data.SBV.Core.Symbolic Data/SBV/Core/Symbolic.hs:1839:10-22 3637 1 0.0 0.0 0.0 0.0 - engine Data.SBV.Core.Symbolic Data/SBV/Core/Symbolic.hs:1914:10-15 3642 1 0.0 0.0 0.0 0.0 - standardEngine Data.SBV.SMT.SMT Data/SBV/SMT/SMT.hs:(628,1)-(635,44) 3645 1 0.0 0.0 0.0 0.0 - solver Data.SBV.Core.Symbolic Data/SBV/Core/Symbolic.hs:1840:10-15 3694 22 0.0 0.0 0.0 0.0 - capabilities Data.SBV.Core.Symbolic Data/SBV/Core/Symbolic.hs:1915:10-21 3701 18 0.0 0.0 0.0 0.0 - debug Data.SBV.SMT.Utils Data/SBV/SMT/Utils.hs:(103,1)-(106,59) 3646 18 0.0 0.0 0.0 0.0 - verbose Data.SBV.Core.Symbolic Data/SBV/Core/Symbolic.hs:1826:10-16 3647 18 0.0 0.0 0.0 0.0 - supportsCustomQueries Data.SBV.Core.Symbolic Data/SBV/Core/Symbolic.hs:1783:10-30 3700 17 0.0 0.0 0.0 0.0 - mergeSExpr Data.SBV.SMT.Utils Data/SBV/SMT/Utils.hs:(111,1)-(138,28) 3708 15 0.0 0.0 0.0 0.0 - transcript Data.SBV.Core.Symbolic Data/SBV/Core/Symbolic.hs:1837:10-19 3699 11 0.0 0.0 0.0 0.0 - executable Data.SBV.Core.Symbolic Data/SBV/Core/Symbolic.hs:1911:10-19 3693 2 0.0 0.0 0.0 0.0 - extraArgs Data.SBV.Core.Symbolic Data/SBV/Core/Symbolic.hs:1841:10-18 3698 1 0.0 0.0 0.0 0.0 - options Data.SBV.Core.Symbolic Data/SBV/Core/Symbolic.hs:1913:10-16 3695 1 0.0 0.0 0.0 0.0 - preprocess Data.SBV.Core.Symbolic Data/SBV/Core/Symbolic.hs:1912:10-19 3703 1 0.0 0.0 0.0 0.0 - cvc4 Data.SBV.Provers.CVC4 Data/SBV/Provers/CVC4.hs:(27,1)-(64,25) 3704 0 0.0 0.0 0.0 0.0 - rQueryState Data.SBV.Core.Symbolic Data/SBV/Core/Symbolic.hs:958:23-33 3709 1 0.0 0.0 0.0 0.0 - supportsGlobalDecls Data.SBV.Core.Symbolic Data/SBV/Core/Symbolic.hs:1784:10-28 3707 1 0.0 0.0 0.0 0.0 - parenDeficit Data.SBV.Utils.SExpr Data/SBV/Utils/SExpr.hs:(82,1)-(87,54) 3706 0 0.0 0.0 0.0 0.0 - splitArgs Data.SBV.Utils.Lib Data/SBV/Utils/Lib.hs:(88,1)-(108,40) 3697 0 0.0 0.0 0.0 0.0 - isRunIStage Data.SBV.Core.Symbolic Data/SBV/Core/Symbolic.hs:(856,1)-(859,32) 3636 1 0.0 0.0 0.0 0.0 - optsMode Main hevm-cli/hevm-cli.hs:241:1-78 3941 1 0.0 0.0 0.0 0.0 - debug Main hevm-cli/hevm-cli.hs:124:9-13 3942 1 0.0 0.0 0.0 0.0 - jsontrace Main hevm-cli/hevm-cli.hs:161:9-17 3943 1 0.0 0.0 0.0 0.0 - rSMTOptions Data.SBV.Core.Symbolic Data/SBV/Core/Symbolic.hs:952:23-33 3641 1 0.0 0.0 0.0 0.0 - rinps Data.SBV.Core.Symbolic Data/SBV/Core/Symbolic.hs:938:23-27 3635 1 0.0 0.0 0.0 0.0 - runProofOn Data.SBV.Control.Utils Data/SBV/Control/Utils.hs:(1433,1)-(1463,126) 3649 1 0.0 0.0 0.0 0.0 - isSafetyCheckingIStage Data.SBV.Core.Symbolic Data/SBV/Core/Symbolic.hs:(842,1)-(845,44) 3691 1 0.0 0.0 0.0 0.0 - isSetupIStage Data.SBV.Core.Symbolic Data/SBV/Core/Symbolic.hs:(849,1)-(852,33) 3692 1 0.0 0.0 0.0 0.0 - toSMTLib Data.SBV.SMT.SMTLib Data/SBV/SMT/SMTLib.hs:(31,1)-(32,58) 3650 1 0.0 0.0 0.0 0.0 - cvt Data.SBV.SMT.SMTLib2 Data/SBV/SMT/SMTLib2.hs:(44,1)-(328,31) 3651 1 0.0 0.0 0.0 0.0 - solverSetOptions Data.SBV.Core.Symbolic Data/SBV/Core/Symbolic.hs:1844:10-25 3652 2 0.0 0.0 0.0 0.0 - biplateData Data.Generics.Uniplate.Internal.Data Data/Generics/Uniplate/Internal/Data.hs:(299,1)-(302,27) 3658 1 0.0 0.0 0.0 0.0 - fromOracle Data.Generics.Uniplate.Internal.Data Data/Generics/Uniplate/Internal/Data.hs:115:26-35 3659 1 0.0 0.0 0.0 0.0 - uniplateData Data.Generics.Uniplate.Internal.Data Data/Generics/Uniplate/Internal/Data.hs:(306,1)-(313,36) 3687 1 0.0 0.0 0.0 0.0 - fromC Data.Generics.Uniplate.Internal.Data Data/Generics/Uniplate/Internal/Data.hs:293:20-24 3688 1 0.0 0.0 0.0 0.0 - needsFlattening Data.SBV.Core.Kind Data/SBV/Core/Kind.hs:(355,1)-(368,34) 3656 1 0.0 0.0 0.0 0.0 - typeKey Data.Generics.Uniplate.Internal.Data Data/Generics/Uniplate/Internal/Data.hs:65:1-16 3685 1 0.0 0.0 0.0 0.0 - setSMTOption Data.SBV.Control.Types Data/SBV/Control/Types.hs:(159,1)-(178,57) 3655 0 0.0 0.0 0.0 0.0 - solver Data.SBV.Core.Symbolic Data/SBV/Core/Symbolic.hs:1840:10-15 3643 1 0.0 0.0 0.0 0.0 - solverSetOptions Data.SBV.Core.Symbolic Data/SBV/Core/Symbolic.hs:1844:10-25 3653 1 0.0 0.0 0.0 0.0 - extractSymbolicSimulationState Data.SBV.Core.Symbolic Data/SBV/Core/Symbolic.hs:(1545,1)-(1570,125) 3639 0 0.0 0.0 0.0 0.0 - rconstMap Data.SBV.Core.Symbolic Data/SBV/Core/Symbolic.hs:945:23-31 3640 1 0.0 0.0 0.0 0.0 - unitTestOptions Main hevm-cli/hevm-cli.hs:(262,1)-(304,5) 3711 0 0.0 0.0 5.8 8.5 - dappInfo EVM.Dapp src/EVM/Dapp.hs:(68,1)-(95,5) 4119 1 0.0 0.0 0.0 0.0 - dappRoot Main hevm-cli/hevm-cli.hs:120:9-16 4121 1 0.0 0.0 0.0 0.0 - getParametersFromEnvironmentVariables EVM.UnitTest src/EVM/UnitTest.hs:(910,1)-(942,38) 3938 0 0.0 0.0 0.0 0.0 - readSolc EVM.Solidity src/EVM/Solidity.hs:(297,1)-(303,47) 3713 0 0.1 0.1 5.8 8.5 - readTextDevice Data.Text.Internal.IO libraries/text/Data/Text/Internal/IO.hs:133:39-64 3714 393 0.2 0.0 0.2 0.0 - readJSON EVM.Solidity src/EVM/Solidity.hs:(329,1)-(331,28) 3715 1 0.0 0.1 5.5 8.3 - lazy Control.Lens.Iso src/Control/Lens/Iso.hs:569:1-18 3716 1 0.0 0.0 1.7 2.4 - hash Data.HashMap.Base Data/HashMap/Base.hs:166:1-28 3840 1 0.0 0.0 0.0 0.0 - hashByteArrayWithSalt Data.Hashable.Class Data/Hashable/Class.hs:(770,1)-(772,20) 3841 1 0.0 0.0 0.0 0.0 - maybeResult Data.Attoparsec.ByteString.Lazy Data/Attoparsec/ByteString/Lazy.hs:(103,1)-(104,32) 3717 1 0.0 0.0 0.0 0.0 - parse Data.Attoparsec.ByteString.Lazy Data/Attoparsec/ByteString/Lazy.hs:(88,1)-(95,56) 3718 1 0.0 0.0 1.7 2.4 - runParser Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:111:7-15 3719 16 0.0 0.0 0.0 0.0 - fromPos Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:46:21-27 3722 3 0.0 0.0 0.0 0.0 - buffer Data.Attoparsec.ByteString.Buffer Data/Attoparsec/ByteString/Buffer.hs:85:1-45 3721 1 0.0 0.0 0.0 0.0 - value Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:196:1-36 3724 0 0.0 0.0 1.7 2.4 - array_ Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:169:35-59 3733 0 0.0 0.1 0.3 0.3 - runParser Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:111:7-15 3734 75877 0.0 0.0 0.0 0.0 - fromPos Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:46:21-27 3735 15377 0.0 0.0 0.0 0.0 - marray# Data.Primitive.Array Data/Primitive/Array.hs:92:5-11 3783 23 0.0 0.0 0.0 0.0 - unId Data.Vector.Fusion.Util Data/Vector/Fusion/Util.hs:25:21-24 3782 15 0.0 0.0 0.0 0.0 - sChunks Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:122:30-36 3781 6 0.0 0.0 0.0 0.0 - sSize Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:124:30-34 3780 6 0.0 0.0 0.0 0.0 - upperBound Data.Vector.Fusion.Bundle.Size Data/Vector/Fusion/Bundle/Size.hs:(126,1)-(128,30) 3779 6 0.0 0.0 0.0 0.0 - jstring Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:317:1-32 3751 0 0.2 0.1 0.2 0.1 - runParser Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:111:7-15 3752 123205 0.0 0.0 0.0 0.0 - fromPos Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:46:21-27 3753 20305 0.0 0.0 0.0 0.0 - fromList Data.HashMap.Strict.Base Data/HashMap/Strict/Base.hs:598:1-64 3787 0 0.0 0.0 0.0 0.0 - unsafeInsert Data.HashMap.Base Data/HashMap/Base.hs:(784,1)-(814,76) 3789 9 0.0 0.0 0.0 0.0 - hash Data.HashMap.Base Data/HashMap/Base.hs:166:1-28 3790 9 0.0 0.0 0.0 0.0 - hashByteArrayWithSalt Data.Hashable.Class Data/Hashable/Class.hs:(770,1)-(772,20) 3791 9 0.0 0.0 0.0 0.0 - copy Data.HashMap.Array Data/HashMap/Array.hs:(328,1)-(333,30) 3798 8 0.0 0.0 0.0 0.0 - sparseIndex Data.HashMap.Base Data/HashMap/Base.hs:1867:1-42 3799 5 0.0 0.0 0.0 0.0 - new_ Data.HashMap.Array Data/HashMap/Array.hs:256:1-28 3797 4 0.0 0.0 0.0 0.0 - jstringSlow Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:(333,44)-(337,31) 3765 0 0.0 0.0 0.0 0.0 - object_ Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:132:46-89 3754 0 0.0 0.0 0.0 0.0 - runParser Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:111:7-15 3755 335 0.0 0.0 0.0 0.0 - marray# Data.Primitive.Array Data/Primitive/Array.hs:92:5-11 3796 80 0.0 0.0 0.0 0.0 - fromPos Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:46:21-27 3756 65 0.0 0.0 0.0 0.0 - unId Data.Vector.Fusion.Util Data/Vector/Fusion/Util.hs:25:21-24 3795 28 0.0 0.0 0.0 0.0 - sChunks Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:122:30-36 3794 2 0.0 0.0 0.0 0.0 - sSize Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:124:30-34 3793 2 0.0 0.0 0.0 0.0 - upperBound Data.Vector.Fusion.Bundle.Size Data/Vector/Fusion/Bundle/Size.hs:(126,1)-(128,30) 3792 2 0.0 0.0 0.0 0.0 - scientific Data.Scientific src/Data/Scientific.hs:174:1-23 3788 0 0.0 0.0 0.0 0.0 - jstringSlow Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:(333,44)-(337,31) 3766 0 0.0 0.0 0.0 0.0 - runParser Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:111:7-15 3769 16 0.0 0.0 0.0 0.0 - fromPos Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:46:21-27 3770 3 0.0 0.0 0.0 0.0 - object_ Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:132:46-89 3767 0 0.0 0.0 0.0 0.0 - jstring Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:317:1-32 3768 0 0.0 0.0 0.0 0.0 - object_ Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:132:46-89 3739 0 0.0 0.0 0.2 0.2 - runParser Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:111:7-15 3749 2467 0.0 0.0 0.0 0.0 - fromPos Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:46:21-27 3750 481 0.0 0.0 0.0 0.0 - marray# Data.Primitive.Array Data/Primitive/Array.hs:92:5-11 3804 7 0.0 0.0 0.0 0.0 - unId Data.Vector.Fusion.Util Data/Vector/Fusion/Util.hs:25:21-24 3803 3 0.0 0.0 0.0 0.0 - sChunks Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:122:30-36 3802 1 0.0 0.0 0.0 0.0 - sSize Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:124:30-34 3801 1 0.0 0.0 0.0 0.0 - upperBound Data.Vector.Fusion.Bundle.Size Data/Vector/Fusion/Bundle/Size.hs:(126,1)-(128,30) 3800 1 0.0 0.0 0.0 0.0 - jstring Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:317:1-32 3740 0 0.2 0.2 0.2 0.2 - runParser Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:111:7-15 3741 184758 0.0 0.0 0.0 0.0 - fromPos Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:46:21-27 3742 31081 0.0 0.0 0.0 0.0 - fromList Data.HashMap.Strict.Base Data/HashMap/Strict/Base.hs:598:1-64 3773 0 0.0 0.0 0.0 0.0 - unsafeInsert Data.HashMap.Base Data/HashMap/Base.hs:(784,1)-(814,76) 3776 26 0.0 0.0 0.0 0.0 - hash Data.HashMap.Base Data/HashMap/Base.hs:166:1-28 3777 26 0.0 0.0 0.0 0.0 - hashByteArrayWithSalt Data.Hashable.Class Data/Hashable/Class.hs:(770,1)-(772,20) 3778 26 0.0 0.0 0.0 0.0 - copy Data.HashMap.Array Data/HashMap/Array.hs:(328,1)-(333,30) 3785 20 0.0 0.0 0.0 0.0 - sparseIndex Data.HashMap.Base Data/HashMap/Base.hs:1867:1-42 3786 12 0.0 0.0 0.0 0.0 - new_ Data.HashMap.Array Data/HashMap/Array.hs:256:1-28 3784 10 0.0 0.0 0.0 0.0 - jstringSlow Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:(333,44)-(337,31) 3764 0 0.0 0.0 0.0 0.0 - scientific Data.Scientific src/Data/Scientific.hs:174:1-23 3775 0 0.0 0.0 0.0 0.0 - fromList Data.HashMap.Strict.Base Data/HashMap/Strict/Base.hs:598:1-64 3772 0 0.0 0.0 0.0 0.0 - unsafeInsert Data.HashMap.Base Data/HashMap/Base.hs:(784,1)-(814,76) 3805 2 0.0 0.0 0.0 0.0 - hash Data.HashMap.Base Data/HashMap/Base.hs:166:1-28 3806 2 0.0 0.0 0.0 0.0 - hashByteArrayWithSalt Data.Hashable.Class Data/Hashable/Class.hs:(770,1)-(772,20) 3807 2 0.0 0.0 0.0 0.0 - object_ Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:132:46-89 3725 0 0.1 0.1 1.4 2.1 - runParser Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:111:7-15 3726 80825 0.0 0.0 0.0 0.0 - fromPos Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:46:21-27 3727 17308 0.0 0.0 0.0 0.0 - array_ Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:169:35-59 3743 0 0.0 0.0 0.0 0.0 - jstring Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:317:1-32 3729 0 0.9 1.5 1.3 2.0 - runParser Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:111:7-15 3730 1858836 0.0 0.0 0.0 0.0 - fromPos Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:46:21-27 3731 309351 0.0 0.0 0.0 0.0 - jstringSlow Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:(333,44)-(337,31) 3757 207 0.1 0.0 0.1 0.2 - runParser Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:111:7-15 3758 17077 0.0 0.0 0.0 0.0 - fromPos Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:46:21-27 3759 2739 0.0 0.0 0.0 0.0 - array_ Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:169:35-59 3761 0 0.0 0.1 0.0 0.1 - runParser Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:111:7-15 3762 105487 0.0 0.0 0.0 0.0 - fromPos Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:46:21-27 3763 17284 0.0 0.0 0.0 0.0 - unescapeText Data.Aeson.Parser.UnescapePure pure/Data/Aeson/Parser/UnescapePure.hs:254:1-70 3760 0 0.0 0.0 0.0 0.0 - array_ Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:169:35-59 3736 0 0.4 0.3 0.4 0.4 - runParser Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:111:7-15 3737 304197 0.0 0.0 0.0 0.0 - fromPos Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:46:21-27 3738 49863 0.0 0.0 0.0 0.0 - marray# Data.Primitive.Array Data/Primitive/Array.hs:92:5-11 3824 145 0.0 0.0 0.0 0.0 - unId Data.Vector.Fusion.Util Data/Vector/Fusion/Util.hs:25:21-24 3823 57 0.0 0.0 0.0 0.0 - sChunks Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:122:30-36 3822 8 0.0 0.0 0.0 0.0 - sSize Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:124:30-34 3821 8 0.0 0.0 0.0 0.0 - upperBound Data.Vector.Fusion.Bundle.Size Data/Vector/Fusion/Bundle/Size.hs:(126,1)-(128,30) 3820 8 0.0 0.0 0.0 0.0 - jstringSlow Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:(333,44)-(337,31) 3744 5 0.0 0.0 0.1 0.1 - runParser Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:111:7-15 3745 1383 0.0 0.0 0.0 0.0 - fromPos Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:46:21-27 3746 221 0.0 0.0 0.0 0.0 - fromList Data.HashMap.Strict.Base Data/HashMap/Strict/Base.hs:598:1-64 3808 0 0.0 0.0 0.0 0.0 - unsafeInsert Data.HashMap.Base Data/HashMap/Base.hs:(784,1)-(814,76) 3825 18 0.0 0.0 0.0 0.0 - hash Data.HashMap.Base Data/HashMap/Base.hs:166:1-28 3826 18 0.0 0.0 0.0 0.0 - hashByteArrayWithSalt Data.Hashable.Class Data/Hashable/Class.hs:(770,1)-(772,20) 3827 18 0.0 0.0 0.0 0.0 - copy Data.HashMap.Array Data/HashMap/Array.hs:(328,1)-(333,30) 3837 14 0.0 0.0 0.0 0.0 - new_ Data.HashMap.Array Data/HashMap/Array.hs:256:1-28 3836 7 0.0 0.0 0.0 0.0 - sparseIndex Data.HashMap.Base Data/HashMap/Base.hs:1867:1-42 3838 7 0.0 0.0 0.0 0.0 - unescapeText Data.Aeson.Parser.UnescapePure pure/Data/Aeson/Parser/UnescapePure.hs:254:1-70 3748 0 0.1 0.1 0.1 0.1 - fromList Data.HashMap.Strict.Base Data/HashMap/Strict/Base.hs:598:1-64 3809 0 0.0 0.0 0.0 0.0 - unsafeInsert Data.HashMap.Base Data/HashMap/Base.hs:(784,1)-(814,76) 3817 30 0.0 0.0 0.0 0.0 - hash Data.HashMap.Base Data/HashMap/Base.hs:166:1-28 3818 30 0.0 0.0 0.0 0.0 - hashByteArrayWithSalt Data.Hashable.Class Data/Hashable/Class.hs:(770,1)-(772,20) 3819 30 0.0 0.0 0.0 0.0 - copy Data.HashMap.Array Data/HashMap/Array.hs:(328,1)-(333,30) 3829 18 0.0 0.0 0.0 0.0 - sparseIndex Data.HashMap.Base Data/HashMap/Base.hs:1867:1-42 3830 12 0.0 0.0 0.0 0.0 - new_ Data.HashMap.Array Data/HashMap/Array.hs:256:1-28 3828 9 0.0 0.0 0.0 0.0 - fromList Data.HashMap.Strict.Base Data/HashMap/Strict/Base.hs:598:1-64 3810 0 0.0 0.0 0.0 0.0 - unsafeInsert Data.HashMap.Base Data/HashMap/Base.hs:(784,1)-(814,76) 3811 47 0.0 0.0 0.0 0.0 - hash Data.HashMap.Base Data/HashMap/Base.hs:166:1-28 3812 47 0.0 0.0 0.0 0.0 - hashByteArrayWithSalt Data.Hashable.Class Data/Hashable/Class.hs:(770,1)-(772,20) 3813 47 0.0 0.0 0.0 0.0 - copy Data.HashMap.Array Data/HashMap/Array.hs:(328,1)-(333,30) 3815 38 0.0 0.0 0.0 0.0 - sparseIndex Data.HashMap.Base Data/HashMap/Base.hs:1867:1-42 3816 22 0.0 0.0 0.0 0.0 - new_ Data.HashMap.Array Data/HashMap/Array.hs:256:1-28 3814 19 0.0 0.0 0.0 0.0 - readStdJSON EVM.Solidity src/EVM/Solidity.hs:(364,1)-(407,39) 3842 1 0.1 0.2 3.8 5.8 - sparseIndex Data.HashMap.Base Data/HashMap/Base.hs:1867:1-42 3930 417 0.0 0.0 0.0 0.0 - hash Data.HashMap.Base Data/HashMap/Base.hs:166:1-28 3926 415 0.0 0.0 0.0 0.0 - hashByteArrayWithSalt Data.Hashable.Class Data/Hashable/Class.hs:(770,1)-(772,20) 3927 415 0.0 0.0 0.0 0.0 - unId Data.Vector.Fusion.Util Data/Vector/Fusion/Util.hs:25:21-24 5545 152 0.0 0.0 0.0 0.0 - array# Data.Primitive.Array Data/Primitive/Array.hs:87:5-10 5546 127 0.0 0.0 0.0 0.0 - signature EVM.Solidity src/EVM/Solidity.hs:(468,1)-(478,7) 5553 83 0.0 0.0 0.0 0.0 - hash Data.HashMap.Base Data/HashMap/Base.hs:166:1-28 5554 364 0.0 0.0 0.0 0.0 - hashByteArrayWithSalt Data.Hashable.Class Data/Hashable/Class.hs:(770,1)-(772,20) 5555 364 0.0 0.0 0.0 0.0 - sparseIndex Data.HashMap.Base Data/HashMap/Base.hs:1867:1-42 5556 364 0.0 0.0 0.0 0.0 - unId Data.Vector.Fusion.Util Data/Vector/Fusion/Util.hs:25:21-24 5557 198 0.0 0.0 0.0 0.0 - array# Data.Primitive.Array Data/Primitive/Array.hs:87:5-10 5580 115 0.0 0.0 0.0 0.0 - decode Data.ByteString.Base16 Data/ByteString/Base16.hs:(100,1)-(136,75) 5520 6 0.0 0.0 0.0 0.0 - stripBytecodeMetadata EVM.Solidity src/EVM/Solidity.hs:(569,1)-(573,22) 5519 6 0.0 0.0 0.0 0.0 - lazy Control.Lens.Iso src/Control/Lens/Iso.hs:569:1-18 3843 5 0.1 0.0 3.3 4.9 - hash Data.HashMap.Base Data/HashMap/Base.hs:166:1-28 3923 5 0.0 0.0 0.0 0.0 - hashByteArrayWithSalt Data.Hashable.Class Data/Hashable/Class.hs:(770,1)-(772,20) 3924 5 0.0 0.0 0.0 0.0 - maybeResult Data.Attoparsec.ByteString.Lazy Data/Attoparsec/ByteString/Lazy.hs:(103,1)-(104,32) 3844 5 0.0 0.0 0.0 0.0 - parse Data.Attoparsec.ByteString.Lazy Data/Attoparsec/ByteString/Lazy.hs:(88,1)-(95,56) 3845 5 0.0 0.0 3.3 4.9 - runParser Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:111:7-15 3846 80 0.0 0.0 0.0 0.0 - fromPos Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:46:21-27 3848 15 0.0 0.0 0.0 0.0 - buffer Data.Attoparsec.ByteString.Buffer Data/Attoparsec/ByteString/Buffer.hs:85:1-45 3847 5 0.0 0.0 0.0 0.0 - value Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:196:1-36 3849 0 0.0 0.0 3.3 4.9 - array_ Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:169:35-59 3856 0 0.2 0.2 0.7 0.7 - runParser Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:111:7-15 3857 155263 0.0 0.0 0.0 0.0 - fromPos Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:46:21-27 3858 31458 0.0 0.0 0.0 0.0 - marray# Data.Primitive.Array Data/Primitive/Array.hs:92:5-11 3902 102 0.0 0.0 0.0 0.0 - unId Data.Vector.Fusion.Util Data/Vector/Fusion/Util.hs:25:21-24 3901 54 0.0 0.0 0.0 0.0 - sChunks Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:122:30-36 3900 20 0.0 0.0 0.0 0.0 - sSize Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:124:30-34 3899 20 0.0 0.0 0.0 0.0 - upperBound Data.Vector.Fusion.Bundle.Size Data/Vector/Fusion/Bundle/Size.hs:(126,1)-(128,30) 3898 20 0.0 0.0 0.0 0.0 - jstring Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:317:1-32 3873 0 0.2 0.2 0.2 0.2 - runParser Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:111:7-15 3874 248104 0.0 0.0 0.0 0.0 - fromPos Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:46:21-27 3875 40882 0.0 0.0 0.0 0.0 - jstringSlow Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:(333,44)-(337,31) 3887 0 0.0 0.0 0.0 0.0 - object_ Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:132:46-89 3876 0 0.0 0.0 0.0 0.0 - runParser Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:111:7-15 3877 891 0.0 0.0 0.0 0.0 - marray# Data.Primitive.Array Data/Primitive/Array.hs:92:5-11 3911 233 0.0 0.0 0.0 0.0 - fromPos Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:46:21-27 3878 173 0.0 0.0 0.0 0.0 - unId Data.Vector.Fusion.Util Data/Vector/Fusion/Util.hs:25:21-24 3910 81 0.0 0.0 0.0 0.0 - sChunks Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:122:30-36 3909 5 0.0 0.0 0.0 0.0 - sSize Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:124:30-34 3908 5 0.0 0.0 0.0 0.0 - upperBound Data.Vector.Fusion.Bundle.Size Data/Vector/Fusion/Bundle/Size.hs:(126,1)-(128,30) 3907 5 0.0 0.0 0.0 0.0 - scientific Data.Scientific src/Data/Scientific.hs:174:1-23 3906 0 0.0 0.0 0.0 0.0 - jstringSlow Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:(333,44)-(337,31) 3888 0 0.0 0.0 0.0 0.0 - runParser Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:111:7-15 3891 32 0.0 0.0 0.0 0.0 - fromPos Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:46:21-27 3892 6 0.0 0.0 0.0 0.0 - object_ Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:132:46-89 3889 0 0.0 0.0 0.0 0.0 - jstring Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:317:1-32 3890 0 0.0 0.0 0.0 0.0 - object_ Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:132:46-89 3862 0 0.0 0.0 0.3 0.3 - runParser Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:111:7-15 3871 4975 0.0 0.0 0.0 0.0 - fromPos Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:46:21-27 3872 970 0.0 0.0 0.0 0.0 - marray# Data.Primitive.Array Data/Primitive/Array.hs:92:5-11 3916 14 0.0 0.0 0.0 0.0 - unId Data.Vector.Fusion.Util Data/Vector/Fusion/Util.hs:25:21-24 3915 6 0.0 0.0 0.0 0.0 - sChunks Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:122:30-36 3914 2 0.0 0.0 0.0 0.0 - sSize Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:124:30-34 3913 2 0.0 0.0 0.0 0.0 - upperBound Data.Vector.Fusion.Bundle.Size Data/Vector/Fusion/Bundle/Size.hs:(126,1)-(128,30) 3912 2 0.0 0.0 0.0 0.0 - jstring Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:317:1-32 3863 0 0.3 0.3 0.3 0.3 - runParser Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:111:7-15 3864 372571 0.0 0.0 0.0 0.0 - fromPos Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:46:21-27 3865 62673 0.0 0.0 0.0 0.0 - jstringSlow Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:(333,44)-(337,31) 3886 0 0.0 0.0 0.0 0.0 - scientific Data.Scientific src/Data/Scientific.hs:174:1-23 3894 0 0.0 0.0 0.0 0.0 - fromList Data.HashMap.Strict.Base Data/HashMap/Strict/Base.hs:598:1-64 3893 0 0.0 0.0 0.0 0.0 - unsafeInsert Data.HashMap.Base Data/HashMap/Base.hs:(784,1)-(814,76) 3895 958 0.0 0.0 0.0 0.0 - hash Data.HashMap.Base Data/HashMap/Base.hs:166:1-28 3896 958 0.0 0.0 0.0 0.0 - hashByteArrayWithSalt Data.Hashable.Class Data/Hashable/Class.hs:(770,1)-(772,20) 3897 958 0.0 0.0 0.0 0.0 - copy Data.HashMap.Array Data/HashMap/Array.hs:(328,1)-(333,30) 3904 676 0.0 0.0 0.0 0.0 - sparseIndex Data.HashMap.Base Data/HashMap/Base.hs:1867:1-42 3905 514 0.0 0.0 0.0 0.0 - new_ Data.HashMap.Array Data/HashMap/Array.hs:256:1-28 3903 338 0.0 0.0 0.0 0.0 - object_ Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:132:46-89 3850 0 0.1 0.2 2.6 4.2 - runParser Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:111:7-15 3851 164662 0.0 0.0 0.0 0.0 - fromPos Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:46:21-27 3852 35256 0.0 0.0 0.0 0.0 - array_ Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:169:35-59 3866 0 0.0 0.0 0.0 0.0 - jstring Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:317:1-32 3853 0 2.0 3.0 2.5 4.0 - runParser Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:111:7-15 3854 3769052 0.0 0.0 0.0 0.0 - fromPos Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:46:21-27 3855 627227 0.0 0.0 0.0 0.0 - jstringSlow Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:(333,44)-(337,31) 3879 414 0.0 0.0 0.2 0.3 - runParser Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:111:7-15 3880 34154 0.0 0.0 0.0 0.0 - fromPos Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:46:21-27 3881 5478 0.0 0.0 0.0 0.0 - array_ Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:169:35-59 3883 0 0.1 0.2 0.1 0.2 - runParser Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:111:7-15 3884 210974 0.0 0.0 0.0 0.0 - fromPos Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:46:21-27 3885 34568 0.0 0.0 0.0 0.0 - unescapeText Data.Aeson.Parser.UnescapePure pure/Data/Aeson/Parser/UnescapePure.hs:254:1-70 3882 0 0.1 0.1 0.1 0.1 - array_ Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:169:35-59 3859 0 0.3 0.6 0.4 0.7 - runParser Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:111:7-15 3860 623248 0.0 0.0 0.0 0.0 - fromPos Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:46:21-27 3861 102190 0.0 0.0 0.0 0.0 - marray# Data.Primitive.Array Data/Primitive/Array.hs:92:5-11 3921 688 0.0 0.0 0.0 0.0 - unId Data.Vector.Fusion.Util Data/Vector/Fusion/Util.hs:25:21-24 3920 320 0.0 0.0 0.0 0.0 - sChunks Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:122:30-36 3919 82 0.0 0.0 0.0 0.0 - sSize Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:124:30-34 3918 82 0.0 0.0 0.0 0.0 - upperBound Data.Vector.Fusion.Bundle.Size Data/Vector/Fusion/Bundle/Size.hs:(126,1)-(128,30) 3917 82 0.0 0.0 0.0 0.0 - jstringSlow Data.Aeson.Parser.Internal Data/Aeson/Parser/Internal.hs:(333,44)-(337,31) 3867 10 0.0 0.0 0.1 0.1 - runParser Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:111:7-15 3868 2766 0.0 0.0 0.0 0.0 - fromPos Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:46:21-27 3869 442 0.0 0.0 0.0 0.0 - unescapeText Data.Aeson.Parser.UnescapePure pure/Data/Aeson/Parser/UnescapePure.hs:254:1-70 3870 0 0.1 0.1 0.1 0.1 - scientific Data.Scientific src/Data/Scientific.hs:174:1-23 3931 0 0.0 0.0 0.0 0.0 - sparseIndex Data.HashMap.Base Data/HashMap/Base.hs:1867:1-42 3925 5 0.0 0.0 0.0 0.0 - new_ Data.HashMap.Array Data/HashMap/Array.hs:256:1-28 3932 2 0.0 0.0 0.0 0.0 - abiKeccak EVM.Types src/EVM/Types.hs:(586,1)-(590,14) 5547 0 0.0 0.0 0.0 0.0 - word32 EVM.Types src/EVM/Types.hs:(576,1)-(577,52) 5579 23 0.0 0.0 0.0 0.0 - keccakBytes EVM.Types src/EVM/Types.hs:(570,1)-(573,15) 5548 0 0.0 0.0 0.0 0.0 - hash Crypto.Hash Crypto/Hash.hs:58:1-47 5549 23 0.0 0.0 0.0 0.0 - hashFinalize Crypto.Hash Crypto/Hash.hs:(92,1)-(95,17) 5550 23 0.0 0.0 0.0 0.0 - allocAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:74:1-45 5563 23 0.0 0.0 0.0 0.0 - new Basement.Block.Base Basement/Block/Base.hs:304:1-76 5564 23 0.0 0.0 0.0 0.0 - unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 5565 23 0.0 0.0 0.0 0.0 - withMutablePtrHint Basement.Block.Base Basement/Block/Base.hs:(475,1)-(489,39) 5566 23 0.0 0.0 0.0 0.0 - copy Data.ByteArray.Methods Data/ByteArray/Methods.hs:(223,1)-(226,21) 5571 23 0.0 0.0 0.0 0.0 - isMutablePinned Basement.Block.Base Basement/Block/Base.hs:100:1-90 5567 23 0.0 0.0 0.0 0.0 - compatIsMutableByteArrayPinned# Basement.Compat.Primitive Basement/Compat/Primitive.hs:70:1-65 5568 23 0.0 0.0 0.0 0.0 - toPinnedStatus# Basement.Compat.Primitive Basement/Compat/Primitive.hs:(47,1)-(48,27) 5569 23 0.0 0.0 0.0 0.0 - unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 5570 23 0.0 0.0 0.0 0.0 - hashInit Crypto.Hash Crypto/Hash.hs:(66,1)-(67,24) 5561 23 0.0 0.0 0.0 0.0 - allocAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:74:1-45 5562 23 0.0 0.0 0.0 0.0 - hashUpdate Crypto.Hash Crypto/Hash.hs:(71,1)-(73,37) 5551 23 0.0 0.0 0.0 0.0 - hashUpdates Crypto.Hash Crypto/Hash.hs:(81,1)-(86,32) 5558 23 0.0 0.0 0.0 0.0 - copyAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:(237,1)-(240,21) 5560 23 0.0 0.0 0.0 0.0 - null Data.ByteArray.Methods Data/ByteArray/Methods.hs:92:1-22 5559 23 0.0 0.0 0.0 0.0 - null Data.ByteArray.Methods Data/ByteArray/Methods.hs:92:1-22 5552 23 0.0 0.0 0.0 0.0 - unpack Data.ByteArray.Methods Data/ByteArray/Methods.hs:(104,1)-(110,34) 5572 23 0.0 0.0 0.0 0.0 - unsafeCast Basement.Block Basement/Block.hs:421:1-32 5573 759 0.0 0.0 0.0 0.0 - withPtr Basement.Block.Base Basement/Block/Base.hs:(402,1)-(411,31) 5574 736 0.0 0.0 0.0 0.0 - isPinned Basement.Block.Base Basement/Block/Base.hs:97:1-67 5575 736 0.0 0.0 0.0 0.0 - compatIsByteArrayPinned# Basement.Compat.Primitive Basement/Compat/Primitive.hs:67:1-51 5576 736 0.0 0.0 0.0 0.0 - toPinnedStatus# Basement.Compat.Primitive Basement/Compat/Primitive.hs:(47,1)-(48,27) 5577 736 0.0 0.0 0.0 0.0 - unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 5578 736 0.0 0.0 0.0 0.0 - keccak EVM.Types src/EVM/Types.hs:(580,1)-(583,12) 5512 0 0.0 0.0 0.1 0.1 - keccakBytes EVM.Types src/EVM/Types.hs:(570,1)-(573,15) 5514 0 0.0 0.0 0.1 0.1 - hash Crypto.Hash Crypto/Hash.hs:58:1-47 5515 43 0.0 0.0 0.0 0.0 - hashFinalize Crypto.Hash Crypto/Hash.hs:(92,1)-(95,17) 5516 43 0.0 0.0 0.0 0.0 - allocAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:74:1-45 5526 43 0.0 0.0 0.0 0.0 - new Basement.Block.Base Basement/Block/Base.hs:304:1-76 5527 43 0.0 0.0 0.0 0.0 - unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 5528 43 0.0 0.0 0.0 0.0 - withMutablePtrHint Basement.Block.Base Basement/Block/Base.hs:(475,1)-(489,39) 5529 43 0.0 0.0 0.0 0.0 - copy Data.ByteArray.Methods Data/ByteArray/Methods.hs:(223,1)-(226,21) 5534 43 0.0 0.0 0.0 0.0 - isMutablePinned Basement.Block.Base Basement/Block/Base.hs:100:1-90 5530 43 0.0 0.0 0.0 0.0 - compatIsMutableByteArrayPinned# Basement.Compat.Primitive Basement/Compat/Primitive.hs:70:1-65 5531 43 0.0 0.0 0.0 0.0 - toPinnedStatus# Basement.Compat.Primitive Basement/Compat/Primitive.hs:(47,1)-(48,27) 5532 43 0.0 0.0 0.0 0.0 - unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 5533 43 0.0 0.0 0.0 0.0 - hashInit Crypto.Hash Crypto/Hash.hs:(66,1)-(67,24) 5524 43 0.0 0.0 0.0 0.0 - allocAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:74:1-45 5525 43 0.0 0.0 0.0 0.0 - hashUpdate Crypto.Hash Crypto/Hash.hs:(71,1)-(73,37) 5517 43 0.0 0.0 0.0 0.0 - hashUpdates Crypto.Hash Crypto/Hash.hs:(81,1)-(86,32) 5521 43 0.0 0.0 0.0 0.0 - copyAndFreeze Data.ByteArray.Methods Data/ByteArray/Methods.hs:(237,1)-(240,21) 5523 43 0.0 0.0 0.0 0.0 - null Data.ByteArray.Methods Data/ByteArray/Methods.hs:92:1-22 5522 43 0.0 0.0 0.0 0.0 - null Data.ByteArray.Methods Data/ByteArray/Methods.hs:92:1-22 5518 43 0.0 0.0 0.0 0.0 - unpack Data.ByteArray.Methods Data/ByteArray/Methods.hs:(104,1)-(110,34) 5535 43 0.0 0.0 0.1 0.0 - unsafeCast Basement.Block Basement/Block.hs:421:1-32 5536 1419 0.0 0.0 0.0 0.0 - withPtr Basement.Block.Base Basement/Block/Base.hs:(402,1)-(411,31) 5537 1376 0.1 0.0 0.1 0.0 - isPinned Basement.Block.Base Basement/Block/Base.hs:97:1-67 5538 1376 0.0 0.0 0.0 0.0 - compatIsByteArrayPinned# Basement.Compat.Primitive Basement/Compat/Primitive.hs:67:1-51 5539 1376 0.0 0.0 0.0 0.0 - toPinnedStatus# Basement.Compat.Primitive Basement/Compat/Primitive.hs:(47,1)-(48,27) 5540 1376 0.0 0.0 0.0 0.0 - unsafeNew Basement.Block.Base Basement/Block/Base.hs:(295,1)-(297,129) 5541 1376 0.0 0.0 0.0 0.0 - word EVM.Types src/EVM/Types.hs:521:1-21 5513 0 0.0 0.0 0.0 0.0 - word256 EVM.Types src/EVM/Types.hs:(510,1)-(518,67) 5542 43 0.0 0.0 0.0 0.0 - padLeft EVM.Types src/EVM/Types.hs:495:1-54 5543 43 0.0 0.0 0.0 0.0 - bytesRead Data.Serialize.Get src/Data/Serialize/Get.hs:838:1-45 5544 0 0.0 0.0 0.0 0.0 - makeSrcMaps EVM.Solidity src/EVM/Solidity.hs:(227,1)-(271,126) 5581 0 0.4 0.5 0.4 0.5 - parseTypeName EVM.ABI src/EVM/ABI.hs:375:1-50 6441 0 0.0 0.0 0.0 0.0 - unParser Text.Megaparsec.Internal Text/Megaparsec/Internal.hs:120:5-12 6448 47 0.0 0.0 0.0 0.0 - parseMaybe Text.Megaparsec Text/Megaparsec.hs:(191,1)-(194,21) 6442 3 0.0 0.0 0.0 0.0 - runParser Text.Megaparsec Text/Megaparsec.hs:223:1-61 6443 3 0.0 0.0 0.0 0.0 - runParser' Text.Megaparsec Text/Megaparsec.hs:236:1-42 6444 3 0.0 0.0 0.0 0.0 - runParserT' Text.Megaparsec Text/Megaparsec.hs:(261,1)-(274,54) 6445 3 0.0 0.0 0.0 0.0 - runParsecT Text.Megaparsec.Internal Text/Megaparsec/Internal.hs:(591,1)-(596,56) 6446 3 0.0 0.0 0.0 0.0 - unParser Text.Megaparsec.Internal Text/Megaparsec/Internal.hs:120:5-12 6447 50 0.0 0.0 0.0 0.0 - stateParseErrors Text.Megaparsec.State Text/Megaparsec/State.hs:48:5-20 6449 3 0.0 0.0 0.0 0.0 - union Data.HashMap.Base Data/HashMap/Base.hs:1287:1-23 3929 0 0.0 0.0 0.0 0.0 - smtdebug Main hevm-cli/hevm-cli.hs:130:9-16 3648 1 0.0 0.0 0.0 0.0 - smttimeout Main hevm-cli/hevm-cli.hs:127:9-18 3608 1 0.0 0.0 0.0 0.0 - solver Main hevm-cli/hevm-cli.hs:129:9-14 3606 1 0.0 0.0 0.0 0.0 - unitTestOptions Main hevm-cli/hevm-cli.hs:(262,1)-(304,5) 3710 1 0.0 0.0 0.0 0.0 - applyCache Main hevm-cli/hevm-cli.hs:(244,1)-(259,63) 3935 1 0.0 0.0 0.0 0.0 - cache Main hevm-cli/hevm-cli.hs:116:9-13 3933 1 0.0 0.0 0.0 0.0 - corpus Main hevm-cli/hevm-cli.hs:177:9-14 4123 1 0.0 0.0 0.0 0.0 - fuzzRuns Main hevm-cli/hevm-cli.hs:175:9-16 5300 1 0.0 0.0 0.0 0.0 - getParametersFromEnvironmentVariables EVM.UnitTest src/EVM/UnitTest.hs:(910,1)-(942,38) 3937 1 0.0 0.0 0.0 0.0 - match Main hevm-cli/hevm-cli.hs:184:9-13 4243 1 0.0 0.0 0.0 0.0 - mutations Main hevm-cli/hevm-cli.hs:176:9-17 5900 1 0.0 0.0 0.0 0.0 - readSolc EVM.Solidity src/EVM/Solidity.hs:(297,1)-(303,47) 3712 1 0.0 0.0 0.0 0.0 - replay Main hevm-cli/hevm-cli.hs:178:9-14 5298 1 0.0 0.0 0.0 0.0 - rpc Main hevm-cli/hevm-cli.hs:113:9-11 3939 1 0.0 0.0 0.0 0.0 - state Main hevm-cli/hevm-cli.hs:115:9-13 3934 1 0.0 0.0 0.0 0.0 - verbose Main hevm-cli/hevm-cli.hs:180:9-15 6421 1 0.0 0.0 0.0 0.0 - unwrapRecord Options.Generic src/Options/Generic.hs:1155:1-38 3452 1 0.0 0.0 0.1 0.0 - unHelpful Options.Generic src/Options/Generic.hs:613:57-65 3603 17 0.0 0.0 0.0 0.0 - getRecord Options.Generic src/Options/Generic.hs:(1017,1)-(1019,51) 3453 1 0.0 0.0 0.1 0.0 - getRecordWith Options.Generic src/Options/Generic.hs:(1032,1)-(1035,46) 3454 1 0.0 0.0 0.1 0.0 - customExecParser Options.Applicative.Extra src/Options/Applicative/Extra.hs:(76,1)-(78,23) 3455 1 0.0 0.0 0.1 0.0 - execParserPure Options.Applicative.Extra src/Options/Applicative/Extra.hs:(130,1)-(139,33) 3456 1 0.0 0.0 0.1 0.0 - runP Options.Applicative.Internal src/Options/Applicative/Internal.hs:91:1-59 3457 1 0.0 0.0 0.1 0.0 - bashCompletionParser Options.Applicative.BashCompletion src/Options/Applicative/BashCompletion.hs:(35,1)-(65,7) 3476 1 0.0 0.0 0.0 0.0 - infoParser Options.Applicative.Types src/Options/Applicative/Types.hs:90:5-14 3513 1 0.0 0.0 0.0 0.0 - runParserInfo Options.Applicative.Common src/Options/Applicative/Common.hs:225:1-62 3458 1 0.0 0.0 0.1 0.0 - infoParser Options.Applicative.Types src/Options/Applicative/Types.hs:90:5-14 3475 1 0.0 0.0 0.0 0.0 - infoPolicy Options.Applicative.Types src/Options/Applicative/Types.hs:97:5-14 3471 1 0.0 0.0 0.0 0.0 - runParserFully Options.Applicative.Common src/Options/Applicative/Common.hs:(228,1)-(232,33) 3459 1 0.0 0.0 0.1 0.0 - runParser Options.Applicative.Common src/Options/Applicative/Common.hs:(201,1)-(219,24) 3460 4 0.0 0.0 0.1 0.0 - evalParser Options.Applicative.Common src/Options/Applicative/Common.hs:(237,1)-(241,56) 3508 81 0.0 0.0 0.0 0.0 - parseRecord Main hevm-cli/hevm-cli.hs:(237,3)-(238,62) 3600 0 0.0 0.0 0.0 0.0 - parseRecordWithModifiers Options.Generic src/Options/Generic.hs:1006:1-78 3601 0 0.0 0.0 0.0 0.0 - optMain Options.Applicative.Types src/Options/Applicative/Types.hs:166:5-11 3488 26 0.0 0.0 0.0 0.0 - Options.Applicative.Internal src/Options/Applicative/Internal.hs:(249,1)-(252,15) 3477 5 0.0 0.0 0.0 0.0 - disamb Options.Applicative.Internal src/Options/Applicative/Internal.hs:(258,1)-(265,18) 3461 2 0.0 0.0 0.1 0.0 - runListT Options.Applicative.Internal src/Options/Applicative/Internal.hs:(183,1)-(187,43) 3462 4 0.0 0.0 0.1 0.0 - takeListT Options.Applicative.Internal src/Options/Applicative/Internal.hs:(179,1)-(180,75) 3470 0 0.0 0.0 0.1 0.0 - Options.Applicative.Internal src/Options/Applicative/Internal.hs:(249,1)-(252,15) 3478 5 0.1 0.0 0.1 0.0 - prefDisambiguate Options.Applicative.Types src/Options/Applicative/Types.hs:113:5-20 3556 4 0.0 0.0 0.0 0.0 - optMain Options.Applicative.Types src/Options/Applicative/Types.hs:166:5-11 3563 3 0.0 0.0 0.0 0.0 - infoParser Options.Applicative.Types src/Options/Applicative/Types.hs:90:5-14 3560 1 0.0 0.0 0.0 0.0 - infoPolicy Options.Applicative.Types src/Options/Applicative/Types.hs:97:5-14 3557 1 0.0 0.0 0.0 0.0 - runReadM Options.Applicative.Internal src/Options/Applicative/Internal.hs:98:1-63 3579 1 0.0 0.0 0.0 0.0 - hoistEither Options.Applicative.Internal src/Options/Applicative/Internal.hs:88:1-34 3589 1 0.0 0.0 0.0 0.0 - withReadM Options.Applicative.Internal src/Options/Applicative/Internal.hs:(101,1)-(104,12) 3581 0 0.0 0.0 0.0 0.0 - crReader Options.Applicative.Types src/Options/Applicative/Types.hs:226:5-12 3583 1 0.0 0.0 0.0 0.0 - parseRecord Main hevm-cli/hevm-cli.hs:(237,3)-(238,62) 3584 0 0.0 0.0 0.0 0.0 - parseRecordWithModifiers Options.Generic src/Options/Generic.hs:1006:1-78 3585 0 0.0 0.0 0.0 0.0 - str Options.Applicative.Builder src/Options/Applicative/Builder.hs:129:1-30 3587 0 0.0 0.0 0.0 0.0 - unReadM Options.Applicative.Types src/Options/Applicative/Types.hs:184:5-11 3582 1 0.0 0.0 0.0 0.0 - uncons Options.Applicative.Internal src/Options/Applicative/Internal.hs:(94,1)-(95,30) 3578 1 0.0 0.0 0.0 0.0 - withReadM Options.Applicative.Internal src/Options/Applicative/Internal.hs:(101,1)-(104,12) 3580 1 0.0 0.0 0.0 0.0 - takeListT Options.Applicative.Internal src/Options/Applicative/Internal.hs:(179,1)-(180,75) 3469 4 0.0 0.0 0.0 0.0 - prefBacktrack Options.Applicative.Types src/Options/Applicative/Types.hs:119:5-17 3555 1 0.0 0.0 0.0 0.0 - prefDisambiguate Options.Applicative.Types src/Options/Applicative/Types.hs:113:5-20 3463 1 0.0 0.0 0.0 0.0 - bashCompletionParser Options.Applicative.BashCompletion src/Options/Applicative/BashCompletion.hs:(35,1)-(65,7) 3509 0 0.0 0.0 0.0 0.0 - fromM Options.Applicative.Types src/Options/Applicative/Types.hs:282:1-26 3510 0 0.0 0.0 0.0 0.0 - manyM Options.Applicative.Types src/Options/Applicative/Types.hs:(288,1)-(292,30) 3511 0 0.0 0.0 0.0 0.0 - runParserM Options.Applicative.Types src/Options/Applicative/Types.hs:268:5-14 3512 1 0.0 0.0 0.0 0.0 - parseRecord Main hevm-cli/hevm-cli.hs:(237,3)-(238,62) 3546 0 0.0 0.0 0.0 0.0 - parseRecordWithModifiers Options.Generic src/Options/Generic.hs:1006:1-78 3547 0 0.0 0.0 0.0 0.0 - infoParser Options.Applicative.Types src/Options/Applicative/Types.hs:90:5-14 3562 3 0.0 0.0 0.0 0.0 - subparser Options.Applicative.Builder src/Options/Applicative/Builder.hs:(270,1)-(274,39) 3549 0 0.0 0.0 0.0 0.0 - mkCommand Options.Applicative.Builder.Internal src/Options/Applicative/Builder/Internal.hs:(154,1)-(157,59) 3550 0 0.0 0.0 0.0 0.0 - handleParseResult Options.Applicative.Extra src/Options/Applicative/Extra.hs:(82,1)-(94,17) 3599 1 0.0 0.0 0.0 0.0 - info Options.Applicative.Builder src/Options/Applicative/Builder.hs:(443,1)-(452,34) 3472 1 0.0 0.0 0.0 0.0 - header Options.Applicative.Builder src/Options/Applicative/Builder.hs:395:1-57 3474 0 0.0 0.0 0.0 0.0 - header Options.Applicative.Builder src/Options/Applicative/Builder.hs:395:1-57 3473 1 0.0 0.0 0.0 0.0 - query Data.SBV.Control Data/SBV/Control.hs:105:1-40 3628 0 0.0 0.0 0.0 0.0 - executeQuery Data.SBV.Control.Utils Data/SBV/Control/Utils.hs:(1467,1)-(1619,43) 3629 1 0.0 0.0 0.0 0.0 diff --git a/src/hevm/src/EVM.hs b/src/hevm/src/EVM.hs index 0137a73ad..47d7d92a4 100644 --- a/src/hevm/src/EVM.hs +++ b/src/hevm/src/EVM.hs @@ -30,7 +30,6 @@ import qualified EVM.Precompiled import Control.Lens hiding (op, (:<), (|>), (.>), elements) import Control.Monad.State.Strict hiding (state) -import Data.Aeson (ToJSON, FromJSON) import Data.ByteString (ByteString) import Data.ByteString.Lazy (fromStrict) import Data.Map.Strict (Map) @@ -39,7 +38,6 @@ import Data.Maybe (fromMaybe) import Data.Sequence (Seq) import Data.Vector.Storable (Vector) import Data.Foldable (toList) -import Test.QuickCheck (Arbitrary(..), elements) import Data.Tree import Data.List (find) @@ -290,14 +288,6 @@ data ContractCode | RuntimeCode Buffer -- ^ "Instance" code, after contract creation deriving (Show, Generic) -instance Arbitrary ContractCode where - arbitrary = do - buf <- arbitrary - elements [InitCode buf, RuntimeCode buf] - -instance ToJSON ContractCode -instance FromJSON ContractCode - -- runtime err when used for symbolic code instance Eq ContractCode where (InitCode x) == (InitCode y) = forceBuffer x == forceBuffer y diff --git a/src/hevm/src/EVM/ABI.hs b/src/hevm/src/EVM/ABI.hs index 4e9a36708..30a00ed10 100644 --- a/src/hevm/src/EVM/ABI.hs +++ b/src/hevm/src/EVM/ABI.hs @@ -77,6 +77,7 @@ import Test.QuickCheck hiding ((.&.), label) import Text.ParserCombinators.ReadP import Control.Applicative import Data.Aeson +import Codec.Serialise (Serialise(..)) import qualified Data.ByteString as BS import qualified Data.ByteString.Char8 as Char8 @@ -100,31 +101,12 @@ data AbiValue | AbiTuple (Vector AbiValue) deriving (Read, Eq, Ord, Generic) -instance ToJSON AbiValue -instance FromJSON AbiValue - -instance ToJSON Int256 -instance FromJSON Int256 - -instance ToJSON Int128 -instance FromJSON Int128 - -instance ToJSON Word256 -instance FromJSON Word256 - -instance ToJSON Word128 -instance FromJSON Word128 - -instance ToJSON ByteString where - toJSON = String . Text.pack . show - -instance FromJSON ByteString where - parseJSON = withText "ByteString" $ pure . read . Text.unpack - -instance Arbitrary ByteString where - arbitrary = do - s <- arbitrary - pure $ encodeUtf8 . pack $ s +instance Serialise AbiValue +instance Serialise Int256 +instance Serialise Int128 +instance Serialise Addr +instance Serialise Word160 +instance Serialise AbiType -- | Pretty-print some 'AbiValue'. instance Show AbiValue where diff --git a/src/hevm/src/EVM/Solidity.hs b/src/hevm/src/EVM/Solidity.hs index 3e13c0a5f..b0d36bb0d 100644 --- a/src/hevm/src/EVM/Solidity.hs +++ b/src/hevm/src/EVM/Solidity.hs @@ -99,9 +99,6 @@ data StorageItem = StorageItem { _slot :: Int } deriving (Show, Eq, Ord, Generic) -instance ToJSON StorageItem -instance FromJSON StorageItem - data SlotType -- Note that mapping keys can only be elementary; -- that excludes arrays, contracts, and mappings. @@ -110,9 +107,6 @@ data SlotType -- | StorageArray AbiType deriving (Eq, Ord, Generic) -instance ToJSON SlotType -instance FromJSON SlotType - instance Show SlotType where show (StorageValue t) = show t show (StorageMapping s t) = @@ -149,9 +143,6 @@ data SolcContract = SolcContract , _creationSrcmap :: Seq SrcMap } deriving (Show, Eq, Generic, Ord) -instance ToJSON SolcContract -instance FromJSON SolcContract - data Method = Method { _methodOutput :: [(Text, AbiType)] , _methodInputs :: [(Text, AbiType)] @@ -159,9 +150,6 @@ data Method = Method , _methodSignature :: Text } deriving (Show, Eq, Ord, Generic) -instance ToJSON Method -instance FromJSON Method - data SourceCache = SourceCache { _sourceFiles :: [(Text, ByteString)] , _sourceLines :: [(Vector ByteString)] @@ -173,9 +161,6 @@ data Reference = Reference _refLength :: Int } deriving (Show, Eq, Ord) -instance ToJSON Reference where - toJSON (Reference start len) = object [ "start" .= start, "length" .= len ] - instance FromJSON Reference where parseJSON (Object v) = Reference <$> v .: "start" @@ -192,9 +177,6 @@ instance Monoid SourceCache where data JumpType = JumpInto | JumpFrom | JumpRegular deriving (Show, Eq, Ord, Generic) -instance ToJSON JumpType -instance FromJSON JumpType - data SrcMap = SM { srcMapOffset :: {-# UNPACK #-} Int, srcMapLength :: {-# UNPACK #-} Int, @@ -203,9 +185,6 @@ data SrcMap = SM { srcMapModifierDepth :: {-# UNPACK #-} Int } deriving (Show, Eq, Ord, Generic) -instance ToJSON SrcMap -instance FromJSON SrcMap - data SrcMapParseState = F1 String Int | F2 Int String Int diff --git a/src/hevm/src/EVM/Types.hs b/src/hevm/src/EVM/Types.hs index e1679c17f..c857b4b31 100644 --- a/src/hevm/src/EVM/Types.hs +++ b/src/hevm/src/EVM/Types.hs @@ -30,6 +30,7 @@ import Numeric (readHex, showHex) import Options.Generic import Control.Arrow ((>>>)) import Test.QuickCheck (Arbitrary(..), choose) +import Codec.Serialise (Serialise(..)) import qualified Data.ByteArray as BA import qualified Data.Aeson as JSON @@ -52,24 +53,16 @@ data Buffer = ConcreteBuffer ByteString | SymbolicBuffer [SWord 8] -instance Arbitrary Buffer where - arbitrary = do - contents <- arbitrary - pure $ ConcreteBuffer (Text.encodeUtf8 . Text.pack $ contents) - -instance ToJSON Buffer where - toJSON (ConcreteBuffer bs) = String . Text.pack . show $ bs - toJSON (SymbolicBuffer _) = error "cannot serialize a symbolic buffer to JSON" - -instance FromJSON Buffer where - parseJSON = withText "Buffer" $ pure . ConcreteBuffer . read . Text.unpack - newtype W256 = W256 Word256 deriving ( Num, Integral, Real, Ord, Enum, Eq , Bits, FiniteBits, Bounded, Generic ) +instance Serialise W256 +instance Serialise Word256 +instance Serialise Word128 + instance Arbitrary W256 where arbitrary = do v <- choose (0, 2 ^ (256 :: Integer)) diff --git a/src/hevm/src/EVM/UnitTest.hs b/src/hevm/src/EVM/UnitTest.hs index 06004724f..72bbf3610 100644 --- a/src/hevm/src/EVM/UnitTest.hs +++ b/src/hevm/src/EVM/UnitTest.hs @@ -110,11 +110,6 @@ data TestVMParams = TestVMParams -- reach each known path in the method type Corpus = Map (W256,Text) (Map [(W256, Int)] AbiValue) -instance Arbitrary (MultiSet OpLocation) where - arbitrary = do - coverage <- listOf (arbitrary :: Gen OpLocation) - pure $ MultiSet.fromList coverage - data FuzzResult = Pass | Fail VM String defaultGasForCreating :: W256 @@ -299,17 +294,6 @@ data OpLocation = OpLocation , srcOpIx :: Int } deriving (Show, Eq, Ord, Generic) -instance Arbitrary OpLocation where - arbitrary = do - src <- arbitrary - hash <- arbitrary - opIx <- choose (0, codesize src) - pure $ OpLocation src hash opIx - where - codesize (InitCode (ConcreteBuffer c)) = BS.length c - codesize (RuntimeCode (ConcreteBuffer c)) = BS.length c - codesize _ = error "cannot compute length for symbolic bytecode" - srcMapForOpLocation :: DappInfo -> OpLocation -> Maybe SrcMap srcMapForOpLocation dapp (OpLocation code' _ opIx) = srcMap dapp code' opIx diff --git a/src/hevm/test/test.hs b/src/hevm/test/test.hs index 539ef1caf..ac505a2dc 100644 --- a/src/hevm/test/test.hs +++ b/src/hevm/test/test.hs @@ -39,6 +39,7 @@ import qualified Data.Map as Map import Data.Binary.Get (runGetOrFail) import Data.Aeson (fromJSON, toJSON, Result(..)) +import Codec.Serialise (serialise, deserialise) import EVM hiding (Query, code, path) import EVM.SymExec @@ -104,27 +105,11 @@ main = defaultMain $ testGroup "hevm" [ testProperty "AbiValue" $ do val <- arbitrary :: Gen AbiValue - pure $ case (fromJSON . toJSON $ val) of - Error _ -> False - Data.Aeson.Success v -> val == v - - , testProperty "ByteString" $ do - val <- arbitrary :: Gen ByteString - pure $ case (fromJSON . toJSON $ val) of - Error _ -> False - Data.Aeson.Success v -> val == v - - , testProperty "W256" $ do - val <- arbitrary :: Gen W256 - pure $ case (fromJSON . toJSON $ val) of - Error _ -> False - Data.Aeson.Success v -> val == v + pure $ (deserialise . serialise $ val) == val , testProperty "Corpus" $ withMaxSuccess 20 $ do val <- arbitrary :: Gen Corpus - pure $ case (fromJSON . toJSON $ val) of - Error _ -> False - Data.Aeson.Success v -> val == v + pure $ (deserialise . serialise $ val) == val ] , testGroup "Precompiled contracts" From 2fb197a5d180024df48bb2e68e94fb532a3ae32a Mon Sep 17 00:00:00 2001 From: David Terry Date: Fri, 28 May 2021 19:04:53 +0200 Subject: [PATCH 21/21] hevm: UnitTest: simplify runTest --- src/hevm/src/EVM/UnitTest.hs | 15 ++++++--------- 1 file changed, 6 insertions(+), 9 deletions(-) diff --git a/src/hevm/src/EVM/UnitTest.hs b/src/hevm/src/EVM/UnitTest.hs index 72bbf3610..7e8e3cc94 100644 --- a/src/hevm/src/EVM/UnitTest.hs +++ b/src/hevm/src/EVM/UnitTest.hs @@ -502,20 +502,17 @@ runUnitTestContract runTest :: UnitTestOptions -> VM -> Corpus -> (Test, [AbiType]) -> SBV.Query (Text, Either Text Text, VM, Corpus) -runTest opts@UnitTestOptions{..} vm corpus' (ConcreteTest testName, []) = do - (msg, verboseMsg, postvm) <- liftIO (runOne opts vm testName emptyAbi) - pure (msg, verboseMsg, postvm, corpus') +runTest opts@UnitTestOptions{..} vm corpus' (ConcreteTest testName, []) = liftIO $ extend3 corpus' <$> runOne opts vm testName emptyAbi runTest opts@UnitTestOptions{..} vm corpus' (ConcreteTest testName, types) = liftIO $ case replay of Nothing -> fuzzRun opts vm corpus' testName types Just (sig, callData) -> if sig == testName - then do - (msg, verboseMsg, postvm) <- runOne opts vm testName $ decodeAbiValue (AbiTupleType (Vector.fromList types)) callData - pure (msg, verboseMsg, postvm, corpus') + then extend3 corpus' <$> (runOne opts vm testName $ decodeAbiValue (AbiTupleType (Vector.fromList types)) callData) else fuzzRun opts vm corpus' testName types -runTest opts vm corpus' (SymbolicTest testName, types) = do - (msg, verboseMsg, postvm) <- symRun opts vm testName types - pure (msg, verboseMsg, postvm, corpus') +runTest opts vm corpus' (SymbolicTest testName, types) = extend3 corpus' <$> (symRun opts vm testName types) + +extend3:: d -> (a, b, c) -> (a, b, c, d) +extend3 d (a, b, c) = (a, b, c, d) -- | Define the thread spawner for normal test cases runOne :: UnitTestOptions -> VM -> ABIMethod -> AbiValue -> IO (Text, Either Text Text, VM)