Skip to content
Merged
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
1 change: 1 addition & 0 deletions lib/Echidna/Config.hs
Original file line number Diff line number Diff line change
Expand Up @@ -55,6 +55,7 @@ instance FromJSON EConfigWithUsage where
<*> testConfParser
<*> txConfParser
<*> (UIConf <$> v ..:? "timeout" <*> formatParser)
<*> v ..:? "allEvents" ..!= False
<*> v ..:? "rpcUrl"
<*> v ..:? "rpcBlock"
<*> v ..:? "etherscanApiKey"
Expand Down
3 changes: 2 additions & 1 deletion lib/Echidna/Exec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -90,7 +90,8 @@ execTxWith executeTx tx = do
if hasSelfdestructed vm tx.dst then
pure $ VMFailure (Revert (ConcreteBuf ""))
else do
#traces .= emptyEvents
config <- asks (.cfg)
when (not config.allEvents) $ #traces .= emptyEvents
vmBeforeTx <- get
setupTx tx
case tx.call of
Expand Down
1 change: 1 addition & 0 deletions lib/Echidna/Types/Config.hs
Original file line number Diff line number Diff line change
Expand Up @@ -44,6 +44,7 @@ data EConfig = EConfig
, txConf :: TxConf
, uiConf :: UIConf

, allEvents :: Bool
, rpcUrl :: Maybe Text
, rpcBlock :: Maybe Word64
, etherscanApiKey :: Maybe Text
Expand Down
21 changes: 3 additions & 18 deletions src/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,7 +2,7 @@

module Main where

import Control.Monad (unless, forM_, when)
import Control.Monad (unless, forM_)
import Control.Monad.Reader (runReaderT, liftIO)
import Control.Monad.Random (getRandomR)
import Data.Aeson.Key qualified as Aeson.Key
Expand All @@ -12,7 +12,7 @@ import Data.Hashable (hash)
import Data.IORef (readIORef)
import Data.List.NonEmpty qualified as NE
import Data.Map qualified as Map
import Data.Maybe (fromMaybe, isJust)
import Data.Maybe (fromMaybe)
import Data.Set qualified as Set
import Data.Text (Text)
import Data.Text qualified as T
Expand All @@ -24,7 +24,6 @@ import Main.Utf8 (withUtf8)
import Options.Applicative
import Paths_echidna (version)
import System.Directory (createDirectoryIfMissing)
import System.Environment (lookupEnv)
import System.Exit (exitWith, exitSuccess, ExitCode(..))
import System.FilePath ((</>), (<.>))
import System.IO (hPutStrLn, stderr)
Expand All @@ -42,13 +41,12 @@ import Echidna.Output.Corpus
import Echidna.Output.Foundry
import Echidna.Output.Source
import Echidna.Solidity (compileContracts)
import Echidna.Test (reproduceTest, validateTestMode)
import Echidna.Test (validateTestMode)
import Echidna.Types.Campaign
import Echidna.Types.Config
import Echidna.Types.Solidity
import Echidna.Types.Test (TestMode, EchidnaTest(..), TestType(..), TestState(..))
import Echidna.UI
import Echidna.UI.Report (ppFailWithTraces, ppTestName)
import Echidna.Utility (measureIO)

main :: IO ()
Expand Down Expand Up @@ -86,19 +84,6 @@ main = withUtf8 $ withCP65001 $ do
measureIO cfg.solConf.quiet "Saving test reproducers" $
saveTxs env (dir </> "reproducers") (filter (not . null) $ (.reproducer) <$> tests)

saveTracesEnabled <- lookupEnv "ECHIDNA_SAVE_TRACES"
when (isJust saveTracesEnabled) $ do
measureIO cfg.solConf.quiet "Saving test reproducers-traces" $ do
flip runReaderT env $ do
forM_ tests $ \test ->
unless (null test.reproducer) $ do
(results, finalVM) <- reproduceTest vm test
let subdir = dir </> "reproducers-traces"
liftIO $ createDirectoryIfMissing True subdir
let file = subdir </> (show . abs . hash) test.reproducer <.> "txt"
txsPrinted <- ppFailWithTraces Nothing finalVM results
liftIO $ writeFile file (ppTestName test <> ": " <> txsPrinted)

measureIO cfg.solConf.quiet "Saving corpus" $ do
corpus <- readIORef env.corpusRef
saveTxs env (dir </> "coverage") (snd <$> Set.toList corpus)
Expand Down
2 changes: 2 additions & 0 deletions tests/solidity/basic/default.yaml
Original file line number Diff line number Diff line change
Expand Up @@ -98,6 +98,8 @@ rpcBlock: null
etherscanApiKey: null
# number of workers. By default (unset) its value is the clamp of the number cores between 1 and 4
workers: null
# show all events from all the transactions, not just the last one
allEvents: false
# events server port
server: null
# whether to add an additional symbolic execution worker
Expand Down