Skip to content

Commit 924dfb2

Browse files
committed
Address review comments
1 parent 8d2cb5e commit 924dfb2

File tree

3 files changed

+17
-17
lines changed

3 files changed

+17
-17
lines changed

Diff for: lib/Echidna/Exec.hs

+8-10
Original file line numberDiff line numberDiff line change
@@ -7,7 +7,7 @@ module Echidna.Exec where
77
import Optics.Core
88
import Optics.State.Operators
99

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

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

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

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

325323
-- | Get the VM's current execution location
326324
currentCovLoc vm = (vm.state.pc, fromMaybe 0 $ vmOpIx vm, length vm.frames)

Diff for: lib/Echidna/Output/Source.hs

+6-7
Original file line numberDiff line numberDiff line change
@@ -9,7 +9,7 @@ import Data.ByteString qualified as BS
99
import Data.Foldable
1010
import Data.IORef (readIORef, IORef)
1111
import Data.List (nub, sort)
12-
import Data.Maybe (fromMaybe, mapMaybe, isJust, fromJust)
12+
import Data.Maybe (fromMaybe, mapMaybe)
1313
import Data.Map (Map)
1414
import Data.Map qualified as Map
1515
import Data.Sequence qualified as Seq
@@ -42,15 +42,15 @@ zipSumStats v1 v2 = do
4242
vec2 <- v2
4343
return [(exec1 + exec2, revert1 + revert2) | (exec1, revert1) <- vec1 | (exec2, revert2) <- vec2]
4444

45-
mvToList :: (VU.Unbox a) => VU.IOVector a -> IO [a]
46-
mvToList = fmap U.toList . U.freeze
47-
4845
combineStats :: TLS (IORef StatsMap) -> IO StatsMapV
4946
combineStats statsRef = do
5047
threadStats' <- allTLS statsRef
5148
threadStats <- mapM readIORef threadStats' :: IO [StatsMap]
52-
statsLists <- pure $ map (\(m :: StatsMap) -> Map.map (\(x :: VU.IOVector StatsInfo) -> mvToList x) m) threadStats :: IO [Map EVM.Types.W256 (IO [StatsInfo])]
49+
let statsLists = map (Map.map mvToList) threadStats :: [Map EVM.Types.W256 (IO [StatsInfo])]
5350
traverse (U.fromList <$>) $ Map.unionsWith zipSumStats statsLists
51+
where
52+
mvToList :: (VU.Unbox a) => VU.IOVector a -> IO [a]
53+
mvToList = fmap U.toList . U.freeze
5454

5555
saveCoverages
5656
:: Env
@@ -199,8 +199,7 @@ srcMapCov sc covMap statMap contracts = do
199199
updateLine (Just (r, q)) = Just ((<> unpackTxResults txResults) r, max q execQty)
200200
updateLine Nothing = Just (unpackTxResults txResults, execQty)
201201
fileStats = Map.lookup c.runtimeCodehash statMap
202-
idxStats | isJust fileStats = fromJust fileStats U.! opIx
203-
| otherwise = (0, 0)
202+
idxStats = maybe (0, 0) (U.! opIx) fileStats
204203
execQty = fst idxStats
205204
Nothing -> acc
206205
Nothing -> acc

Diff for: lib/Echidna/Types/Coverage.hs

+3
Original file line numberDiff line numberDiff line change
@@ -20,10 +20,13 @@ type CoverageMap = Map W256 (IOVector CoverageInfo)
2020

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

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

2932
-- | Basic coverage information

0 commit comments

Comments
 (0)