Skip to content

Commit

Permalink
cleanup
Browse files Browse the repository at this point in the history
  • Loading branch information
samalws-tob committed Sep 9, 2024
1 parent 9b72370 commit 4eb2f33
Showing 1 changed file with 18 additions and 4 deletions.
22 changes: 18 additions & 4 deletions lib/Echidna/Types/Coverage.hs
Original file line number Diff line number Diff line change
@@ -1,5 +1,6 @@
module Echidna.Types.Coverage where

import Control.Monad ((>=>))
import Data.Aeson (ToJSON(toJSON), FromJSON(parseJSON), withText)
import Data.Bits (testBit)
import Data.IORef (IORef, readIORef)
Expand All @@ -22,6 +23,8 @@ import Echidna.Types.Tx (TxResult)
-- Indexed by contracts' compile-time codehash; see `CodehashMap`.
type CoverageMap = Map W256 (IOVector CoverageInfo)

-- | CoverageMap, but using Vectors instead of IOVectors.
-- IO is not required to access this map's members.
type FrozenCoverageMap = Map W256 (V.Vector CoverageInfo)

-- | Basic coverage information
Expand All @@ -36,17 +39,28 @@ type StackDepths = Word64
-- | Packed TxResults used for coverage, corresponding bits are set
type TxResults = Word64

-- | Given the CoverageMaps used for contract init and runtime, produce a single combined coverage map
-- with op indices from init correctly shifted over (see srcMapForOpLocation in Echidna.Output.Source).
-- Takes IORef CoverageMap because this is how they are stored in the Env.
mergeCoverageMaps :: DappInfo -> IORef CoverageMap -> IORef CoverageMap -> IO FrozenCoverageMap
mergeCoverageMaps dapp initMap runtimeMap = do
initMap' <- Map.mapWithKey modifyInitMapEntry <$> (mapM V.freeze =<< readIORef initMap)
runtimeMap' <- mapM V.freeze =<< readIORef runtimeMap
pure $ Map.unionWith (<>) runtimeMap' initMap'
mergeCoverageMaps dapp initMap runtimeMap = mergeFrozenCoverageMaps dapp <$> freeze initMap <*> freeze runtimeMap
where freeze = readIORef >=> mapM V.freeze

-- | Given the FrozenCoverageMaps used for contract init and runtime, produce a single combined coverage map
-- with op indices from init correctly shifted over (see srcMapForOpLocation in Echidna.Output.Source).
-- Helper function for mergeCoverageMaps.
mergeFrozenCoverageMaps :: DappInfo -> FrozenCoverageMap -> FrozenCoverageMap -> FrozenCoverageMap
mergeFrozenCoverageMaps dapp initMap runtimeMap = Map.unionWith (<>) runtimeMap initMap'
where
initMap' = Map.mapWithKey modifyInitMapEntry initMap
-- eta reduced, second argument is a vec
modifyInitMapEntry hash = V.map $ modifyCoverageInfo $ getOpOffset hash
modifyCoverageInfo toAdd (op, x, y) = (op + toAdd, x, y)
getOpOffset hash = maybe 0 (length . (.runtimeSrcmap) . snd) $ Map.lookup hash dapp.solcByHash

-- | Given the CoverageMaps used for contract init and runtime,
-- return the point coverage and the number of unique contracts hit.
-- Takes IORef CoverageMap because this is how they are stored in the Env.
coverageStats :: IORef CoverageMap -> IORef CoverageMap -> IO (Int, Int)
coverageStats initRef runtimeRef = do
initMap <- readIORef initRef
Expand Down

0 comments on commit 4eb2f33

Please sign in to comment.