Skip to content

Commit

Permalink
Address review comments
Browse files Browse the repository at this point in the history
  • Loading branch information
elopez committed Jul 11, 2024
1 parent 8d2cb5e commit 924dfb2
Show file tree
Hide file tree
Showing 3 changed files with 17 additions and 17 deletions.
18 changes: 8 additions & 10 deletions lib/Echidna/Exec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -7,7 +7,7 @@ module Echidna.Exec where
import Optics.Core
import Optics.State.Operators

import Control.Monad (when, forM_)
import Control.Monad (when)
import Control.Monad.Catch (MonadThrow(..))
import Control.Monad.State.Strict (MonadState(get, put), execState, runStateT, MonadIO(liftIO), gets, modify', execStateT)
import Control.Monad.Reader (MonadReader, ask, asks)
Expand Down Expand Up @@ -287,23 +287,20 @@ execTxWithCov tx = do
addCoverage !vm = do
let (pc, opIx, depth) = currentCovLoc vm
contract = currentContract vm
contractSize = BS.length . forceBuf . fromJust . view bytecode $ contract

maybeCovVec <- lookupUsingCodehashOrInsert env.codehashMap contract env.dapp env.coverageRef $ do
let size = BS.length . forceBuf . fromJust . view bytecode $ contract
if size == 0 then pure Nothing else do
if contractSize == 0 then pure Nothing else do
-- IO for making a new vec
vec <- VMut.new size
-- We use -1 for opIx to indicate that the location was not covered
forM_ [0..size-1] $ \i -> VMut.write vec i (-1, 0, 0)
vec <- VMut.replicate contractSize (-1, 0, 0)
pure $ Just vec

statsRef <- getTLS env.statsRef
maybeStatsVec <- lookupUsingCodehashOrInsert env.codehashMap contract env.dapp statsRef $ do
let size = BS.length . forceBuf . fromJust . view bytecode $ contract
if size == 0 then pure Nothing else do
if contractSize == 0 then pure Nothing else do
-- IO for making a new vec
vec <- VMut.new size
forM_ [0..size-1] $ \i -> VMut.write vec i (0, 0)
vec <- VMut.replicate contractSize (0, 0)
pure $ Just vec

case maybeCovVec of
Expand All @@ -320,7 +317,8 @@ execTxWithCov tx = do
(_, depths, results) | depth < 64 && not (depths `testBit` depth) -> do
VMut.write vec pc (opIx, depths `setBit` depth, results `setBit` fromEnum Stop)
writeIORef covContextRef (True, Just (vec, pc))
_ -> modifyIORef' covContextRef $ \(new, _) -> (new, Just (vec, pc))
_ ->
modifyIORef' covContextRef $ \(new, _) -> (new, Just (vec, pc))

-- | Get the VM's current execution location
currentCovLoc vm = (vm.state.pc, fromMaybe 0 $ vmOpIx vm, length vm.frames)
Expand Down
13 changes: 6 additions & 7 deletions lib/Echidna/Output/Source.hs
Original file line number Diff line number Diff line change
Expand Up @@ -9,7 +9,7 @@ import Data.ByteString qualified as BS
import Data.Foldable
import Data.IORef (readIORef, IORef)
import Data.List (nub, sort)
import Data.Maybe (fromMaybe, mapMaybe, isJust, fromJust)
import Data.Maybe (fromMaybe, mapMaybe)
import Data.Map (Map)
import Data.Map qualified as Map
import Data.Sequence qualified as Seq
Expand Down Expand Up @@ -42,15 +42,15 @@ zipSumStats v1 v2 = do
vec2 <- v2
return [(exec1 + exec2, revert1 + revert2) | (exec1, revert1) <- vec1 | (exec2, revert2) <- vec2]

mvToList :: (VU.Unbox a) => VU.IOVector a -> IO [a]
mvToList = fmap U.toList . U.freeze

combineStats :: TLS (IORef StatsMap) -> IO StatsMapV
combineStats statsRef = do
threadStats' <- allTLS statsRef
threadStats <- mapM readIORef threadStats' :: IO [StatsMap]
statsLists <- pure $ map (\(m :: StatsMap) -> Map.map (\(x :: VU.IOVector StatsInfo) -> mvToList x) m) threadStats :: IO [Map EVM.Types.W256 (IO [StatsInfo])]
let statsLists = map (Map.map mvToList) threadStats :: [Map EVM.Types.W256 (IO [StatsInfo])]
traverse (U.fromList <$>) $ Map.unionsWith zipSumStats statsLists
where
mvToList :: (VU.Unbox a) => VU.IOVector a -> IO [a]
mvToList = fmap U.toList . U.freeze

saveCoverages
:: Env
Expand Down Expand Up @@ -199,8 +199,7 @@ srcMapCov sc covMap statMap contracts = do
updateLine (Just (r, q)) = Just ((<> unpackTxResults txResults) r, max q execQty)
updateLine Nothing = Just (unpackTxResults txResults, execQty)
fileStats = Map.lookup c.runtimeCodehash statMap
idxStats | isJust fileStats = fromJust fileStats U.! opIx
| otherwise = (0, 0)
idxStats = maybe (0, 0) (U.! opIx) fileStats
execQty = fst idxStats
Nothing -> acc
Nothing -> acc
Expand Down
3 changes: 3 additions & 0 deletions lib/Echidna/Types/Coverage.hs
Original file line number Diff line number Diff line change
Expand Up @@ -20,10 +20,13 @@ type CoverageMap = Map W256 (IOVector CoverageInfo)

-- | Map with the statistic information needed for source code printing.
-- Indexed by contracts' compile-time codehash; see `CodehashMap`.
-- Used during runtime data collection
type StatsMap = Map W256 (IOVector StatsInfo)

-- | Map with the statistic information needed for source code printing.
-- Indexed by contracts' compile-time codehash; see `CodehashMap`.
-- Used during statistics summarization (combining multiple `StatsMap`)
-- and coverage report generation.
type StatsMapV = Map W256 (Vector StatsInfo)

-- | Basic coverage information
Expand Down

0 comments on commit 924dfb2

Please sign in to comment.