-- SPDX-FileCopyrightText: 2021 Oxhead Alpha -- SPDX-License-Identifier: LicenseRef-MIT-OA {-# OPTIONS_HADDOCK not-home #-} -- | This module declares all options/flags that @tasty@ will -- parse from the command line/environment variables. -- -- They're used to configure "Test.Cleveland". module Test.Cleveland.Tasty.Internal.Options ( clevelandOptions , MoneybagAliasOpt(..) , EndpointOpt(..) , PathOpt(..) , DataDirOpt(..) , VerboseOpt(..) , SecretKeyOpt(..) , RunModeOpt(..) , ContextLinesOpt(..) ) where import Control.Monad.Except (runExcept) import Data.Tagged (untag) import Options.Applicative qualified as Opt import Options.Applicative.Types (Parser, ReadM(..)) import Servant.Client.Core (BaseUrl(..)) import Test.Tasty.Options as Tasty (IsOption(..), OptionDescription(Option), safeRead) import Morley.Client.Parser (baseUrlReader) import Morley.Tezos.Address.Alias import Morley.Tezos.Crypto qualified as Crypto import Morley.Util.CLI (HasCLReader(getMetavar, getReader)) -- $defaultValues -- -- Tasty will use 'optionCLParser' to attempt to parse options from the command line. -- If it fails, it will try to parse them from environment variables instead (using 'parseValue'). -- -- For this reason, it's important that 'optionCLParser' is NOT a parser -- that /always/ succeeds. If it is, tasty will not attempt to read environment variables. -- -- From the [docs](http://hackage.haskell.org/package/tasty-1.3.1/docs/Test-Tasty-Options.html#v:optionCLParser): -- -- > Do not supply a default value (e.g., with the value function) here for this parser! -- > This is because if no value was provided on the command line we may lookup the option e.g. -- > in the environment. But if the parser always succeeds, we have no way to tell -- > whether the user really provided the option on the command line. -- | A list with all the options needed to configure "Test.Cleveland". clevelandOptions :: [OptionDescription] clevelandOptions = [ Tasty.Option (Proxy @EndpointOpt) , Tasty.Option (Proxy @PathOpt) , Tasty.Option (Proxy @DataDirOpt) , Tasty.Option (Proxy @VerboseOpt) , Tasty.Option (Proxy @SecretKeyOpt) , Tasty.Option (Proxy @MoneybagAliasOpt) , Tasty.Option (Proxy @RunModeOpt) , Tasty.Option (Proxy @ContextLinesOpt) ] ---------------------------------------------------------------------------- -- Morley Client options ---------------------------------------------------------------------------- -- | Morley Client option specifying endpoint URL of the Tezos node. newtype EndpointOpt = EndpointOpt (Maybe BaseUrl) deriving stock (Show, Eq) instance IsOption EndpointOpt where defaultValue = EndpointOpt Nothing optionName = "cleveland-node-endpoint" optionHelp = "[Test.Cleveland] Remote node endpoint URL" parseValue = mkParseValueWithReadM baseUrlReader (EndpointOpt . Just) optionCLParser = mkOptionParserWithReadM baseUrlReader "URL" (EndpointOpt . Just) (Just 'E') newtype PathOpt = PathOpt FilePath deriving stock (Show, Eq) instance IsOption PathOpt where defaultValue = PathOpt "octez-client" optionName = "cleveland-client-path" optionHelp = "[Test.Cleveland] Path to `octez-client` binary" parseValue = mkParseValue PathOpt optionCLParser = mkOptionParser PathOpt (Just 'I') newtype DataDirOpt = DataDirOpt (Maybe FilePath) deriving stock (Show, Eq) instance IsOption DataDirOpt where defaultValue = DataDirOpt Nothing optionName = "cleveland-data-dir" optionHelp = "[Test.Cleveland] Path to `octez-client` data directory" parseValue = mkParseValue (DataDirOpt . Just) optionCLParser = mkOptionParser (DataDirOpt . Just) (Just 'd') -- | To increase verbosity, pass @-V@ several times on the command line (e.g. @-VVV@), -- or set @TASTY_CLEVELAND_VERBOSE=3@ as an environment variable. newtype VerboseOpt = VerboseOpt Word deriving stock (Show, Eq) instance IsOption VerboseOpt where defaultValue = VerboseOpt 0 optionName = "cleveland-verbose" optionHelp = "[Test.Cleveland] Increase verbosity (pass several times to increase further)" parseValue = \str -> VerboseOpt <$> safeRead str optionCLParser = -- See: $defaultValues -- -- Therefore, we use `some` instead of `many` here. -- `some` will fail if "-V" is absent, and then tasty will attempt -- to parse the "TASTY_CLEVELAND_VERBOSE" env variable instead. VerboseOpt . genericLength <$> some flag where flag = Opt.flag' () . mconcat $ [ Opt.short 'V' , Opt.long (untag (optionName @VerboseOpt)) , Opt.help (untag (optionHelp @VerboseOpt)) ] ---------------------------------------------------------------------------- -- cleveland options ---------------------------------------------------------------------------- newtype SecretKeyOpt = SecretKeyOpt (Maybe Crypto.SecretKey) deriving stock (Show, Eq) instance IsOption SecretKeyOpt where defaultValue = SecretKeyOpt Nothing optionName = "cleveland-moneybag-secret-key" optionHelp = "[Test.Cleveland] Secret key of the account to be used to execute all transfers/originations " <> "(unless overriden with `withSender`) and fund new accounts (unless overriden with `withMoneybag`)." parseValue = mkParseValue (SecretKeyOpt . Just) optionCLParser = mkOptionParser (SecretKeyOpt . Just) Nothing newtype MoneybagAliasOpt = MoneybagAliasOpt ImplicitAlias deriving stock (Show, Eq) instance IsOption MoneybagAliasOpt where defaultValue = MoneybagAliasOpt $ ImplicitAlias "moneybag" optionName = "cleveland-moneybag-alias" optionHelp = "[Test.Cleveland] Alias of the account to be used to execute all transfers/originations " <> "(unless overriden with `withSender`) and fund new accounts (unless overriden with `withMoneybag`)." parseValue = Just . MoneybagAliasOpt . ImplicitAlias . fromString data RunModeOpt = RunAllMode | OnlyNetworkMode | DisableNetworkMode | DefaultMode instance IsOption RunModeOpt where defaultValue = DefaultMode optionName = "cleveland-mode" optionHelp = "[Test.Cleveland] Determines whether tests on a Tezos network\ \and Morley.Michelson emulator should run. \ \The following modes are supported:\ \ 1) 'all' — run both network and emulator tests. Also, all non-cleveland \ \ tests are run as well.\ \ 2) 'only-network' — run only network tests, this mod is a short version of\ \ '--pattern \"$1 == \"On network\" || $NF == \"On network\" || $0 ~ /.On network./\"'.\ \ Non-cleveland tests will be disabled as well.\ \ 3) 'disable-network' — disable network tests and run only emulator\ \ and non-cleveland tests.\ \\ \In case no mode is provided, the behaviour of this option depends on whether\ \the 'CI' environment variable is set: \ \ * In case 'CI' is set, the default behaviour is 'all'\ \ * In case 'CI' is unset, the default behaviour is 'disable-network'" parseValue str = case str of "all" -> Just RunAllMode "only-network" -> Just OnlyNetworkMode "disable-network" -> Just DisableNetworkMode _ -> Nothing newtype ContextLinesOpt = ContextLinesOpt Natural deriving stock (Show, Eq) instance IsOption ContextLinesOpt where defaultValue = ContextLinesOpt 5 optionName = "cleveland-context-lines" optionHelp = "[Test.Cleveland] Number of source code lines to show around an error when a test fails" parseValue = mkParseValue ContextLinesOpt optionCLParser = mkOptionParser ContextLinesOpt Nothing ---------------------------------------------------------------------------- -- Helpers ---------------------------------------------------------------------------- -- Create an environment variable parser for types that don't have a -- 'HasCLReader' instance to avoid adding an unnecessary dependency. mkParseValueWithReadM :: forall v a. ReadM a -> (a -> v) -> String -> Maybe v mkParseValueWithReadM readm wrap = fmap wrap . rightToMaybe . runExcept . runReaderT (unReadM readm) -- | Create an environment variable parser by reusing an instance of `HasCLReader`. mkParseValue :: forall v a . HasCLReader a => (a -> v) -> String -> Maybe v mkParseValue = mkParseValueWithReadM (getReader @a) -- | Build a command line option parser by reusing an instance of `IsOption`, -- for types that don't have an instance of 'HasCLReader'. mkOptionParserWithReadM :: forall v a . IsOption v => ReadM a -> String -- ^ metavar -> (a -> v) -> Maybe Char -> Parser v mkOptionParserWithReadM readm metav wrap shortMb = wrap <$> Opt.option readm mods where -- See: $defaultValues -- -- Therefore, we never specify a default value here. mods = mconcat [ Opt.metavar metav , maybe mempty Opt.short shortMb , Opt.long (untag (optionName @v)) , Opt.help (untag (optionHelp @v)) ] -- | Build a command line option parser by reusing instances of `HasCLReader` and `IsOption` mkOptionParser :: forall v a . (IsOption v, HasCLReader a) => (a -> v) -> Maybe Char -> Parser v mkOptionParser = mkOptionParserWithReadM (getReader @a) (getMetavar @a)