Skip to content

Commit bbd35b0

Browse files
authored
Save corpus and reproducers continuously (#1167)
1 parent 24cd972 commit bbd35b0

File tree

8 files changed

+165
-86
lines changed

8 files changed

+165
-86
lines changed

lib/Echidna/Campaign.hs

Lines changed: 49 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -3,7 +3,7 @@
33

44
module Echidna.Campaign where
55

6-
import Control.Concurrent (writeChan)
6+
import Control.Concurrent
77
import Control.DeepSeq (force)
88
import Control.Monad (replicateM, when, void, forM_)
99
import Control.Monad.Catch (MonadThrow(..))
@@ -22,6 +22,7 @@ import Data.Maybe (isJust, mapMaybe, fromMaybe)
2222
import Data.Set (Set)
2323
import Data.Set qualified as Set
2424
import Data.Text (Text)
25+
import Data.Time (LocalTime)
2526
import System.Random (mkStdGen)
2627

2728
import EVM (cheatCode)
@@ -67,7 +68,7 @@ replayCorpus
6768
replayCorpus vm txSeqs =
6869
forM_ (zip [1..] txSeqs) $ \(i, txSeq) -> do
6970
_ <- callseq vm txSeq
70-
pushEvent (TxSequenceReplayed i (length txSeqs))
71+
pushWorkerEvent (TxSequenceReplayed i (length txSeqs))
7172

7273
-- | Run a fuzzing campaign given an initial universe state, some tests, and an
7374
-- optional dictionary to generate calls with. Return the 'Campaign' state once
@@ -206,7 +207,11 @@ callseq vm txSeq = do
206207

207208
cov <- liftIO . readIORef =<< asks (.coverageRef)
208209
points <- liftIO $ scoveragePoints cov
209-
pushEvent (NewCoverage points (length cov) newSize)
210+
pushWorkerEvent NewCoverage { points
211+
, numCodehashes = length cov
212+
, corpusSize = newSize
213+
, transactions = fst <$> results
214+
}
210215

211216
modify' $ \workerState ->
212217

@@ -368,10 +373,10 @@ updateTest vmForShrink (vm, xs) test = do
368373
test' = updateOpenTest test xs (testValue, vm', results)
369374
case test'.state of
370375
Large _ -> do
371-
pushEvent (TestFalsified test')
376+
pushWorkerEvent (TestFalsified test')
372377
pure (Just test')
373378
_ | test'.value > test.value -> do
374-
pushEvent (TestOptimized test')
379+
pushWorkerEvent (TestOptimized test')
375380
pure (Just test')
376381
_ -> pure Nothing
377382
Large _ ->
@@ -381,12 +386,46 @@ updateTest vmForShrink (vm, xs) test = do
381386
shrinkTest vmForShrink test
382387
_ -> pure Nothing
383388

384-
pushEvent
389+
pushWorkerEvent
385390
:: (MonadReader Env m, MonadState WorkerState m, MonadIO m)
386-
=> CampaignEvent
391+
=> WorkerEvent
387392
-> m ()
388-
pushEvent event = do
393+
pushWorkerEvent event = do
389394
workerId <- gets (.workerId)
395+
env <- ask
396+
liftIO $ pushCampaignEvent env (WorkerEvent workerId event)
397+
398+
pushCampaignEvent :: Env -> CampaignEvent -> IO ()
399+
pushCampaignEvent env event = do
390400
time <- liftIO getTimestamp
391-
chan <- asks (.eventQueue)
392-
liftIO $ writeChan chan (workerId, time, event)
401+
writeChan env.eventQueue (time, event)
402+
403+
-- | Listener reads events and runs the given 'handler' function. It exits after
404+
-- receiving all 'WorkerStopped' events and sets the returned 'MVar' so the
405+
-- parent thread can safely block on listener until all events are processed.
406+
--
407+
-- NOTE: because the 'Failure' event does not come from a specific fuzzing worker
408+
-- it is possible that a listener won't process it if emitted after all workers
409+
-- are stopped. This is quite unlikely and non-critical but should be addressed
410+
-- in the long term.
411+
spawnListener
412+
:: (MonadReader Env m, MonadIO m)
413+
=> ((LocalTime, CampaignEvent) -> IO ())
414+
-- ^ a function that handles the events
415+
-> m (MVar ())
416+
spawnListener handler = do
417+
cfg <- asks (.cfg)
418+
let nworkers = fromMaybe 1 cfg.campaignConf.workers
419+
eventQueue <- asks (.eventQueue)
420+
chan <- liftIO $ dupChan eventQueue
421+
stopVar <- liftIO newEmptyMVar
422+
liftIO $ void $ forkFinally (loop chan nworkers) (const $ putMVar stopVar ())
423+
pure stopVar
424+
where
425+
loop chan !workersAlive =
426+
when (workersAlive > 0) $ do
427+
event <- readChan chan
428+
handler event
429+
case event of
430+
(_, WorkerEvent _ (WorkerStopped _)) -> loop chan (workersAlive - 1)
431+
_ -> loop chan workersAlive

lib/Echidna/Output/Corpus.hs

Lines changed: 37 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,20 +1,28 @@
11
module Echidna.Output.Corpus where
22

3+
import Control.Exception (IOException, handle)
4+
import Control.Monad (unless)
35
import Control.Monad.Extra (unlessM)
46
import Data.Aeson (ToJSON(..), decodeStrict, encodeFile)
57
import Data.ByteString qualified as BS
68
import Data.Hashable (hash)
79
import Data.Maybe (catMaybes)
10+
import Data.Time (LocalTime)
811
import System.Directory (createDirectoryIfMissing, makeRelativeToCurrentDirectory, doesFileExist)
912
import System.FilePath ((</>), (<.>))
1013

14+
import Echidna.Campaign (pushCampaignEvent)
15+
import Echidna.Types.Config
16+
import Echidna.Types.Campaign
17+
import Echidna.Types.Test (EchidnaTest(..))
1118
import Echidna.Types.Tx (Tx)
1219
import Echidna.Utility (listDirectory, withCurrentDirectory)
1320

1421
saveTxs :: FilePath -> [[Tx]] -> IO ()
1522
saveTxs dir = mapM_ saveTxSeq where
1623
saveTxSeq txSeq = do
17-
let file = dir </> (show . hash . show) txSeq <.> "txt"
24+
createDirectoryIfMissing True dir
25+
let file = dir </> (show . abs . hash . show) txSeq <.> "txt"
1826
unlessM (doesFileExist file) $ encodeFile file (toJSON txSeq)
1927

2028
loadTxs :: FilePath -> IO [[Tx]]
@@ -26,3 +34,31 @@ loadTxs dir = do
2634
putStrLn ("Loaded " ++ show (length txSeqs) ++ " transaction sequences from " ++ dir)
2735
pure txSeqs
2836
where readCall f = decodeStrict <$> BS.readFile f
37+
38+
-- Save corpus/reproducers transactions based on an event
39+
saveCorpusEvent :: Env -> (LocalTime, CampaignEvent) -> IO ()
40+
saveCorpusEvent env (_time, campaignEvent) = do
41+
case env.cfg.campaignConf.corpusDir of
42+
Just corpusDir -> saveEvent corpusDir campaignEvent
43+
Nothing -> pure ()
44+
where
45+
saveEvent dir (WorkerEvent _workerId event) =
46+
maybe (pure ()) (saveFile dir) $ getEventInfo event
47+
saveEvent _ _ = pure ()
48+
49+
getEventInfo = \case
50+
-- TODO: We save intermediate reproducers in separate directories.
51+
-- This is to because there can be a lot of them and we want to skip
52+
-- loading those on startup. Ideally, we should override the same file
53+
-- with a better version of a reproducer, this is smaller or more optimized.
54+
TestFalsified test -> Just ("reproducers-unshrunk", test.reproducer)
55+
TestOptimized test -> Just ("reproducers-optimizations", test.reproducer)
56+
NewCoverage { transactions } -> Just ("coverage", transactions)
57+
_ -> Nothing
58+
59+
saveFile dir (subdir, txs) =
60+
unless (null txs) $
61+
handle exceptionHandler $ saveTxs (dir </> subdir) [txs]
62+
63+
exceptionHandler (e :: IOException) =
64+
pushCampaignEvent env (Failure $ "Problem while writing to file: " ++ show e)

lib/Echidna/Server.hs

Lines changed: 17 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -10,17 +10,21 @@ import Data.Word (Word16)
1010
import Network.Wai.EventSource (ServerEvent(..), eventSourceAppIO)
1111
import Network.Wai.Handler.Warp (run)
1212

13-
import Echidna.Types.Campaign (CampaignEvent (..))
13+
import Echidna.Types.Campaign
1414
import Echidna.Types.Config (Env(..))
1515

16-
newtype SSE = SSE (Int, LocalTime, CampaignEvent)
16+
newtype SSE = SSE (LocalTime, CampaignEvent)
1717

1818
instance ToJSON SSE where
19-
toJSON (SSE (workerId, time, event)) =
19+
toJSON (SSE (time, WorkerEvent workerId event)) =
2020
object [ "worker" .= workerId
2121
, "timestamp" .= time
2222
, "data" .= event
2323
]
24+
toJSON (SSE (time, Failure reason)) =
25+
object [ "timestamp" .= time
26+
, "data" .= reason
27+
]
2428

2529
runSSEServer :: MVar () -> Env -> Word16 -> Int -> IO ()
2630
runSSEServer serverStopVar env port nworkers = do
@@ -32,15 +36,18 @@ runSSEServer serverStopVar env port nworkers = do
3236
if aliveNow == 0 then
3337
pure CloseEvent
3438
else do
35-
event@(_, _, campaignEvent) <- readChan sseChan
39+
event@(_, campaignEvent) <- readChan sseChan
3640
let eventName = \case
37-
TestFalsified _ -> "test_falsified"
38-
TestOptimized _ -> "test_optimized"
39-
NewCoverage {} -> "new_coverage"
40-
TxSequenceReplayed _ _ -> "tx_sequence_replayed"
41-
WorkerStopped _ -> "worker_stopped"
41+
WorkerEvent _ workerEvent ->
42+
case workerEvent of
43+
TestFalsified _ -> "test_falsified"
44+
TestOptimized _ -> "test_optimized"
45+
NewCoverage {} -> "new_coverage"
46+
TxSequenceReplayed _ _ -> "tx_sequence_replayed"
47+
WorkerStopped _ -> "worker_stopped"
48+
Failure _err -> "failure"
4249
case campaignEvent of
43-
WorkerStopped _ -> do
50+
WorkerEvent _ (WorkerStopped _) -> do
4451
aliveAfter <- atomicModifyIORef' aliveRef (\n -> (n-1, n-1))
4552
when (aliveAfter == 0) $ putMVar serverStopVar ()
4653
_ -> pure ()

lib/Echidna/Types/Campaign.hs

Lines changed: 25 additions & 13 deletions
Original file line numberDiff line numberDiff line change
@@ -45,22 +45,28 @@ data CampaignConf = CampaignConf
4545
-- ^ Server-Sent Events HTTP port number, if missing server is not ran
4646
}
4747

48+
type WorkerId = Int
49+
4850
data CampaignEvent
51+
= WorkerEvent WorkerId WorkerEvent
52+
| Failure String
53+
54+
data WorkerEvent
4955
= TestFalsified !EchidnaTest
5056
| TestOptimized !EchidnaTest
51-
| NewCoverage !Int !Int !Int
57+
| NewCoverage { points :: !Int, numCodehashes :: !Int, corpusSize :: !Int, transactions :: [Tx] }
5258
| TxSequenceReplayed !Int !Int
5359
| WorkerStopped WorkerStopReason
5460
-- ^ This is a terminal event. Worker exits and won't push any events after
5561
-- this one
5662
deriving Show
5763

58-
instance ToJSON CampaignEvent where
64+
instance ToJSON WorkerEvent where
5965
toJSON = \case
6066
TestFalsified test -> toJSON test
6167
TestOptimized test -> toJSON test
62-
NewCoverage coverage numContracts corpusSize ->
63-
object [ "coverage" .= coverage, "contracts" .= numContracts, "corpus_size" .= corpusSize]
68+
NewCoverage { points, numCodehashes, corpusSize } ->
69+
object [ "coverage" .= points, "contracts" .= numCodehashes, "corpus_size" .= corpusSize]
6470
TxSequenceReplayed current total -> object [ "current" .= current, "total" .= total ]
6571
WorkerStopped reason -> object [ "reason" .= show reason ]
6672

@@ -74,20 +80,20 @@ data WorkerStopReason
7480

7581
ppCampaignEvent :: CampaignEvent -> String
7682
ppCampaignEvent = \case
83+
WorkerEvent _ e -> ppWorkerEvent e
84+
Failure err -> err
85+
86+
ppWorkerEvent :: WorkerEvent -> String
87+
ppWorkerEvent = \case
7788
TestFalsified test ->
78-
let name = case test.testType of
79-
PropertyTest n _ -> n
80-
AssertionTest _ n _ -> encodeSig n
81-
CallTest n _ -> n
82-
_ -> error "impossible"
83-
in "Test " <> T.unpack name <> " falsified!"
89+
"Test " <> T.unpack (showTest test) <> " falsified!"
8490
TestOptimized test ->
8591
let name = case test.testType of OptimizationTest n _ -> n; _ -> error "fixme"
8692
in "New maximum value of " <> T.unpack name <> ": " <> show test.value
87-
NewCoverage points codehashes corpus ->
93+
NewCoverage { points, numCodehashes, corpusSize } ->
8894
"New coverage: " <> show points <> " instr, "
89-
<> show codehashes <> " contracts, "
90-
<> show corpus <> " seqs in corpus"
95+
<> show numCodehashes <> " contracts, "
96+
<> show corpusSize <> " seqs in corpus"
9197
TxSequenceReplayed current total ->
9298
"Sequence replayed from corpus (" <> show current <> "/" <> show total <> ")"
9399
WorkerStopped TestLimitReached ->
@@ -102,6 +108,12 @@ ppCampaignEvent = \case
102108
"Crashed:\n\n" <>
103109
e <>
104110
"\n\nPlease report it to https://github.com/crytic/echidna/issues"
111+
where
112+
showTest test = case test.testType of
113+
PropertyTest n _ -> n
114+
AssertionTest _ n _ -> encodeSig n
115+
CallTest n _ -> n
116+
_ -> error "impossible"
105117

106118
-- | The state of a fuzzing campaign.
107119
data WorkerState = WorkerState

lib/Echidna/Types/Config.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -65,7 +65,7 @@ data Env = Env
6565

6666
-- | Shared between all workers. Events are fairly rare so contention is
6767
-- minimal.
68-
, eventQueue :: Chan (Int, LocalTime, CampaignEvent)
68+
, eventQueue :: Chan (LocalTime, CampaignEvent)
6969

7070
, testsRef :: IORef [EchidnaTest]
7171
, coverageRef :: IORef CoverageMap

0 commit comments

Comments
 (0)