Skip to content

Commit

Permalink
coverageStats
Browse files Browse the repository at this point in the history
  • Loading branch information
samalws-tob committed Sep 6, 2024
1 parent 1bfa119 commit 9b72370
Show file tree
Hide file tree
Showing 4 changed files with 18 additions and 18 deletions.
7 changes: 3 additions & 4 deletions lib/Echidna/Campaign.hs
Original file line number Diff line number Diff line change
Expand Up @@ -43,7 +43,7 @@ import Echidna.Transaction
import Echidna.Types (Gas)
import Echidna.Types.Campaign
import Echidna.Types.Corpus (Corpus, corpusSize)
import Echidna.Types.Coverage (scoveragePoints)
import Echidna.Types.Coverage (coverageStats)
import Echidna.Types.Config
import Echidna.Types.Signature (FunctionName)
import Echidna.Types.Test
Expand Down Expand Up @@ -353,10 +353,9 @@ callseq vm txSeq = do
let !corp' = force $ addToCorpus (ncallseqs + 1) results corp
in (corp', corpusSize corp')

cov <- liftIO . readIORef =<< asks (.coverageRefRuntime)
points <- liftIO $ scoveragePoints cov
(points, numCodehashes) <- liftIO $ coverageStats env.coverageRefInit env.coverageRefRuntime
pushWorkerEvent NewCoverage { points
, numCodehashes = length cov
, numCodehashes
, corpusSize = newSize
, transactions = fst <$> results
}
Expand Down
9 changes: 9 additions & 0 deletions lib/Echidna/Types/Coverage.hs
Original file line number Diff line number Diff line change
Expand Up @@ -6,6 +6,7 @@ import Data.IORef (IORef, readIORef)
import Data.List (foldl')
import Data.Map qualified as Map
import Data.Map.Strict (Map)
import Data.Set qualified as Set
import Data.Text (toLower)
import Data.Vector.Unboxed.Mutable (IOVector)
import Data.Vector.Unboxed.Mutable qualified as VM
Expand Down Expand Up @@ -46,6 +47,14 @@ mergeCoverageMaps dapp initMap runtimeMap = do
modifyCoverageInfo toAdd (op, x, y) = (op + toAdd, x, y)
getOpOffset hash = maybe 0 (length . (.runtimeSrcmap) . snd) $ Map.lookup hash dapp.solcByHash

coverageStats :: IORef CoverageMap -> IORef CoverageMap -> IO (Int, Int)
coverageStats initRef runtimeRef = do
initMap <- readIORef initRef
runtimeMap <- readIORef runtimeRef
pointsInit <- scoveragePoints initMap
pointsRuntime <- scoveragePoints runtimeMap
pure (pointsInit + pointsRuntime, length $ Set.toList $ Set.fromList $ Map.keys initMap ++ Map.keys runtimeMap)

-- | Given good point coverage, count the number of unique points but
-- only considering the different instruction PCs (discarding the TxResult).
-- This is useful for reporting a coverage measure to the user
Expand Down
6 changes: 2 additions & 4 deletions lib/Echidna/UI.hs
Original file line number Diff line number Diff line change
Expand Up @@ -39,7 +39,7 @@ import Echidna.Server (runSSEServer)
import Echidna.Types.Campaign
import Echidna.Types.Config
import Echidna.Types.Corpus qualified as Corpus
import Echidna.Types.Coverage (scoveragePoints)
import Echidna.Types.Coverage (coverageStats)
import Echidna.Types.Test (EchidnaTest(..), didFail, isOptimizationTest)
import Echidna.Types.Tx (Tx)
import Echidna.UI.Report
Expand Down Expand Up @@ -339,9 +339,7 @@ statusLine
-> IO String
statusLine env states = do
tests <- traverse readIORef env.testRefs
pointsInit <- scoveragePoints =<< readIORef env.coverageRefInit
pointsRuntime <- scoveragePoints =<< readIORef env.coverageRefRuntime
let points = pointsInit + pointsRuntime
(points, _) <- coverageStats env.coverageRefInit env.coverageRefRuntime
corpus <- readIORef env.corpusRef
let totalCalls = sum ((.ncalls) <$> states)
pure $ "tests: " <> show (length $ filter didFail tests) <> "/" <> show (length tests)
Expand Down
14 changes: 4 additions & 10 deletions lib/Echidna/UI/Report.hs
Original file line number Diff line number Diff line change
@@ -1,14 +1,13 @@
module Echidna.UI.Report where

import Control.Monad (forM)
import Control.Monad.Reader (MonadReader, MonadIO (liftIO), asks)
import Control.Monad.Reader (MonadReader, MonadIO (liftIO), asks, ask)
import Control.Monad.ST (RealWorld)
import Data.IORef (readIORef)
import Data.List (intercalate, nub, sortOn)
import Data.Map (toList)
import Data.Map qualified as Map
import Data.Maybe (catMaybes, fromJust, fromMaybe)
import Data.Set qualified as Set
import Data.Text (Text, unpack)
import Data.Text qualified as T
import Data.Time (LocalTime)
Expand All @@ -21,7 +20,7 @@ import Echidna.Types (Gas)
import Echidna.Types.Campaign
import Echidna.Types.Config
import Echidna.Types.Corpus (corpusSize)
import Echidna.Types.Coverage (scoveragePoints)
import Echidna.Types.Coverage (coverageStats)
import Echidna.Types.Test (EchidnaTest(..), TestState(..), TestType(..))
import Echidna.Types.Tx (Tx(..), TxCall(..), TxConf(..))
import Echidna.Utility (timePrefix)
Expand Down Expand Up @@ -98,13 +97,8 @@ ppDelay (time, block) =
-- | Pretty-print the coverage a 'Campaign' has obtained.
ppCoverage :: (MonadIO m, MonadReader Env m) => m String
ppCoverage = do
coverageInit <- liftIO . readIORef =<< asks (.coverageRefInit)
coverageRuntime <- liftIO . readIORef =<< asks (.coverageRefRuntime)
pointsInit <- liftIO $ scoveragePoints coverageInit
pointsRuntime <- liftIO $ scoveragePoints coverageRuntime
let
points = pointsInit + pointsRuntime
uniqueCodehashes = length $ Set.fromList $ Map.keys coverageInit ++ Map.keys coverageRuntime
env <- ask
(points, uniqueCodehashes) <- liftIO $ coverageStats env.coverageRefInit env.coverageRefRuntime
pure $ "Unique instructions: " <> show points <> "\n" <>
"Unique codehashes: " <> show uniqueCodehashes

Expand Down

0 comments on commit 9b72370

Please sign in to comment.