Skip to content

Commit 559bbc1

Browse files
committed
Further cleaning
1 parent 6e46d86 commit 559bbc1

File tree

2 files changed

+7
-8
lines changed

2 files changed

+7
-8
lines changed

Diff for: lib/Echidna/Exec.hs

+1-2
Original file line numberDiff line numberDiff line change
@@ -320,8 +320,7 @@ execTxWithCov tx = do
320320
(_, depths, results) | depth < 64 && not (depths `testBit` depth) -> do
321321
VMut.write vec pc (opIx, depths `setBit` depth, results `setBit` fromEnum Stop)
322322
writeIORef covContextRef (True, Just (vec, pc))
323-
_ -> do
324-
modifyIORef' covContextRef $ \(new, _) -> (new, Just (vec, pc))
323+
_ -> modifyIORef' covContextRef $ \(new, _) -> (new, Just (vec, pc))
325324

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

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

+6-6
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,5 @@
11
{-# LANGUAGE ViewPatterns #-}
2+
{-# LANGUAGE ParallelListComp #-}
23

34
module Echidna.Output.Source where
45

@@ -39,18 +40,17 @@ zipSumStats :: IO [StatsInfo] -> IO [StatsInfo] -> IO [StatsInfo]
3940
zipSumStats v1 v2 = do
4041
vec1 <- v1
4142
vec2 <- v2
42-
return $ zipWith (\a b -> (fst a + fst b, snd a + snd b)) vec1 vec2
43+
return [(exec1 + exec2, revert1 + revert2) | (exec1, revert1) <- vec1 | (exec2, revert2) <- vec2]
4344

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

4748
combineStats :: TLS (IORef StatsMap) -> IO StatsMapV
4849
combineStats statsRef = do
4950
threadStats' <- allTLS statsRef
50-
threadStats <- sequence $ map readIORef threadStats' :: IO [StatsMap]
51+
threadStats <- mapM readIORef threadStats' :: IO [StatsMap]
5152
statsLists <- pure $ map (\(m :: StatsMap) -> Map.map (\(x :: VU.IOVector StatsInfo) -> mvToList x) m) threadStats :: IO [Map EVM.Types.W256 (IO [StatsInfo])]
52-
stats <- traverse (\x -> x >>= U.thaw . U.fromList >>= U.freeze) $ ((Map.unionsWith) (\(x :: IO [StatsInfo]) (y :: IO [StatsInfo]) -> zipSumStats x y) statsLists)
53-
return stats
53+
traverse (\x -> x >>= U.thaw . U.fromList >>= U.freeze) $ Map.unionsWith zipSumStats statsLists
5454

5555
saveCoverages
5656
:: Env
@@ -199,8 +199,8 @@ 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 = (fromInteger 0, fromInteger 0)
202+
idxStats | isJust fileStats = fromJust fileStats U.! opIx
203+
| otherwise = (0, 0)
204204
execQty = fst idxStats
205205
Nothing -> acc
206206
Nothing -> acc

0 commit comments

Comments
 (0)