Skip to content
Draft
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
4 changes: 4 additions & 0 deletions lib/Echidna/Utility.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,6 +4,7 @@ import Control.Monad (unless)
import Control.Monad.Catch (bracket)
import Data.Time (diffUTCTime, getCurrentTime, zonedTimeToLocalTime, LocalTime, getZonedTime)
import Data.Time.Format (defaultTimeLocale, formatTime)
import Language.Haskell.TH
import System.Directory (getDirectoryContents, getCurrentDirectory, setCurrentDirectory)
import System.IO (hFlush, stdout)

Expand Down Expand Up @@ -38,3 +39,6 @@ withCurrentDirectory dir action =
bracket getCurrentDirectory setCurrentDirectory $ \_ -> do
setCurrentDirectory dir
action

includeFile :: FilePath -> Q Exp
includeFile fp = LitE . StringL <$> runIO (readFile fp)
1 change: 1 addition & 0 deletions package.yaml
Original file line number Diff line number Diff line change
Expand Up @@ -67,6 +67,7 @@ library:
- signal
- split
- strip-ansi-escape
- template-haskell
- time
- unliftio
- unliftio-core
Expand Down
46 changes: 37 additions & 9 deletions src/Main.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,5 @@
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE TemplateHaskell #-}

module Main where

Expand Down Expand Up @@ -47,11 +48,27 @@
import Echidna.Types.Test (TestMode, EchidnaTest(..))
import Echidna.UI
import Echidna.UI.Report (ppFailWithTraces, ppTestName)
import Echidna.Utility (measureIO)
import Echidna.Utility (includeFile, measureIO)

main :: IO ()
main = withUtf8 $ withCP65001 $ do
opts@Options{..} <- execParser optsParser
cli <- execParser cliParser
case cli of
InitCommand -> do
let config = "echidna.yaml"
configExists <- doesFileExist config
if configExists
then do
putStrLn $ "Config file " <> config <> " already exists."
exitWith (ExitFailure 1)
else do
writeFile config $(includeFile "tests/solidity/basic/default.yaml")
putStrLn $ "Sample config file written to " <> config
FuzzCommand fuzzOpts ->
fuzz fuzzOpts

fuzz :: FuzzOptions -> IO ()
fuzz opts@FuzzOptions {..} = do
EConfigWithUsage loadedCfg ks _ <-
maybe (pure (EConfigWithUsage defaultConfig mempty mempty)) parseConfig cliConfigFilepath
cfg <- overrideConfig loadedCfg opts
Expand Down Expand Up @@ -118,7 +135,11 @@

if isSuccessful tests then exitSuccess else exitWith (ExitFailure 1)

data Options = Options
data CLI
= InitCommand
| FuzzCommand FuzzOptions

data FuzzOptions = FuzzOptions
{ cliFilePath :: NE.NonEmpty FilePath
, cliWorkers :: Maybe Word8
, cliServerPort :: Maybe Word16
Expand Down Expand Up @@ -147,8 +168,8 @@
, cliSymExecNSolvers :: Maybe Int
}

optsParser :: ParserInfo Options
optsParser = info (helper <*> versionOption <*> options) $ fullDesc
cliParser :: ParserInfo CLI
cliParser = info (helper <*> versionOption <*> commands) $ fullDesc
<> progDesc "EVM property-based testing framework"
<> header "Echidna"

Expand All @@ -158,8 +179,15 @@
f "false" = Just False
f _ = Nothing

options :: Parser Options
options = Options . NE.fromList
where

Check failure on line 182 in src/Main.hs

View workflow job for this annotation

GitHub Actions / Build Echidna on windows-latest

|
commands = subparser $
command "init" (info (pure InitCommand)
(progDesc "Write a sample config file to echidna.yaml"))
<> command "fuzz" (info (FuzzCommand <$> fuzzOptions)
(progDesc "Run fuzzing"))

fuzzOptions :: Parser FuzzOptions
fuzzOptions = FuzzOptions
<$> some (argument str (metavar "FILES"
<> help "Solidity files to analyze"))
<*> optional (option auto $ long "workers"
Expand Down Expand Up @@ -240,8 +268,8 @@
("Echidna " ++ showVersion version)
(long "version" <> help "Show version")

overrideConfig :: EConfig -> Options -> IO EConfig
overrideConfig config Options{..} = do
overrideConfig :: EConfig -> FuzzOptions -> IO EConfig
overrideConfig config FuzzOptions{..} = do
envRpcUrl <- Onchain.rpcUrlEnv
envRpcBlock <- Onchain.rpcBlockEnv
envEtherscanApiKey <- Onchain.etherscanApiKey
Expand Down
Loading