11{-# LANGUAGE RecordWildCards #-}
2+ {-# LANGUAGE TemplateHaskell #-}
23
34module Main where
45
@@ -47,11 +48,27 @@ import Echidna.Types.Solidity
4748import Echidna.Types.Test (TestMode , EchidnaTest (.. ))
4849import Echidna.UI
4950import Echidna.UI.Report (ppFailWithTraces , ppTestName )
50- import Echidna.Utility (measureIO )
51+ import Echidna.Utility (includeFile , measureIO )
5152
5253main :: IO ()
5354main = withUtf8 $ withCP65001 $ do
54- opts@ Options {.. } <- execParser optsParser
55+ cli <- execParser cliParser
56+ case cli of
57+ InitCommand -> do
58+ let config = " echidna.yaml"
59+ configExists <- doesFileExist config
60+ if configExists
61+ then do
62+ putStrLn $ " Config file " <> config <> " already exists."
63+ exitWith (ExitFailure 1 )
64+ else do
65+ writeFile config $ (includeFile " tests/solidity/basic/default.yaml" )
66+ putStrLn $ " Sample config file written to " <> config
67+ FuzzCommand fuzzOpts ->
68+ fuzz fuzzOpts
69+
70+ fuzz :: FuzzOptions -> IO ()
71+ fuzz opts@ FuzzOptions {.. } = do
5572 EConfigWithUsage loadedCfg ks _ <-
5673 maybe (pure (EConfigWithUsage defaultConfig mempty mempty )) parseConfig cliConfigFilepath
5774 cfg <- overrideConfig loadedCfg opts
@@ -118,7 +135,11 @@ main = withUtf8 $ withCP65001 $ do
118135
119136 if isSuccessful tests then exitSuccess else exitWith (ExitFailure 1 )
120137
121- data Options = Options
138+ data CLI
139+ = InitCommand
140+ | FuzzCommand FuzzOptions
141+
142+ data FuzzOptions = FuzzOptions
122143 { cliFilePath :: NE. NonEmpty FilePath
123144 , cliWorkers :: Maybe Word8
124145 , cliServerPort :: Maybe Word16
@@ -147,8 +168,8 @@ data Options = Options
147168 , cliSymExecNSolvers :: Maybe Int
148169 }
149170
150- optsParser :: ParserInfo Options
151- optsParser = info (helper <*> versionOption <*> options ) $ fullDesc
171+ cliParser :: ParserInfo CLI
172+ cliParser = info (helper <*> versionOption <*> commands ) $ fullDesc
152173 <> progDesc " EVM property-based testing framework"
153174 <> header " Echidna"
154175
@@ -158,8 +179,15 @@ bool = maybeReader (f . map toLower) where
158179 f " false" = Just False
159180 f _ = Nothing
160181
161- options :: Parser Options
162- options = Options . NE. fromList
182+ where
183+ commands = subparser $
184+ command " init" (info (pure InitCommand )
185+ (progDesc " Write a sample config file to echidna.yaml" ))
186+ <> command " fuzz" (info (FuzzCommand <$> fuzzOptions)
187+ (progDesc " Run fuzzing" ))
188+
189+ fuzzOptions :: Parser FuzzOptions
190+ fuzzOptions = FuzzOptions
163191 <$> some (argument str (metavar " FILES"
164192 <> help " Solidity files to analyze" ))
165193 <*> optional (option auto $ long " workers"
@@ -240,8 +268,8 @@ versionOption = infoOption
240268 (" Echidna " ++ showVersion version)
241269 (long " version" <> help " Show version" )
242270
243- overrideConfig :: EConfig -> Options -> IO EConfig
244- overrideConfig config Options {.. } = do
271+ overrideConfig :: EConfig -> FuzzOptions -> IO EConfig
272+ overrideConfig config FuzzOptions {.. } = do
245273 envRpcUrl <- Onchain. rpcUrlEnv
246274 envRpcBlock <- Onchain. rpcBlockEnv
247275 envEtherscanApiKey <- Onchain. etherscanApiKey
0 commit comments