{-# LANGUAGE CPP #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TypeOperators #-}

module Test.Sandwich.ArgParsing where

import Control.Monad.Logger
import Data.Function
import qualified Data.List as L
import Data.Maybe
import qualified Data.Text as T
import Data.Time.Clock.POSIX
import Data.Typeable
import Options.Applicative
import qualified Options.Applicative as OA
import Safe
import Test.Sandwich.Formatters.FailureReport
import Test.Sandwich.Formatters.MarkdownSummary
import Test.Sandwich.Formatters.Print.Types
import Test.Sandwich.Formatters.Silent
import Test.Sandwich.Formatters.TerminalUI
import Test.Sandwich.Formatters.TerminalUI.Types
import Test.Sandwich.Internal.Running
import Test.Sandwich.Options
import Test.Sandwich.Types.ArgParsing
import Test.Sandwich.Types.RunTree
import Test.Sandwich.Types.Spec

#if MIN_VERSION_time(1,9,0)
import Data.Time.Format.ISO8601
formatTime :: UTCTime -> String
formatTime = Text -> String
T.unpack (Text -> String) -> (UTCTime -> Text) -> UTCTime -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HasCallStack => Text -> Text -> Text -> Text
Text -> Text -> Text -> Text
T.replace Text
":" Text
"_" (Text -> Text) -> (UTCTime -> Text) -> UTCTime -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
T.pack (String -> Text) -> (UTCTime -> String) -> UTCTime -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UTCTime -> String
forall t. ISO8601 t => t -> String
iso8601Show
#else
formatTime = show
#endif


commandLineOptionsWithInfo :: Parser a -> Parser (Maybe IndividualTestModule) -> ParserInfo (CommandLineOptions a)
commandLineOptionsWithInfo :: forall a.
Parser a
-> Parser (Maybe IndividualTestModule)
-> ParserInfo (CommandLineOptions a)
commandLineOptionsWithInfo Parser a
userOptionsParser Parser (Maybe IndividualTestModule)
individualTestParser = Parser (CommandLineOptions a)
-> InfoMod (CommandLineOptions a)
-> ParserInfo (CommandLineOptions a)
forall a. Parser a -> InfoMod a -> ParserInfo a
OA.info (Parser a
-> Parser (Maybe IndividualTestModule)
-> Parser (CommandLineOptions a)
forall a.
Parser a
-> Parser (Maybe IndividualTestModule)
-> Parser (CommandLineOptions a)
mainCommandLineOptions Parser a
userOptionsParser Parser (Maybe IndividualTestModule)
individualTestParser Parser (CommandLineOptions a)
-> Parser (CommandLineOptions a -> CommandLineOptions a)
-> Parser (CommandLineOptions a)
forall (f :: * -> *) a b. Applicative f => f a -> f (a -> b) -> f b
<**> Parser (CommandLineOptions a -> CommandLineOptions a)
forall a. Parser (a -> a)
helper)
  (
    InfoMod (CommandLineOptions a)
forall a. InfoMod a
fullDesc
    InfoMod (CommandLineOptions a)
-> InfoMod (CommandLineOptions a) -> InfoMod (CommandLineOptions a)
forall a. Semigroup a => a -> a -> a
<> String -> InfoMod (CommandLineOptions a)
forall a. String -> InfoMod a
progDesc String
"Run tests with Sandwich"
    InfoMod (CommandLineOptions a)
-> InfoMod (CommandLineOptions a) -> InfoMod (CommandLineOptions a)
forall a. Semigroup a => a -> a -> a
<> String -> InfoMod (CommandLineOptions a)
forall a. String -> InfoMod a
header String
"Sandwich test runner"
  )

goldenOptionsWithInfo :: ParserInfo CommandLineGoldenOptions
goldenOptionsWithInfo :: ParserInfo CommandLineGoldenOptions
goldenOptionsWithInfo = Parser CommandLineGoldenOptions
-> InfoMod CommandLineGoldenOptions
-> ParserInfo CommandLineGoldenOptions
forall a. Parser a -> InfoMod a -> ParserInfo a
OA.info ((forall (f :: * -> *) a. Mod f a)
-> Parser CommandLineGoldenOptions
commandLineGoldenOptions Mod f a
forall a. Monoid a => a
forall (f :: * -> *) a. Mod f a
mempty Parser CommandLineGoldenOptions
-> Parser (CommandLineGoldenOptions -> CommandLineGoldenOptions)
-> Parser CommandLineGoldenOptions
forall (f :: * -> *) a b. Applicative f => f a -> f (a -> b) -> f b
<**> Parser (CommandLineGoldenOptions -> CommandLineGoldenOptions)
forall a. Parser (a -> a)
helper)
  (
    InfoMod CommandLineGoldenOptions
forall a. InfoMod a
briefDesc
    InfoMod CommandLineGoldenOptions
-> InfoMod CommandLineGoldenOptions
-> InfoMod CommandLineGoldenOptions
forall a. Semigroup a => a -> a -> a
<> String -> InfoMod CommandLineGoldenOptions
forall a. String -> InfoMod a
header String
"Special options used for golden testing."
  )

hedgehogOptionsWithInfo :: ParserInfo CommandLineHedgehogOptions
hedgehogOptionsWithInfo :: ParserInfo CommandLineHedgehogOptions
hedgehogOptionsWithInfo = Parser CommandLineHedgehogOptions
-> InfoMod CommandLineHedgehogOptions
-> ParserInfo CommandLineHedgehogOptions
forall a. Parser a -> InfoMod a -> ParserInfo a
OA.info ((forall (f :: * -> *) a. Mod f a)
-> Parser CommandLineHedgehogOptions
commandLineHedgehogOptions Mod f a
forall a. Monoid a => a
forall (f :: * -> *) a. Mod f a
mempty Parser CommandLineHedgehogOptions
-> Parser
     (CommandLineHedgehogOptions -> CommandLineHedgehogOptions)
-> Parser CommandLineHedgehogOptions
forall (f :: * -> *) a b. Applicative f => f a -> f (a -> b) -> f b
<**> Parser (CommandLineHedgehogOptions -> CommandLineHedgehogOptions)
forall a. Parser (a -> a)
helper)
  (
    InfoMod CommandLineHedgehogOptions
forall a. InfoMod a
briefDesc
    InfoMod CommandLineHedgehogOptions
-> InfoMod CommandLineHedgehogOptions
-> InfoMod CommandLineHedgehogOptions
forall a. Semigroup a => a -> a -> a
<> String -> InfoMod CommandLineHedgehogOptions
forall a. String -> InfoMod a
header String
"Special options used by sandwich-hedgehog.\n\nIf a flag is passed, it will override the value in the Hedgehog option configured in the code."
  )

quickCheckOptionsWithInfo :: ParserInfo CommandLineQuickCheckOptions
quickCheckOptionsWithInfo :: ParserInfo CommandLineQuickCheckOptions
quickCheckOptionsWithInfo = Parser CommandLineQuickCheckOptions
-> InfoMod CommandLineQuickCheckOptions
-> ParserInfo CommandLineQuickCheckOptions
forall a. Parser a -> InfoMod a -> ParserInfo a
OA.info ((forall (f :: * -> *) a. Mod f a)
-> Parser CommandLineQuickCheckOptions
commandLineQuickCheckOptions Mod f a
forall a. Monoid a => a
forall (f :: * -> *) a. Mod f a
mempty Parser CommandLineQuickCheckOptions
-> Parser
     (CommandLineQuickCheckOptions -> CommandLineQuickCheckOptions)
-> Parser CommandLineQuickCheckOptions
forall (f :: * -> *) a b. Applicative f => f a -> f (a -> b) -> f b
<**> Parser
  (CommandLineQuickCheckOptions -> CommandLineQuickCheckOptions)
forall a. Parser (a -> a)
helper)
  (
    InfoMod CommandLineQuickCheckOptions
forall a. InfoMod a
briefDesc
    InfoMod CommandLineQuickCheckOptions
-> InfoMod CommandLineQuickCheckOptions
-> InfoMod CommandLineQuickCheckOptions
forall a. Semigroup a => a -> a -> a
<> String -> InfoMod CommandLineQuickCheckOptions
forall a. String -> InfoMod a
header String
"Special options used by sandwich-quickcheck.\n\nIf a flag is passed, it will override the value in the QuickCheck option configured in the code."
  )

slackOptionsWithInfo :: ParserInfo CommandLineSlackOptions
slackOptionsWithInfo :: ParserInfo CommandLineSlackOptions
slackOptionsWithInfo = Parser CommandLineSlackOptions
-> InfoMod CommandLineSlackOptions
-> ParserInfo CommandLineSlackOptions
forall a. Parser a -> InfoMod a -> ParserInfo a
OA.info ((forall (f :: * -> *) a. Mod f a) -> Parser CommandLineSlackOptions
commandLineSlackOptions Mod f a
forall a. Monoid a => a
forall (f :: * -> *) a. Mod f a
mempty Parser CommandLineSlackOptions
-> Parser (CommandLineSlackOptions -> CommandLineSlackOptions)
-> Parser CommandLineSlackOptions
forall (f :: * -> *) a b. Applicative f => f a -> f (a -> b) -> f b
<**> Parser (CommandLineSlackOptions -> CommandLineSlackOptions)
forall a. Parser (a -> a)
helper)
  (
    InfoMod CommandLineSlackOptions
forall a. InfoMod a
briefDesc
    InfoMod CommandLineSlackOptions
-> InfoMod CommandLineSlackOptions
-> InfoMod CommandLineSlackOptions
forall a. Semigroup a => a -> a -> a
<> String -> InfoMod CommandLineSlackOptions
forall a. String -> InfoMod a
header String
"Special options passed to the Slack formatter.\n\nIf a flag is passed, it will override the value in the SlackFormatter configured in the code."
  )

webDriverOptionsWithInfo :: ParserInfo CommandLineWebdriverOptions
webDriverOptionsWithInfo :: ParserInfo CommandLineWebdriverOptions
webDriverOptionsWithInfo = Parser CommandLineWebdriverOptions
-> InfoMod CommandLineWebdriverOptions
-> ParserInfo CommandLineWebdriverOptions
forall a. Parser a -> InfoMod a -> ParserInfo a
OA.info ((forall (f :: * -> *) a. Mod f a)
-> Parser CommandLineWebdriverOptions
commandLineWebdriverOptions Mod f a
forall a. Monoid a => a
forall (f :: * -> *) a. Mod f a
mempty Parser CommandLineWebdriverOptions
-> Parser
     (CommandLineWebdriverOptions -> CommandLineWebdriverOptions)
-> Parser CommandLineWebdriverOptions
forall (f :: * -> *) a b. Applicative f => f a -> f (a -> b) -> f b
<**> Parser (CommandLineWebdriverOptions -> CommandLineWebdriverOptions)
forall a. Parser (a -> a)
helper)
  (
    InfoMod CommandLineWebdriverOptions
forall a. InfoMod a
fullDesc
    InfoMod CommandLineWebdriverOptions
-> InfoMod CommandLineWebdriverOptions
-> InfoMod CommandLineWebdriverOptions
forall a. Semigroup a => a -> a -> a
<> String -> InfoMod CommandLineWebdriverOptions
forall a. String -> InfoMod a
progDesc String
"Special options passed to the WebDriver formatter, if present.\n\nIf a flag is passed, it will override the value in the WdOptions configured in the code."
    InfoMod CommandLineWebdriverOptions
-> InfoMod CommandLineWebdriverOptions
-> InfoMod CommandLineWebdriverOptions
forall a. Semigroup a => a -> a -> a
<> String -> InfoMod CommandLineWebdriverOptions
forall a. String -> InfoMod a
header String
"WebDriver flags"
  )

mainCommandLineOptions :: Parser a -> Parser (Maybe IndividualTestModule) -> Parser (CommandLineOptions a)
mainCommandLineOptions :: forall a.
Parser a
-> Parser (Maybe IndividualTestModule)
-> Parser (CommandLineOptions a)
mainCommandLineOptions Parser a
userOptionsParser Parser (Maybe IndividualTestModule)
individualTestParser = FormatterType
-> Maybe LogLevel
-> Maybe Int
-> [String]
-> [String]
-> Int
-> Maybe String
-> Maybe Bool
-> Maybe String
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe IndividualTestModule
-> CommandLineGoldenOptions
-> CommandLineQuickCheckOptions
-> CommandLineHedgehogOptions
-> CommandLineSlackOptions
-> CommandLineWebdriverOptions
-> a
-> CommandLineOptions a
forall a.
FormatterType
-> Maybe LogLevel
-> Maybe Int
-> [String]
-> [String]
-> Int
-> Maybe String
-> Maybe Bool
-> Maybe String
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe IndividualTestModule
-> CommandLineGoldenOptions
-> CommandLineQuickCheckOptions
-> CommandLineHedgehogOptions
-> CommandLineSlackOptions
-> CommandLineWebdriverOptions
-> a
-> CommandLineOptions a
CommandLineOptions
  (FormatterType
 -> Maybe LogLevel
 -> Maybe Int
 -> [String]
 -> [String]
 -> Int
 -> Maybe String
 -> Maybe Bool
 -> Maybe String
 -> Maybe Bool
 -> Maybe Bool
 -> Maybe Bool
 -> Maybe Bool
 -> Maybe Bool
 -> Maybe Bool
 -> Maybe IndividualTestModule
 -> CommandLineGoldenOptions
 -> CommandLineQuickCheckOptions
 -> CommandLineHedgehogOptions
 -> CommandLineSlackOptions
 -> CommandLineWebdriverOptions
 -> a
 -> CommandLineOptions a)
-> Parser FormatterType
-> Parser
     (Maybe LogLevel
      -> Maybe Int
      -> [String]
      -> [String]
      -> Int
      -> Maybe String
      -> Maybe Bool
      -> Maybe String
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe IndividualTestModule
      -> CommandLineGoldenOptions
      -> CommandLineQuickCheckOptions
      -> CommandLineHedgehogOptions
      -> CommandLineSlackOptions
      -> CommandLineWebdriverOptions
      -> a
      -> CommandLineOptions a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser FormatterType
formatter
  Parser
  (Maybe LogLevel
   -> Maybe Int
   -> [String]
   -> [String]
   -> Int
   -> Maybe String
   -> Maybe Bool
   -> Maybe String
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe IndividualTestModule
   -> CommandLineGoldenOptions
   -> CommandLineQuickCheckOptions
   -> CommandLineHedgehogOptions
   -> CommandLineSlackOptions
   -> CommandLineWebdriverOptions
   -> a
   -> CommandLineOptions a)
-> Parser (Maybe LogLevel)
-> Parser
     (Maybe Int
      -> [String]
      -> [String]
      -> Int
      -> Maybe String
      -> Maybe Bool
      -> Maybe String
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe IndividualTestModule
      -> CommandLineGoldenOptions
      -> CommandLineQuickCheckOptions
      -> CommandLineHedgehogOptions
      -> CommandLineSlackOptions
      -> CommandLineWebdriverOptions
      -> a
      -> CommandLineOptions a)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser (Maybe LogLevel)
logLevel
  Parser
  (Maybe Int
   -> [String]
   -> [String]
   -> Int
   -> Maybe String
   -> Maybe Bool
   -> Maybe String
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe IndividualTestModule
   -> CommandLineGoldenOptions
   -> CommandLineQuickCheckOptions
   -> CommandLineHedgehogOptions
   -> CommandLineSlackOptions
   -> CommandLineWebdriverOptions
   -> a
   -> CommandLineOptions a)
-> Parser (Maybe Int)
-> Parser
     ([String]
      -> [String]
      -> Int
      -> Maybe String
      -> Maybe Bool
      -> Maybe String
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe IndividualTestModule
      -> CommandLineGoldenOptions
      -> CommandLineQuickCheckOptions
      -> CommandLineHedgehogOptions
      -> CommandLineSlackOptions
      -> CommandLineWebdriverOptions
      -> a
      -> CommandLineOptions a)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Int -> Parser (Maybe Int)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (ReadM Int -> Mod OptionFields Int -> Parser Int
forall a. ReadM a -> Mod OptionFields a -> Parser a
option ReadM Int
forall a. Read a => ReadM a
auto (String -> Mod OptionFields Int
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"visibility-threshold" Mod OptionFields Int
-> Mod OptionFields Int -> Mod OptionFields Int
forall a. Semigroup a => a -> a -> a
<> Char -> Mod OptionFields Int
forall (f :: * -> *) a. HasName f => Char -> Mod f a
short Char
'v' Mod OptionFields Int
-> Mod OptionFields Int -> Mod OptionFields Int
forall a. Semigroup a => a -> a -> a
<> Mod OptionFields Int
forall a (f :: * -> *). Show a => Mod f a
showDefault Mod OptionFields Int
-> Mod OptionFields Int -> Mod OptionFields Int
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields Int
forall (f :: * -> *) a. String -> Mod f a
help String
"Set the visibility threshold for formatters" Mod OptionFields Int
-> Mod OptionFields Int -> Mod OptionFields Int
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields Int
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
metavar String
"INT"))
  Parser
  ([String]
   -> [String]
   -> Int
   -> Maybe String
   -> Maybe Bool
   -> Maybe String
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe IndividualTestModule
   -> CommandLineGoldenOptions
   -> CommandLineQuickCheckOptions
   -> CommandLineHedgehogOptions
   -> CommandLineSlackOptions
   -> CommandLineWebdriverOptions
   -> a
   -> CommandLineOptions a)
-> Parser [String]
-> Parser
     ([String]
      -> Int
      -> Maybe String
      -> Maybe Bool
      -> Maybe String
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe IndividualTestModule
      -> CommandLineGoldenOptions
      -> CommandLineQuickCheckOptions
      -> CommandLineHedgehogOptions
      -> CommandLineSlackOptions
      -> CommandLineWebdriverOptions
      -> a
      -> CommandLineOptions a)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser String -> Parser [String]
forall a. Parser a -> Parser [a]
forall (f :: * -> *) a. Alternative f => f a -> f [a]
many (Mod OptionFields String -> Parser String
forall s. IsString s => Mod OptionFields s -> Parser s
strOption (String -> Mod OptionFields String
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"prune" Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<> Char -> Mod OptionFields String
forall (f :: * -> *) a. HasName f => Char -> Mod f a
short Char
'p' Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields String
forall (f :: * -> *) a. String -> Mod f a
help String
"Prune test subtrees by string matching text example labels. The matched test and all its children are removed. Pruning happens before filtering, if any" Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields String
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
metavar String
"STRING"))
  Parser
  ([String]
   -> Int
   -> Maybe String
   -> Maybe Bool
   -> Maybe String
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe IndividualTestModule
   -> CommandLineGoldenOptions
   -> CommandLineQuickCheckOptions
   -> CommandLineHedgehogOptions
   -> CommandLineSlackOptions
   -> CommandLineWebdriverOptions
   -> a
   -> CommandLineOptions a)
-> Parser [String]
-> Parser
     (Int
      -> Maybe String
      -> Maybe Bool
      -> Maybe String
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe IndividualTestModule
      -> CommandLineGoldenOptions
      -> CommandLineQuickCheckOptions
      -> CommandLineHedgehogOptions
      -> CommandLineSlackOptions
      -> CommandLineWebdriverOptions
      -> a
      -> CommandLineOptions a)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser String -> Parser [String]
forall a. Parser a -> Parser [a]
forall (f :: * -> *) a. Alternative f => f a -> f [a]
many (Mod OptionFields String -> Parser String
forall s. IsString s => Mod OptionFields s -> Parser s
strOption (String -> Mod OptionFields String
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"filter" Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<> Char -> Mod OptionFields String
forall (f :: * -> *) a. HasName f => Char -> Mod f a
short Char
'f' Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields String
forall (f :: * -> *) a. String -> Mod f a
help String
"Filter test tree by string matching text example labels. Filtering happens after pruning, if any" Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields String
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
metavar String
"STRING"))
  Parser
  (Int
   -> Maybe String
   -> Maybe Bool
   -> Maybe String
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe IndividualTestModule
   -> CommandLineGoldenOptions
   -> CommandLineQuickCheckOptions
   -> CommandLineHedgehogOptions
   -> CommandLineSlackOptions
   -> CommandLineWebdriverOptions
   -> a
   -> CommandLineOptions a)
-> Parser Int
-> Parser
     (Maybe String
      -> Maybe Bool
      -> Maybe String
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe IndividualTestModule
      -> CommandLineGoldenOptions
      -> CommandLineQuickCheckOptions
      -> CommandLineHedgehogOptions
      -> CommandLineSlackOptions
      -> CommandLineWebdriverOptions
      -> a
      -> CommandLineOptions a)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ReadM Int -> Mod OptionFields Int -> Parser Int
forall a. ReadM a -> Mod OptionFields a -> Parser a
option ReadM Int
forall a. Read a => ReadM a
auto (String -> Mod OptionFields Int
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"repeat" Mod OptionFields Int
-> Mod OptionFields Int -> Mod OptionFields Int
forall a. Semigroup a => a -> a -> a
<> Char -> Mod OptionFields Int
forall (f :: * -> *) a. HasName f => Char -> Mod f a
short Char
'r' Mod OptionFields Int
-> Mod OptionFields Int -> Mod OptionFields Int
forall a. Semigroup a => a -> a -> a
<> Mod OptionFields Int
forall a (f :: * -> *). Show a => Mod f a
showDefault Mod OptionFields Int
-> Mod OptionFields Int -> Mod OptionFields Int
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields Int
forall (f :: * -> *) a. String -> Mod f a
help String
"Repeat the test N times and report how many failures occur" Mod OptionFields Int
-> Mod OptionFields Int -> Mod OptionFields Int
forall a. Semigroup a => a -> a -> a
<> Int -> Mod OptionFields Int
forall (f :: * -> *) a. HasValue f => a -> Mod f a
value Int
1 Mod OptionFields Int
-> Mod OptionFields Int -> Mod OptionFields Int
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields Int
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
metavar String
"INT")
  Parser
  (Maybe String
   -> Maybe Bool
   -> Maybe String
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe IndividualTestModule
   -> CommandLineGoldenOptions
   -> CommandLineQuickCheckOptions
   -> CommandLineHedgehogOptions
   -> CommandLineSlackOptions
   -> CommandLineWebdriverOptions
   -> a
   -> CommandLineOptions a)
-> Parser (Maybe String)
-> Parser
     (Maybe Bool
      -> Maybe String
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe IndividualTestModule
      -> CommandLineGoldenOptions
      -> CommandLineQuickCheckOptions
      -> CommandLineHedgehogOptions
      -> CommandLineSlackOptions
      -> CommandLineWebdriverOptions
      -> a
      -> CommandLineOptions a)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser String -> Parser (Maybe String)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (Mod OptionFields String -> Parser String
forall s. IsString s => Mod OptionFields s -> Parser s
strOption (String -> Mod OptionFields String
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"fixed-root" Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields String
forall (f :: * -> *) a. String -> Mod f a
help String
"Store test artifacts at a fixed path" Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields String
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
metavar String
"STRING"))
  Parser
  (Maybe Bool
   -> Maybe String
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe IndividualTestModule
   -> CommandLineGoldenOptions
   -> CommandLineQuickCheckOptions
   -> CommandLineHedgehogOptions
   -> CommandLineSlackOptions
   -> CommandLineWebdriverOptions
   -> a
   -> CommandLineOptions a)
-> Parser (Maybe Bool)
-> Parser
     (Maybe String
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe IndividualTestModule
      -> CommandLineGoldenOptions
      -> CommandLineQuickCheckOptions
      -> CommandLineHedgehogOptions
      -> CommandLineSlackOptions
      -> CommandLineWebdriverOptions
      -> a
      -> CommandLineOptions a)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Bool -> Parser (Maybe Bool)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (Bool -> Bool -> Mod FlagFields Bool -> Parser Bool
forall a. a -> a -> Mod FlagFields a -> Parser a
flag Bool
False Bool
True (String -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"dry-run" Mod FlagFields Bool -> Mod FlagFields Bool -> Mod FlagFields Bool
forall a. Semigroup a => a -> a -> a
<> String -> Mod FlagFields Bool
forall (f :: * -> *) a. String -> Mod f a
help String
"Skip actually launching the tests. This is useful if you want to see the set of the tests that would be run, or start them manually in the terminal UI."))
  Parser
  (Maybe String
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe IndividualTestModule
   -> CommandLineGoldenOptions
   -> CommandLineQuickCheckOptions
   -> CommandLineHedgehogOptions
   -> CommandLineSlackOptions
   -> CommandLineWebdriverOptions
   -> a
   -> CommandLineOptions a)
-> Parser (Maybe String)
-> Parser
     (Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe IndividualTestModule
      -> CommandLineGoldenOptions
      -> CommandLineQuickCheckOptions
      -> CommandLineHedgehogOptions
      -> CommandLineSlackOptions
      -> CommandLineWebdriverOptions
      -> a
      -> CommandLineOptions a)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser String -> Parser (Maybe String)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (Mod OptionFields String -> Parser String
forall s. IsString s => Mod OptionFields s -> Parser s
strOption (String -> Mod OptionFields String
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"markdown-summary" Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields String
forall (f :: * -> *) a. String -> Mod f a
help String
"File path to write a Markdown summary of the results." Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields String
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
metavar String
"STRING"))

  Parser
  (Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe IndividualTestModule
   -> CommandLineGoldenOptions
   -> CommandLineQuickCheckOptions
   -> CommandLineHedgehogOptions
   -> CommandLineSlackOptions
   -> CommandLineWebdriverOptions
   -> a
   -> CommandLineOptions a)
-> Parser (Maybe Bool)
-> Parser
     (Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe IndividualTestModule
      -> CommandLineGoldenOptions
      -> CommandLineQuickCheckOptions
      -> CommandLineHedgehogOptions
      -> CommandLineSlackOptions
      -> CommandLineWebdriverOptions
      -> a
      -> CommandLineOptions a)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Bool -> Parser (Maybe Bool)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (Bool -> Bool -> Mod FlagFields Bool -> Parser Bool
forall a. a -> a -> Mod FlagFields a -> Parser a
flag Bool
False Bool
True (String -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"list-tests" Mod FlagFields Bool -> Mod FlagFields Bool -> Mod FlagFields Bool
forall a. Semigroup a => a -> a -> a
<> String -> Mod FlagFields Bool
forall (f :: * -> *) a. String -> Mod f a
help String
"List individual test modules"))
  Parser
  (Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe IndividualTestModule
   -> CommandLineGoldenOptions
   -> CommandLineQuickCheckOptions
   -> CommandLineHedgehogOptions
   -> CommandLineSlackOptions
   -> CommandLineWebdriverOptions
   -> a
   -> CommandLineOptions a)
-> Parser (Maybe Bool)
-> Parser
     (Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe IndividualTestModule
      -> CommandLineGoldenOptions
      -> CommandLineQuickCheckOptions
      -> CommandLineHedgehogOptions
      -> CommandLineSlackOptions
      -> CommandLineWebdriverOptions
      -> a
      -> CommandLineOptions a)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Bool -> Parser (Maybe Bool)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (Bool -> Bool -> Mod FlagFields Bool -> Parser Bool
forall a. a -> a -> Mod FlagFields a -> Parser a
flag Bool
False Bool
True (String -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"print-golden-flags" Mod FlagFields Bool -> Mod FlagFields Bool -> Mod FlagFields Bool
forall a. Semigroup a => a -> a -> a
<> String -> Mod FlagFields Bool
forall (f :: * -> *) a. String -> Mod f a
help String
"Print the additional golden testing flags"))
  Parser
  (Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe IndividualTestModule
   -> CommandLineGoldenOptions
   -> CommandLineQuickCheckOptions
   -> CommandLineHedgehogOptions
   -> CommandLineSlackOptions
   -> CommandLineWebdriverOptions
   -> a
   -> CommandLineOptions a)
-> Parser (Maybe Bool)
-> Parser
     (Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe IndividualTestModule
      -> CommandLineGoldenOptions
      -> CommandLineQuickCheckOptions
      -> CommandLineHedgehogOptions
      -> CommandLineSlackOptions
      -> CommandLineWebdriverOptions
      -> a
      -> CommandLineOptions a)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Bool -> Parser (Maybe Bool)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (Bool -> Bool -> Mod FlagFields Bool -> Parser Bool
forall a. a -> a -> Mod FlagFields a -> Parser a
flag Bool
False Bool
True (String -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"print-quickcheck-flags" Mod FlagFields Bool -> Mod FlagFields Bool -> Mod FlagFields Bool
forall a. Semigroup a => a -> a -> a
<> String -> Mod FlagFields Bool
forall (f :: * -> *) a. String -> Mod f a
help String
"Print the additional QuickCheck flags"))
  Parser
  (Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe IndividualTestModule
   -> CommandLineGoldenOptions
   -> CommandLineQuickCheckOptions
   -> CommandLineHedgehogOptions
   -> CommandLineSlackOptions
   -> CommandLineWebdriverOptions
   -> a
   -> CommandLineOptions a)
-> Parser (Maybe Bool)
-> Parser
     (Maybe Bool
      -> Maybe Bool
      -> Maybe IndividualTestModule
      -> CommandLineGoldenOptions
      -> CommandLineQuickCheckOptions
      -> CommandLineHedgehogOptions
      -> CommandLineSlackOptions
      -> CommandLineWebdriverOptions
      -> a
      -> CommandLineOptions a)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Bool -> Parser (Maybe Bool)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (Bool -> Bool -> Mod FlagFields Bool -> Parser Bool
forall a. a -> a -> Mod FlagFields a -> Parser a
flag Bool
False Bool
True (String -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"print-hedgehog-flags" Mod FlagFields Bool -> Mod FlagFields Bool -> Mod FlagFields Bool
forall a. Semigroup a => a -> a -> a
<> String -> Mod FlagFields Bool
forall (f :: * -> *) a. String -> Mod f a
help String
"Print the additional Hedgehog flags"))
  Parser
  (Maybe Bool
   -> Maybe Bool
   -> Maybe IndividualTestModule
   -> CommandLineGoldenOptions
   -> CommandLineQuickCheckOptions
   -> CommandLineHedgehogOptions
   -> CommandLineSlackOptions
   -> CommandLineWebdriverOptions
   -> a
   -> CommandLineOptions a)
-> Parser (Maybe Bool)
-> Parser
     (Maybe Bool
      -> Maybe IndividualTestModule
      -> CommandLineGoldenOptions
      -> CommandLineQuickCheckOptions
      -> CommandLineHedgehogOptions
      -> CommandLineSlackOptions
      -> CommandLineWebdriverOptions
      -> a
      -> CommandLineOptions a)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Bool -> Parser (Maybe Bool)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (Bool -> Bool -> Mod FlagFields Bool -> Parser Bool
forall a. a -> a -> Mod FlagFields a -> Parser a
flag Bool
False Bool
True (String -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"print-slack-flags" Mod FlagFields Bool -> Mod FlagFields Bool -> Mod FlagFields Bool
forall a. Semigroup a => a -> a -> a
<> String -> Mod FlagFields Bool
forall (f :: * -> *) a. String -> Mod f a
help String
"Print the additional Slack flags"))
  Parser
  (Maybe Bool
   -> Maybe IndividualTestModule
   -> CommandLineGoldenOptions
   -> CommandLineQuickCheckOptions
   -> CommandLineHedgehogOptions
   -> CommandLineSlackOptions
   -> CommandLineWebdriverOptions
   -> a
   -> CommandLineOptions a)
-> Parser (Maybe Bool)
-> Parser
     (Maybe IndividualTestModule
      -> CommandLineGoldenOptions
      -> CommandLineQuickCheckOptions
      -> CommandLineHedgehogOptions
      -> CommandLineSlackOptions
      -> CommandLineWebdriverOptions
      -> a
      -> CommandLineOptions a)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Bool -> Parser (Maybe Bool)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (Bool -> Bool -> Mod FlagFields Bool -> Parser Bool
forall a. a -> a -> Mod FlagFields a -> Parser a
flag Bool
False Bool
True (String -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"print-webdriver-flags" Mod FlagFields Bool -> Mod FlagFields Bool -> Mod FlagFields Bool
forall a. Semigroup a => a -> a -> a
<> String -> Mod FlagFields Bool
forall (f :: * -> *) a. String -> Mod f a
help String
"Print the additional Webdriver flags"))

  Parser
  (Maybe IndividualTestModule
   -> CommandLineGoldenOptions
   -> CommandLineQuickCheckOptions
   -> CommandLineHedgehogOptions
   -> CommandLineSlackOptions
   -> CommandLineWebdriverOptions
   -> a
   -> CommandLineOptions a)
-> Parser (Maybe IndividualTestModule)
-> Parser
     (CommandLineGoldenOptions
      -> CommandLineQuickCheckOptions
      -> CommandLineHedgehogOptions
      -> CommandLineSlackOptions
      -> CommandLineWebdriverOptions
      -> a
      -> CommandLineOptions a)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser (Maybe IndividualTestModule)
individualTestParser

  Parser
  (CommandLineGoldenOptions
   -> CommandLineQuickCheckOptions
   -> CommandLineHedgehogOptions
   -> CommandLineSlackOptions
   -> CommandLineWebdriverOptions
   -> a
   -> CommandLineOptions a)
-> Parser CommandLineGoldenOptions
-> Parser
     (CommandLineQuickCheckOptions
      -> CommandLineHedgehogOptions
      -> CommandLineSlackOptions
      -> CommandLineWebdriverOptions
      -> a
      -> CommandLineOptions a)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall (f :: * -> *) a. Mod f a)
-> Parser CommandLineGoldenOptions
commandLineGoldenOptions Mod f a
forall (f :: * -> *) a. Mod f a
internal
  Parser
  (CommandLineQuickCheckOptions
   -> CommandLineHedgehogOptions
   -> CommandLineSlackOptions
   -> CommandLineWebdriverOptions
   -> a
   -> CommandLineOptions a)
-> Parser CommandLineQuickCheckOptions
-> Parser
     (CommandLineHedgehogOptions
      -> CommandLineSlackOptions
      -> CommandLineWebdriverOptions
      -> a
      -> CommandLineOptions a)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall (f :: * -> *) a. Mod f a)
-> Parser CommandLineQuickCheckOptions
commandLineQuickCheckOptions Mod f a
forall (f :: * -> *) a. Mod f a
internal
  Parser
  (CommandLineHedgehogOptions
   -> CommandLineSlackOptions
   -> CommandLineWebdriverOptions
   -> a
   -> CommandLineOptions a)
-> Parser CommandLineHedgehogOptions
-> Parser
     (CommandLineSlackOptions
      -> CommandLineWebdriverOptions -> a -> CommandLineOptions a)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall (f :: * -> *) a. Mod f a)
-> Parser CommandLineHedgehogOptions
commandLineHedgehogOptions Mod f a
forall (f :: * -> *) a. Mod f a
internal
  Parser
  (CommandLineSlackOptions
   -> CommandLineWebdriverOptions -> a -> CommandLineOptions a)
-> Parser CommandLineSlackOptions
-> Parser
     (CommandLineWebdriverOptions -> a -> CommandLineOptions a)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall (f :: * -> *) a. Mod f a) -> Parser CommandLineSlackOptions
commandLineSlackOptions Mod f a
forall (f :: * -> *) a. Mod f a
internal
  Parser (CommandLineWebdriverOptions -> a -> CommandLineOptions a)
-> Parser CommandLineWebdriverOptions
-> Parser (a -> CommandLineOptions a)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall (f :: * -> *) a. Mod f a)
-> Parser CommandLineWebdriverOptions
commandLineWebdriverOptions Mod f a
forall (f :: * -> *) a. Mod f a
internal

  Parser (a -> CommandLineOptions a)
-> Parser a -> Parser (CommandLineOptions a)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser a
userOptionsParser

formatter :: Parser FormatterType
formatter :: Parser FormatterType
formatter =
  FormatterType
-> Mod FlagFields FormatterType -> Parser FormatterType
forall a. a -> Mod FlagFields a -> Parser a
flag' FormatterType
Print (String -> Mod FlagFields FormatterType
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"print" Mod FlagFields FormatterType
-> Mod FlagFields FormatterType -> Mod FlagFields FormatterType
forall a. Semigroup a => a -> a -> a
<> String -> Mod FlagFields FormatterType
forall (f :: * -> *) a. String -> Mod f a
help String
"Print to stdout")
  Parser FormatterType
-> Parser FormatterType -> Parser FormatterType
forall a. Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> FormatterType
-> Mod FlagFields FormatterType -> Parser FormatterType
forall a. a -> Mod FlagFields a -> Parser a
flag' FormatterType
PrintFailures (String -> Mod FlagFields FormatterType
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"print-failures" Mod FlagFields FormatterType
-> Mod FlagFields FormatterType -> Mod FlagFields FormatterType
forall a. Semigroup a => a -> a -> a
<> String -> Mod FlagFields FormatterType
forall (f :: * -> *) a. String -> Mod f a
help String
"Print failures only to stdout")
  Parser FormatterType
-> Parser FormatterType -> Parser FormatterType
forall a. Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> FormatterType
-> Mod FlagFields FormatterType -> Parser FormatterType
forall a. a -> Mod FlagFields a -> Parser a
flag' FormatterType
TUI (String -> Mod FlagFields FormatterType
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"tui" Mod FlagFields FormatterType
-> Mod FlagFields FormatterType -> Mod FlagFields FormatterType
forall a. Semigroup a => a -> a -> a
<> String -> Mod FlagFields FormatterType
forall (f :: * -> *) a. String -> Mod f a
help String
"Open terminal UI app")
  Parser FormatterType
-> Parser FormatterType -> Parser FormatterType
forall a. Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> FormatterType
-> Mod FlagFields FormatterType -> Parser FormatterType
forall a. a -> Mod FlagFields a -> Parser a
flag' FormatterType
Silent (String -> Mod FlagFields FormatterType
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"silent" Mod FlagFields FormatterType
-> Mod FlagFields FormatterType -> Mod FlagFields FormatterType
forall a. Semigroup a => a -> a -> a
<> String -> Mod FlagFields FormatterType
forall (f :: * -> *) a. String -> Mod f a
help String
"Run silently (print the run root only)")
  Parser FormatterType
-> Parser FormatterType -> Parser FormatterType
forall a. Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> FormatterType
-> FormatterType
-> Mod FlagFields FormatterType
-> Parser FormatterType
forall a. a -> a -> Mod FlagFields a -> Parser a
flag FormatterType
Auto FormatterType
Auto (String -> Mod FlagFields FormatterType
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"auto" Mod FlagFields FormatterType
-> Mod FlagFields FormatterType -> Mod FlagFields FormatterType
forall a. Semigroup a => a -> a -> a
<> String -> Mod FlagFields FormatterType
forall (f :: * -> *) a. String -> Mod f a
help String
"Automatically decide which formatter to use")

logLevel :: Parser (Maybe LogLevel)
logLevel :: Parser (Maybe LogLevel)
logLevel =
  Maybe LogLevel
-> Mod FlagFields (Maybe LogLevel) -> Parser (Maybe LogLevel)
forall a. a -> Mod FlagFields a -> Parser a
flag' (LogLevel -> Maybe LogLevel
forall a. a -> Maybe a
Just LogLevel
LevelDebug) (String -> Mod FlagFields (Maybe LogLevel)
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"debug" Mod FlagFields (Maybe LogLevel)
-> Mod FlagFields (Maybe LogLevel)
-> Mod FlagFields (Maybe LogLevel)
forall a. Semigroup a => a -> a -> a
<> String -> Mod FlagFields (Maybe LogLevel)
forall (f :: * -> *) a. String -> Mod f a
help String
"Log level DEBUG")
  Parser (Maybe LogLevel)
-> Parser (Maybe LogLevel) -> Parser (Maybe LogLevel)
forall a. Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Maybe LogLevel
-> Mod FlagFields (Maybe LogLevel) -> Parser (Maybe LogLevel)
forall a. a -> Mod FlagFields a -> Parser a
flag' (LogLevel -> Maybe LogLevel
forall a. a -> Maybe a
Just LogLevel
LevelInfo) (String -> Mod FlagFields (Maybe LogLevel)
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"info" Mod FlagFields (Maybe LogLevel)
-> Mod FlagFields (Maybe LogLevel)
-> Mod FlagFields (Maybe LogLevel)
forall a. Semigroup a => a -> a -> a
<> String -> Mod FlagFields (Maybe LogLevel)
forall (f :: * -> *) a. String -> Mod f a
help String
"Log level INFO")
  Parser (Maybe LogLevel)
-> Parser (Maybe LogLevel) -> Parser (Maybe LogLevel)
forall a. Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Maybe LogLevel
-> Mod FlagFields (Maybe LogLevel) -> Parser (Maybe LogLevel)
forall a. a -> Mod FlagFields a -> Parser a
flag' (LogLevel -> Maybe LogLevel
forall a. a -> Maybe a
Just LogLevel
LevelWarn) (String -> Mod FlagFields (Maybe LogLevel)
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"warn" Mod FlagFields (Maybe LogLevel)
-> Mod FlagFields (Maybe LogLevel)
-> Mod FlagFields (Maybe LogLevel)
forall a. Semigroup a => a -> a -> a
<> String -> Mod FlagFields (Maybe LogLevel)
forall (f :: * -> *) a. String -> Mod f a
help String
"Log level WARN")
  Parser (Maybe LogLevel)
-> Parser (Maybe LogLevel) -> Parser (Maybe LogLevel)
forall a. Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Maybe LogLevel
-> Maybe LogLevel
-> Mod FlagFields (Maybe LogLevel)
-> Parser (Maybe LogLevel)
forall a. a -> a -> Mod FlagFields a -> Parser a
flag (LogLevel -> Maybe LogLevel
forall a. a -> Maybe a
Just LogLevel
LevelWarn) (LogLevel -> Maybe LogLevel
forall a. a -> Maybe a
Just LogLevel
LevelError) (String -> Mod FlagFields (Maybe LogLevel)
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"error" Mod FlagFields (Maybe LogLevel)
-> Mod FlagFields (Maybe LogLevel)
-> Mod FlagFields (Maybe LogLevel)
forall a. Semigroup a => a -> a -> a
<> String -> Mod FlagFields (Maybe LogLevel)
forall (f :: * -> *) a. String -> Mod f a
help String
"Log level ERROR")

commandLineWebdriverOptions :: (forall f a. Mod f a) -> Parser CommandLineWebdriverOptions
commandLineWebdriverOptions :: (forall (f :: * -> *) a. Mod f a)
-> Parser CommandLineWebdriverOptions
commandLineWebdriverOptions forall (f :: * -> *) a. Mod f a
maybeInternal = Maybe BrowserToUse
-> Maybe DisplayType
-> Bool
-> Bool
-> Bool
-> Maybe String
-> Maybe String
-> Maybe String
-> Maybe String
-> Maybe String
-> CommandLineWebdriverOptions
CommandLineWebdriverOptions
  (Maybe BrowserToUse
 -> Maybe DisplayType
 -> Bool
 -> Bool
 -> Bool
 -> Maybe String
 -> Maybe String
 -> Maybe String
 -> Maybe String
 -> Maybe String
 -> CommandLineWebdriverOptions)
-> Parser (Maybe BrowserToUse)
-> Parser
     (Maybe DisplayType
      -> Bool
      -> Bool
      -> Bool
      -> Maybe String
      -> Maybe String
      -> Maybe String
      -> Maybe String
      -> Maybe String
      -> CommandLineWebdriverOptions)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser BrowserToUse -> Parser (Maybe BrowserToUse)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional ((forall (f :: * -> *) a. Mod f a) -> Parser BrowserToUse
browserToUse Mod f a
forall (f :: * -> *) a. Mod f a
maybeInternal)
  Parser
  (Maybe DisplayType
   -> Bool
   -> Bool
   -> Bool
   -> Maybe String
   -> Maybe String
   -> Maybe String
   -> Maybe String
   -> Maybe String
   -> CommandLineWebdriverOptions)
-> Parser (Maybe DisplayType)
-> Parser
     (Bool
      -> Bool
      -> Bool
      -> Maybe String
      -> Maybe String
      -> Maybe String
      -> Maybe String
      -> Maybe String
      -> CommandLineWebdriverOptions)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser DisplayType -> Parser (Maybe DisplayType)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional ((forall (f :: * -> *) a. Mod f a) -> Parser DisplayType
display Mod f a
forall (f :: * -> *) a. Mod f a
maybeInternal)
  Parser
  (Bool
   -> Bool
   -> Bool
   -> Maybe String
   -> Maybe String
   -> Maybe String
   -> Maybe String
   -> Maybe String
   -> CommandLineWebdriverOptions)
-> Parser Bool
-> Parser
     (Bool
      -> Bool
      -> Maybe String
      -> Maybe String
      -> Maybe String
      -> Maybe String
      -> Maybe String
      -> CommandLineWebdriverOptions)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Bool -> Bool -> Mod FlagFields Bool -> Parser Bool
forall a. a -> a -> Mod FlagFields a -> Parser a
flag Bool
False Bool
True (String -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"fluxbox" Mod FlagFields Bool -> Mod FlagFields Bool -> Mod FlagFields Bool
forall a. Semigroup a => a -> a -> a
<> String -> Mod FlagFields Bool
forall (f :: * -> *) a. String -> Mod f a
help String
"Launch fluxbox as window manager when using Xvfb" Mod FlagFields Bool -> Mod FlagFields Bool -> Mod FlagFields Bool
forall a. Semigroup a => a -> a -> a
<> Mod FlagFields Bool
forall (f :: * -> *) a. Mod f a
maybeInternal)
  Parser
  (Bool
   -> Bool
   -> Maybe String
   -> Maybe String
   -> Maybe String
   -> Maybe String
   -> Maybe String
   -> CommandLineWebdriverOptions)
-> Parser Bool
-> Parser
     (Bool
      -> Maybe String
      -> Maybe String
      -> Maybe String
      -> Maybe String
      -> Maybe String
      -> CommandLineWebdriverOptions)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Bool -> Bool -> Mod FlagFields Bool -> Parser Bool
forall a. a -> a -> Mod FlagFields a -> Parser a
flag Bool
False Bool
True (String -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"individual-videos" Mod FlagFields Bool -> Mod FlagFields Bool -> Mod FlagFields Bool
forall a. Semigroup a => a -> a -> a
<> String -> Mod FlagFields Bool
forall (f :: * -> *) a. String -> Mod f a
help String
"Record individual videos of each test (requires ffmpeg and Xvfb)" Mod FlagFields Bool -> Mod FlagFields Bool -> Mod FlagFields Bool
forall a. Semigroup a => a -> a -> a
<> Mod FlagFields Bool
forall (f :: * -> *) a. Mod f a
maybeInternal)
  Parser
  (Bool
   -> Maybe String
   -> Maybe String
   -> Maybe String
   -> Maybe String
   -> Maybe String
   -> CommandLineWebdriverOptions)
-> Parser Bool
-> Parser
     (Maybe String
      -> Maybe String
      -> Maybe String
      -> Maybe String
      -> Maybe String
      -> CommandLineWebdriverOptions)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Bool -> Bool -> Mod FlagFields Bool -> Parser Bool
forall a. a -> a -> Mod FlagFields a -> Parser a
flag Bool
False Bool
True (String -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"error-videos" Mod FlagFields Bool -> Mod FlagFields Bool -> Mod FlagFields Bool
forall a. Semigroup a => a -> a -> a
<> String -> Mod FlagFields Bool
forall (f :: * -> *) a. String -> Mod f a
help String
"Record videos of each test but delete them unless there was an exception" Mod FlagFields Bool -> Mod FlagFields Bool -> Mod FlagFields Bool
forall a. Semigroup a => a -> a -> a
<> Mod FlagFields Bool
forall (f :: * -> *) a. Mod f a
maybeInternal)

  Parser
  (Maybe String
   -> Maybe String
   -> Maybe String
   -> Maybe String
   -> Maybe String
   -> CommandLineWebdriverOptions)
-> Parser (Maybe String)
-> Parser
     (Maybe String
      -> Maybe String
      -> Maybe String
      -> Maybe String
      -> CommandLineWebdriverOptions)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser String -> Parser (Maybe String)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (Mod OptionFields String -> Parser String
forall s. IsString s => Mod OptionFields s -> Parser s
strOption (String -> Mod OptionFields String
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"selenium-jar" Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields String
forall (f :: * -> *) a. String -> Mod f a
help String
"" Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields String
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
metavar String
"STRING" Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<> Mod OptionFields String
forall (f :: * -> *) a. Mod f a
maybeInternal))

  Parser
  (Maybe String
   -> Maybe String
   -> Maybe String
   -> Maybe String
   -> CommandLineWebdriverOptions)
-> Parser (Maybe String)
-> Parser
     (Maybe String
      -> Maybe String -> Maybe String -> CommandLineWebdriverOptions)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser String -> Parser (Maybe String)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (Mod OptionFields String -> Parser String
forall s. IsString s => Mod OptionFields s -> Parser s
strOption (String -> Mod OptionFields String
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"chrome-binary" Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields String
forall (f :: * -> *) a. String -> Mod f a
help String
"" Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields String
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
metavar String
"STRING" Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<> Mod OptionFields String
forall (f :: * -> *) a. Mod f a
maybeInternal))
  Parser
  (Maybe String
   -> Maybe String -> Maybe String -> CommandLineWebdriverOptions)
-> Parser (Maybe String)
-> Parser
     (Maybe String -> Maybe String -> CommandLineWebdriverOptions)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser String -> Parser (Maybe String)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (Mod OptionFields String -> Parser String
forall s. IsString s => Mod OptionFields s -> Parser s
strOption (String -> Mod OptionFields String
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"chromedriver-binary" Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields String
forall (f :: * -> *) a. String -> Mod f a
help String
"" Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields String
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
metavar String
"STRING" Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<> Mod OptionFields String
forall (f :: * -> *) a. Mod f a
maybeInternal))

  Parser
  (Maybe String -> Maybe String -> CommandLineWebdriverOptions)
-> Parser (Maybe String)
-> Parser (Maybe String -> CommandLineWebdriverOptions)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser String -> Parser (Maybe String)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (Mod OptionFields String -> Parser String
forall s. IsString s => Mod OptionFields s -> Parser s
strOption (String -> Mod OptionFields String
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"firefox-binary" Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields String
forall (f :: * -> *) a. String -> Mod f a
help String
"" Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields String
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
metavar String
"STRING" Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<> Mod OptionFields String
forall (f :: * -> *) a. Mod f a
maybeInternal))
  Parser (Maybe String -> CommandLineWebdriverOptions)
-> Parser (Maybe String) -> Parser CommandLineWebdriverOptions
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser String -> Parser (Maybe String)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (Mod OptionFields String -> Parser String
forall s. IsString s => Mod OptionFields s -> Parser s
strOption (String -> Mod OptionFields String
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"geckodriver-binary" Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields String
forall (f :: * -> *) a. String -> Mod f a
help String
"" Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields String
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
metavar String
"STRING" Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<> Mod OptionFields String
forall (f :: * -> *) a. Mod f a
maybeInternal))

browserToUse :: (forall f a. Mod f a) -> Parser BrowserToUse
browserToUse :: (forall (f :: * -> *) a. Mod f a) -> Parser BrowserToUse
browserToUse forall (f :: * -> *) a. Mod f a
maybeInternal =
  BrowserToUse -> Mod FlagFields BrowserToUse -> Parser BrowserToUse
forall a. a -> Mod FlagFields a -> Parser a
flag' BrowserToUse
UseFirefox (String -> Mod FlagFields BrowserToUse
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"firefox" Mod FlagFields BrowserToUse
-> Mod FlagFields BrowserToUse -> Mod FlagFields BrowserToUse
forall a. Semigroup a => a -> a -> a
<> String -> Mod FlagFields BrowserToUse
forall (f :: * -> *) a. String -> Mod f a
help String
"Use Firefox" Mod FlagFields BrowserToUse
-> Mod FlagFields BrowserToUse -> Mod FlagFields BrowserToUse
forall a. Semigroup a => a -> a -> a
<> Mod FlagFields BrowserToUse
forall (f :: * -> *) a. Mod f a
maybeInternal)
  Parser BrowserToUse -> Parser BrowserToUse -> Parser BrowserToUse
forall a. Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> BrowserToUse
-> BrowserToUse
-> Mod FlagFields BrowserToUse
-> Parser BrowserToUse
forall a. a -> a -> Mod FlagFields a -> Parser a
flag BrowserToUse
UseChrome BrowserToUse
UseChrome (String -> Mod FlagFields BrowserToUse
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"chrome" Mod FlagFields BrowserToUse
-> Mod FlagFields BrowserToUse -> Mod FlagFields BrowserToUse
forall a. Semigroup a => a -> a -> a
<> String -> Mod FlagFields BrowserToUse
forall (f :: * -> *) a. String -> Mod f a
help String
"Use Chrome (default)" Mod FlagFields BrowserToUse
-> Mod FlagFields BrowserToUse -> Mod FlagFields BrowserToUse
forall a. Semigroup a => a -> a -> a
<> Mod FlagFields BrowserToUse
forall (f :: * -> *) a. Mod f a
maybeInternal)

display :: (forall f a. Mod f a) -> Parser DisplayType
display :: (forall (f :: * -> *) a. Mod f a) -> Parser DisplayType
display forall (f :: * -> *) a. Mod f a
maybeInternal =
  DisplayType -> Mod FlagFields DisplayType -> Parser DisplayType
forall a. a -> Mod FlagFields a -> Parser a
flag' DisplayType
Current (String -> Mod FlagFields DisplayType
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"current" Mod FlagFields DisplayType
-> Mod FlagFields DisplayType -> Mod FlagFields DisplayType
forall a. Semigroup a => a -> a -> a
<> String -> Mod FlagFields DisplayType
forall (f :: * -> *) a. String -> Mod f a
help String
"Open browser in current display (default)" Mod FlagFields DisplayType
-> Mod FlagFields DisplayType -> Mod FlagFields DisplayType
forall a. Semigroup a => a -> a -> a
<> Mod FlagFields DisplayType
forall (f :: * -> *) a. Mod f a
maybeInternal)
  Parser DisplayType -> Parser DisplayType -> Parser DisplayType
forall a. Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> DisplayType -> Mod FlagFields DisplayType -> Parser DisplayType
forall a. a -> Mod FlagFields a -> Parser a
flag' DisplayType
Headless (String -> Mod FlagFields DisplayType
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"headless" Mod FlagFields DisplayType
-> Mod FlagFields DisplayType -> Mod FlagFields DisplayType
forall a. Semigroup a => a -> a -> a
<> String -> Mod FlagFields DisplayType
forall (f :: * -> *) a. String -> Mod f a
help String
"Open browser in headless mode" Mod FlagFields DisplayType
-> Mod FlagFields DisplayType -> Mod FlagFields DisplayType
forall a. Semigroup a => a -> a -> a
<> Mod FlagFields DisplayType
forall (f :: * -> *) a. Mod f a
maybeInternal)
  Parser DisplayType -> Parser DisplayType -> Parser DisplayType
forall a. Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> DisplayType
-> DisplayType -> Mod FlagFields DisplayType -> Parser DisplayType
forall a. a -> a -> Mod FlagFields a -> Parser a
flag DisplayType
Current DisplayType
Xvfb (String -> Mod FlagFields DisplayType
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"xvfb" Mod FlagFields DisplayType
-> Mod FlagFields DisplayType -> Mod FlagFields DisplayType
forall a. Semigroup a => a -> a -> a
<> String -> Mod FlagFields DisplayType
forall (f :: * -> *) a. String -> Mod f a
help String
"Open browser in Xvfb session" Mod FlagFields DisplayType
-> Mod FlagFields DisplayType -> Mod FlagFields DisplayType
forall a. Semigroup a => a -> a -> a
<> Mod FlagFields DisplayType
forall (f :: * -> *) a. Mod f a
maybeInternal)

commandLineGoldenOptions :: (forall f a. Mod f a) -> Parser CommandLineGoldenOptions
commandLineGoldenOptions :: (forall (f :: * -> *) a. Mod f a)
-> Parser CommandLineGoldenOptions
commandLineGoldenOptions forall (f :: * -> *) a. Mod f a
maybeInternal = Maybe Bool -> Maybe String -> CommandLineGoldenOptions
CommandLineGoldenOptions
  (Maybe Bool -> Maybe String -> CommandLineGoldenOptions)
-> Parser (Maybe Bool)
-> Parser (Maybe String -> CommandLineGoldenOptions)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser Bool -> Parser (Maybe Bool)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (Bool -> Bool -> Mod FlagFields Bool -> Parser Bool
forall a. a -> a -> Mod FlagFields a -> Parser a
flag Bool
False Bool
True (String -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"golden-update" Mod FlagFields Bool -> Mod FlagFields Bool -> Mod FlagFields Bool
forall a. Semigroup a => a -> a -> a
<> String -> Mod FlagFields Bool
forall (f :: * -> *) a. String -> Mod f a
help String
"Update your golden files" Mod FlagFields Bool -> Mod FlagFields Bool -> Mod FlagFields Bool
forall a. Semigroup a => a -> a -> a
<> Mod FlagFields Bool
forall (f :: * -> *) a. Mod f a
maybeInternal))
  Parser (Maybe String -> CommandLineGoldenOptions)
-> Parser (Maybe String) -> Parser CommandLineGoldenOptions
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser String -> Parser (Maybe String)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (Mod OptionFields String -> Parser String
forall s. IsString s => Mod OptionFields s -> Parser s
strOption (String -> Mod OptionFields String
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"golden-dir" Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields String
forall (f :: * -> *) a. String -> Mod f a
help String
"The directory where golden results are stored (defaults to \".golden\")" Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields String
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
metavar String
"STRING" Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<> Mod OptionFields String
forall (f :: * -> *) a. Mod f a
maybeInternal))

commandLineQuickCheckOptions :: (forall f a. Mod f a) -> Parser CommandLineQuickCheckOptions
commandLineQuickCheckOptions :: (forall (f :: * -> *) a. Mod f a)
-> Parser CommandLineQuickCheckOptions
commandLineQuickCheckOptions forall (f :: * -> *) a. Mod f a
maybeInternal = Maybe Integer
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> CommandLineQuickCheckOptions
CommandLineQuickCheckOptions
  (Maybe Integer
 -> Maybe Int
 -> Maybe Int
 -> Maybe Int
 -> Maybe Int
 -> CommandLineQuickCheckOptions)
-> Parser (Maybe Integer)
-> Parser
     (Maybe Int
      -> Maybe Int
      -> Maybe Int
      -> Maybe Int
      -> CommandLineQuickCheckOptions)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser Integer -> Parser (Maybe Integer)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (ReadM Integer -> Mod OptionFields Integer -> Parser Integer
forall a. ReadM a -> Mod OptionFields a -> Parser a
option ReadM Integer
forall a. Read a => ReadM a
auto (String -> Mod OptionFields Integer
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"quickcheck-seed" Mod OptionFields Integer
-> Mod OptionFields Integer -> Mod OptionFields Integer
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields Integer
forall (f :: * -> *) a. String -> Mod f a
help String
"QuickCheck seed" Mod OptionFields Integer
-> Mod OptionFields Integer -> Mod OptionFields Integer
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields Integer
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
metavar String
"INT" Mod OptionFields Integer
-> Mod OptionFields Integer -> Mod OptionFields Integer
forall a. Semigroup a => a -> a -> a
<> Mod OptionFields Integer
forall (f :: * -> *) a. Mod f a
maybeInternal))
  Parser
  (Maybe Int
   -> Maybe Int
   -> Maybe Int
   -> Maybe Int
   -> CommandLineQuickCheckOptions)
-> Parser (Maybe Int)
-> Parser
     (Maybe Int
      -> Maybe Int -> Maybe Int -> CommandLineQuickCheckOptions)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Int -> Parser (Maybe Int)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (ReadM Int -> Mod OptionFields Int -> Parser Int
forall a. ReadM a -> Mod OptionFields a -> Parser a
option ReadM Int
forall a. Read a => ReadM a
auto (String -> Mod OptionFields Int
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"quickcheck-max-discard-ratio" Mod OptionFields Int
-> Mod OptionFields Int -> Mod OptionFields Int
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields Int
forall (f :: * -> *) a. String -> Mod f a
help String
"Maximum number of discarded tests per successful test before giving up" Mod OptionFields Int
-> Mod OptionFields Int -> Mod OptionFields Int
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields Int
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
metavar String
"INT" Mod OptionFields Int
-> Mod OptionFields Int -> Mod OptionFields Int
forall a. Semigroup a => a -> a -> a
<> Mod OptionFields Int
forall (f :: * -> *) a. Mod f a
maybeInternal))
  Parser
  (Maybe Int
   -> Maybe Int -> Maybe Int -> CommandLineQuickCheckOptions)
-> Parser (Maybe Int)
-> Parser (Maybe Int -> Maybe Int -> CommandLineQuickCheckOptions)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Int -> Parser (Maybe Int)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (ReadM Int -> Mod OptionFields Int -> Parser Int
forall a. ReadM a -> Mod OptionFields a -> Parser a
option ReadM Int
forall a. Read a => ReadM a
auto (String -> Mod OptionFields Int
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"quickcheck-max-size" Mod OptionFields Int
-> Mod OptionFields Int -> Mod OptionFields Int
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields Int
forall (f :: * -> *) a. String -> Mod f a
help String
"Size to use for the biggest test cases" Mod OptionFields Int
-> Mod OptionFields Int -> Mod OptionFields Int
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields Int
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
metavar String
"INT" Mod OptionFields Int
-> Mod OptionFields Int -> Mod OptionFields Int
forall a. Semigroup a => a -> a -> a
<> Mod OptionFields Int
forall (f :: * -> *) a. Mod f a
maybeInternal))
  Parser (Maybe Int -> Maybe Int -> CommandLineQuickCheckOptions)
-> Parser (Maybe Int)
-> Parser (Maybe Int -> CommandLineQuickCheckOptions)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Int -> Parser (Maybe Int)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (ReadM Int -> Mod OptionFields Int -> Parser Int
forall a. ReadM a -> Mod OptionFields a -> Parser a
option ReadM Int
forall a. Read a => ReadM a
auto (String -> Mod OptionFields Int
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"quickcheck-max-success" Mod OptionFields Int
-> Mod OptionFields Int -> Mod OptionFields Int
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields Int
forall (f :: * -> *) a. String -> Mod f a
help String
"Maximum number of successful tests before succeeding" Mod OptionFields Int
-> Mod OptionFields Int -> Mod OptionFields Int
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields Int
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
metavar String
"INT" Mod OptionFields Int
-> Mod OptionFields Int -> Mod OptionFields Int
forall a. Semigroup a => a -> a -> a
<> Mod OptionFields Int
forall (f :: * -> *) a. Mod f a
maybeInternal))
  Parser (Maybe Int -> CommandLineQuickCheckOptions)
-> Parser (Maybe Int) -> Parser CommandLineQuickCheckOptions
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Int -> Parser (Maybe Int)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (ReadM Int -> Mod OptionFields Int -> Parser Int
forall a. ReadM a -> Mod OptionFields a -> Parser a
option ReadM Int
forall a. Read a => ReadM a
auto (String -> Mod OptionFields Int
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"quickcheck-max-shrinks" Mod OptionFields Int
-> Mod OptionFields Int -> Mod OptionFields Int
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields Int
forall (f :: * -> *) a. String -> Mod f a
help String
"Maximum number of shrinks before giving up" Mod OptionFields Int
-> Mod OptionFields Int -> Mod OptionFields Int
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields Int
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
metavar String
"INT" Mod OptionFields Int
-> Mod OptionFields Int -> Mod OptionFields Int
forall a. Semigroup a => a -> a -> a
<> Mod OptionFields Int
forall (f :: * -> *) a. Mod f a
maybeInternal))

commandLineHedgehogOptions :: (forall f a. Mod f a) -> Parser CommandLineHedgehogOptions
commandLineHedgehogOptions :: (forall (f :: * -> *) a. Mod f a)
-> Parser CommandLineHedgehogOptions
commandLineHedgehogOptions forall (f :: * -> *) a. Mod f a
maybeInternal = Maybe String
-> Maybe Int
-> Maybe Integer
-> Maybe Integer
-> Maybe Integer
-> CommandLineHedgehogOptions
CommandLineHedgehogOptions
  (Maybe String
 -> Maybe Int
 -> Maybe Integer
 -> Maybe Integer
 -> Maybe Integer
 -> CommandLineHedgehogOptions)
-> Parser (Maybe String)
-> Parser
     (Maybe Int
      -> Maybe Integer
      -> Maybe Integer
      -> Maybe Integer
      -> CommandLineHedgehogOptions)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser String -> Parser (Maybe String)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (ReadM String -> Mod OptionFields String -> Parser String
forall a. ReadM a -> Mod OptionFields a -> Parser a
option ReadM String
forall a. Read a => ReadM a
auto (String -> Mod OptionFields String
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"hedgehog-seed" Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields String
forall (f :: * -> *) a. String -> Mod f a
help String
"Seed as a tuple (a, b)" Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields String
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
metavar String
"STRING" Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<> Mod OptionFields String
forall (f :: * -> *) a. Mod f a
maybeInternal))
  Parser
  (Maybe Int
   -> Maybe Integer
   -> Maybe Integer
   -> Maybe Integer
   -> CommandLineHedgehogOptions)
-> Parser (Maybe Int)
-> Parser
     (Maybe Integer
      -> Maybe Integer -> Maybe Integer -> CommandLineHedgehogOptions)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Int -> Parser (Maybe Int)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (ReadM Int -> Mod OptionFields Int -> Parser Int
forall a. ReadM a -> Mod OptionFields a -> Parser a
option ReadM Int
forall a. Read a => ReadM a
auto (String -> Mod OptionFields Int
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"hedgehog-size" Mod OptionFields Int
-> Mod OptionFields Int -> Mod OptionFields Int
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields Int
forall (f :: * -> *) a. String -> Mod f a
help String
"Size of the randomly-generated data" Mod OptionFields Int
-> Mod OptionFields Int -> Mod OptionFields Int
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields Int
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
metavar String
"INT" Mod OptionFields Int
-> Mod OptionFields Int -> Mod OptionFields Int
forall a. Semigroup a => a -> a -> a
<> Mod OptionFields Int
forall (f :: * -> *) a. Mod f a
maybeInternal))
  Parser
  (Maybe Integer
   -> Maybe Integer -> Maybe Integer -> CommandLineHedgehogOptions)
-> Parser (Maybe Integer)
-> Parser
     (Maybe Integer -> Maybe Integer -> CommandLineHedgehogOptions)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Integer -> Parser (Maybe Integer)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (ReadM Integer -> Mod OptionFields Integer -> Parser Integer
forall a. ReadM a -> Mod OptionFields a -> Parser a
option ReadM Integer
forall a. Read a => ReadM a
auto (String -> Mod OptionFields Integer
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"hedgehog-discard-limit" Mod OptionFields Integer
-> Mod OptionFields Integer -> Mod OptionFields Integer
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields Integer
forall (f :: * -> *) a. String -> Mod f a
help String
"The number of times a property is allowed to discard before the test runner gives up" Mod OptionFields Integer
-> Mod OptionFields Integer -> Mod OptionFields Integer
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields Integer
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
metavar String
"INT" Mod OptionFields Integer
-> Mod OptionFields Integer -> Mod OptionFields Integer
forall a. Semigroup a => a -> a -> a
<> Mod OptionFields Integer
forall (f :: * -> *) a. Mod f a
maybeInternal))
  Parser
  (Maybe Integer -> Maybe Integer -> CommandLineHedgehogOptions)
-> Parser (Maybe Integer)
-> Parser (Maybe Integer -> CommandLineHedgehogOptions)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Integer -> Parser (Maybe Integer)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (ReadM Integer -> Mod OptionFields Integer -> Parser Integer
forall a. ReadM a -> Mod OptionFields a -> Parser a
option ReadM Integer
forall a. Read a => ReadM a
auto (String -> Mod OptionFields Integer
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"hedgehog-shrink-limit" Mod OptionFields Integer
-> Mod OptionFields Integer -> Mod OptionFields Integer
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields Integer
forall (f :: * -> *) a. String -> Mod f a
help String
"The number of times a property is allowed to shrink before the test runner gives up and prints the counterexample" Mod OptionFields Integer
-> Mod OptionFields Integer -> Mod OptionFields Integer
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields Integer
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
metavar String
"INT" Mod OptionFields Integer
-> Mod OptionFields Integer -> Mod OptionFields Integer
forall a. Semigroup a => a -> a -> a
<> Mod OptionFields Integer
forall (f :: * -> *) a. Mod f a
maybeInternal))
  Parser (Maybe Integer -> CommandLineHedgehogOptions)
-> Parser (Maybe Integer) -> Parser CommandLineHedgehogOptions
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Integer -> Parser (Maybe Integer)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (ReadM Integer -> Mod OptionFields Integer -> Parser Integer
forall a. ReadM a -> Mod OptionFields a -> Parser a
option ReadM Integer
forall a. Read a => ReadM a
auto (String -> Mod OptionFields Integer
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"hedgehog-shrink-retries" Mod OptionFields Integer
-> Mod OptionFields Integer -> Mod OptionFields Integer
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields Integer
forall (f :: * -> *) a. String -> Mod f a
help String
"The number of times to re-run a test during shrinking" Mod OptionFields Integer
-> Mod OptionFields Integer -> Mod OptionFields Integer
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields Integer
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
metavar String
"INT" Mod OptionFields Integer
-> Mod OptionFields Integer -> Mod OptionFields Integer
forall a. Semigroup a => a -> a -> a
<> Mod OptionFields Integer
forall (f :: * -> *) a. Mod f a
maybeInternal))

commandLineSlackOptions :: (forall f a. Mod f a) -> Parser CommandLineSlackOptions
commandLineSlackOptions :: (forall (f :: * -> *) a. Mod f a) -> Parser CommandLineSlackOptions
commandLineSlackOptions forall (f :: * -> *) a. Mod f a
maybeInternal = Maybe String
-> Maybe String
-> Maybe String
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe Int64
-> CommandLineSlackOptions
CommandLineSlackOptions
  (Maybe String
 -> Maybe String
 -> Maybe String
 -> Maybe Int
 -> Maybe Int
 -> Maybe Int
 -> Maybe Int
 -> Maybe Int64
 -> CommandLineSlackOptions)
-> Parser (Maybe String)
-> Parser
     (Maybe String
      -> Maybe String
      -> Maybe Int
      -> Maybe Int
      -> Maybe Int
      -> Maybe Int
      -> Maybe Int64
      -> CommandLineSlackOptions)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser String -> Parser (Maybe String)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (Mod OptionFields String -> Parser String
forall s. IsString s => Mod OptionFields s -> Parser s
strOption (String -> Mod OptionFields String
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"slack-token" Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields String
forall (f :: * -> *) a. String -> Mod f a
help String
"Slack token to use with the Slack formatter" Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields String
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
metavar String
"STRING" Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<> Mod OptionFields String
forall (f :: * -> *) a. Mod f a
maybeInternal))
  Parser
  (Maybe String
   -> Maybe String
   -> Maybe Int
   -> Maybe Int
   -> Maybe Int
   -> Maybe Int
   -> Maybe Int64
   -> CommandLineSlackOptions)
-> Parser (Maybe String)
-> Parser
     (Maybe String
      -> Maybe Int
      -> Maybe Int
      -> Maybe Int
      -> Maybe Int
      -> Maybe Int64
      -> CommandLineSlackOptions)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser String -> Parser (Maybe String)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (Mod OptionFields String -> Parser String
forall s. IsString s => Mod OptionFields s -> Parser s
strOption (String -> Mod OptionFields String
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"slack-channel" Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields String
forall (f :: * -> *) a. String -> Mod f a
help String
"Slack channel to use with the Slack formatter" Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields String
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
metavar String
"STRING" Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<> Mod OptionFields String
forall (f :: * -> *) a. Mod f a
maybeInternal))

  Parser
  (Maybe String
   -> Maybe Int
   -> Maybe Int
   -> Maybe Int
   -> Maybe Int
   -> Maybe Int64
   -> CommandLineSlackOptions)
-> Parser (Maybe String)
-> Parser
     (Maybe Int
      -> Maybe Int
      -> Maybe Int
      -> Maybe Int
      -> Maybe Int64
      -> CommandLineSlackOptions)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser String -> Parser (Maybe String)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (Mod OptionFields String -> Parser String
forall s. IsString s => Mod OptionFields s -> Parser s
strOption (String -> Mod OptionFields String
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"slack-top-message" Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields String
forall (f :: * -> *) a. String -> Mod f a
help String
"Top message to display on Slack progress bars" Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields String
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
metavar String
"STRING" Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<> Mod OptionFields String
forall (f :: * -> *) a. Mod f a
maybeInternal))

  Parser
  (Maybe Int
   -> Maybe Int
   -> Maybe Int
   -> Maybe Int
   -> Maybe Int64
   -> CommandLineSlackOptions)
-> Parser (Maybe Int)
-> Parser
     (Maybe Int
      -> Maybe Int
      -> Maybe Int
      -> Maybe Int64
      -> CommandLineSlackOptions)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Int -> Parser (Maybe Int)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (ReadM Int -> Mod OptionFields Int -> Parser Int
forall a. ReadM a -> Mod OptionFields a -> Parser a
option ReadM Int
forall a. Read a => ReadM a
auto (String -> Mod OptionFields Int
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"slack-max-failures" Mod OptionFields Int
-> Mod OptionFields Int -> Mod OptionFields Int
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields Int
forall (f :: * -> *) a. String -> Mod f a
help String
"Maximum number of failures to include in a message" Mod OptionFields Int
-> Mod OptionFields Int -> Mod OptionFields Int
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields Int
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
metavar String
"INT" Mod OptionFields Int
-> Mod OptionFields Int -> Mod OptionFields Int
forall a. Semigroup a => a -> a -> a
<> Mod OptionFields Int
forall (f :: * -> *) a. Mod f a
maybeInternal))
  Parser
  (Maybe Int
   -> Maybe Int
   -> Maybe Int
   -> Maybe Int64
   -> CommandLineSlackOptions)
-> Parser (Maybe Int)
-> Parser
     (Maybe Int -> Maybe Int -> Maybe Int64 -> CommandLineSlackOptions)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Int -> Parser (Maybe Int)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (ReadM Int -> Mod OptionFields Int -> Parser Int
forall a. ReadM a -> Mod OptionFields a -> Parser a
option ReadM Int
forall a. Read a => ReadM a
auto (String -> Mod OptionFields Int
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"slack-max-failure-reason-lines" Mod OptionFields Int
-> Mod OptionFields Int -> Mod OptionFields Int
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields Int
forall (f :: * -> *) a. String -> Mod f a
help String
"Maximum number of lines for the failure reason underneath a failure" Mod OptionFields Int
-> Mod OptionFields Int -> Mod OptionFields Int
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields Int
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
metavar String
"INT" Mod OptionFields Int
-> Mod OptionFields Int -> Mod OptionFields Int
forall a. Semigroup a => a -> a -> a
<> Mod OptionFields Int
forall (f :: * -> *) a. Mod f a
maybeInternal))
  Parser
  (Maybe Int -> Maybe Int -> Maybe Int64 -> CommandLineSlackOptions)
-> Parser (Maybe Int)
-> Parser (Maybe Int -> Maybe Int64 -> CommandLineSlackOptions)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Int -> Parser (Maybe Int)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (ReadM Int -> Mod OptionFields Int -> Parser Int
forall a. ReadM a -> Mod OptionFields a -> Parser a
option ReadM Int
forall a. Read a => ReadM a
auto (String -> Mod OptionFields Int
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"slack-max-callstack-lines" Mod OptionFields Int
-> Mod OptionFields Int -> Mod OptionFields Int
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields Int
forall (f :: * -> *) a. String -> Mod f a
help String
"Maximum number of lines for the callstack reason underneath a failure" Mod OptionFields Int
-> Mod OptionFields Int -> Mod OptionFields Int
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields Int
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
metavar String
"INT" Mod OptionFields Int
-> Mod OptionFields Int -> Mod OptionFields Int
forall a. Semigroup a => a -> a -> a
<> Mod OptionFields Int
forall (f :: * -> *) a. Mod f a
maybeInternal))

  Parser (Maybe Int -> Maybe Int64 -> CommandLineSlackOptions)
-> Parser (Maybe Int)
-> Parser (Maybe Int64 -> CommandLineSlackOptions)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Int -> Parser (Maybe Int)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (ReadM Int -> Mod OptionFields Int -> Parser Int
forall a. ReadM a -> Mod OptionFields a -> Parser a
option ReadM Int
forall a. Read a => ReadM a
auto (String -> Mod OptionFields Int
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"slack-visibility-threshold" Mod OptionFields Int
-> Mod OptionFields Int -> Mod OptionFields Int
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields Int
forall (f :: * -> *) a. String -> Mod f a
help String
"Filter the headings on failures by visibility threshold" Mod OptionFields Int
-> Mod OptionFields Int -> Mod OptionFields Int
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields Int
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
metavar String
"INT" Mod OptionFields Int
-> Mod OptionFields Int -> Mod OptionFields Int
forall a. Semigroup a => a -> a -> a
<> Mod OptionFields Int
forall (f :: * -> *) a. Mod f a
maybeInternal))

  Parser (Maybe Int64 -> CommandLineSlackOptions)
-> Parser (Maybe Int64) -> Parser CommandLineSlackOptions
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Int64 -> Parser (Maybe Int64)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (ReadM Int64 -> Mod OptionFields Int64 -> Parser Int64
forall a. ReadM a -> Mod OptionFields a -> Parser a
option ReadM Int64
forall a. Read a => ReadM a
auto (String -> Mod OptionFields Int64
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"slack-max-message-size" Mod OptionFields Int64
-> Mod OptionFields Int64 -> Mod OptionFields Int64
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields Int64
forall (f :: * -> *) a. String -> Mod f a
help String
"Maximum message size in bytes (default: 8192)" Mod OptionFields Int64
-> Mod OptionFields Int64 -> Mod OptionFields Int64
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields Int64
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
metavar String
"INT" Mod OptionFields Int64
-> Mod OptionFields Int64 -> Mod OptionFields Int64
forall a. Semigroup a => a -> a -> a
<> Mod OptionFields Int64
forall (f :: * -> *) a. Mod f a
maybeInternal))

-- * Parse command line args

parseCommandLineArgs :: forall a. (Typeable a) => Parser a -> TopSpecWithOptions' a -> IO (CommandLineOptions a)
parseCommandLineArgs :: forall a.
Typeable a =>
Parser a -> TopSpecWithOptions' a -> IO (CommandLineOptions a)
parseCommandLineArgs Parser a
parser TopSpecWithOptions' a
spec = do
  (CommandLineOptions a
clo, Mod FlagFields (Maybe IndividualTestModule)
-> Parser (Maybe IndividualTestModule)
_, [(NodeModuleInfo, Text)]
_) <- Parser a
-> TopSpecWithOptions' a
-> IO
     (CommandLineOptions a,
      Mod FlagFields (Maybe IndividualTestModule)
      -> Parser (Maybe IndividualTestModule),
      [(NodeModuleInfo, Text)])
forall a.
Typeable a =>
Parser a
-> TopSpecWithOptions' a
-> IO
     (CommandLineOptions a,
      Mod FlagFields (Maybe IndividualTestModule)
      -> Parser (Maybe IndividualTestModule),
      [(NodeModuleInfo, Text)])
parseCommandLineArgs' Parser a
parser SpecFree context IO ()
TopSpecWithOptions' a
spec
  CommandLineOptions a -> IO (CommandLineOptions a)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CommandLineOptions a
clo

parseCommandLineArgs' :: forall a. (Typeable a) => Parser a -> TopSpecWithOptions' a -> IO (
  CommandLineOptions a
  , Mod FlagFields (Maybe IndividualTestModule) -> Parser (Maybe IndividualTestModule)
  , [(NodeModuleInfo, T.Text)]
  )
parseCommandLineArgs' :: forall a.
Typeable a =>
Parser a
-> TopSpecWithOptions' a
-> IO
     (CommandLineOptions a,
      Mod FlagFields (Maybe IndividualTestModule)
      -> Parser (Maybe IndividualTestModule),
      [(NodeModuleInfo, Text)])
parseCommandLineArgs' Parser a
userOptionsParser TopSpecWithOptions' a
spec = do
  let modulesAndShorthands :: [(NodeModuleInfo, Text)]
modulesAndShorthands = Free
  (SpecCommand
     (LabelValue "commandLineOptions" (CommandLineOptions a)
      :> BaseContext)
     IO)
  ()
-> [NodeModuleInfo]
forall context (m :: * -> *) r.
Free (SpecCommand context m) r -> [NodeModuleInfo]
gatherMainFunctions (Free
  (SpecCommand
     (LabelValue "commandLineOptions" (CommandLineOptions a)
      :> BaseContext)
     IO)
  ()
TopSpecWithOptions' a
spec :: SpecFree (LabelValue "commandLineOptions" (CommandLineOptions a) :> BaseContext) IO ())
                           [NodeModuleInfo]
-> ([NodeModuleInfo] -> [NodeModuleInfo]) -> [NodeModuleInfo]
forall a b. a -> (a -> b) -> b
& (NodeModuleInfo -> String) -> [NodeModuleInfo] -> [NodeModuleInfo]
forall b a. Ord b => (a -> b) -> [a] -> [a]
L.sortOn NodeModuleInfo -> String
nodeModuleInfoModuleName
                           [NodeModuleInfo]
-> ([NodeModuleInfo] -> [(NodeModuleInfo, Text)])
-> [(NodeModuleInfo, Text)]
forall a b. a -> (a -> b) -> b
& [NodeModuleInfo] -> [(NodeModuleInfo, Text)]
gatherShorthands
  let individualTestFlags :: Mod FlagFields (Maybe IndividualTestModule)
-> [[Maybe (Parser (Maybe IndividualTestModule))]]
individualTestFlags Mod FlagFields (Maybe IndividualTestModule)
maybeInternal =
        [[ Parser (Maybe IndividualTestModule)
-> Maybe (Parser (Maybe IndividualTestModule))
forall a. a -> Maybe a
Just (Parser (Maybe IndividualTestModule)
 -> Maybe (Parser (Maybe IndividualTestModule)))
-> Parser (Maybe IndividualTestModule)
-> Maybe (Parser (Maybe IndividualTestModule))
forall a b. (a -> b) -> a -> b
$ Maybe IndividualTestModule
-> Mod FlagFields (Maybe IndividualTestModule)
-> Parser (Maybe IndividualTestModule)
forall a. a -> Mod FlagFields a -> Parser a
flag' (IndividualTestModule -> Maybe IndividualTestModule
forall a. a -> Maybe a
Just (IndividualTestModule -> Maybe IndividualTestModule)
-> IndividualTestModule -> Maybe IndividualTestModule
forall a b. (a -> b) -> a -> b
$ String -> IndividualTestModule
IndividualTestModuleName String
nodeModuleInfoModuleName)
                        (String -> Mod FlagFields (Maybe IndividualTestModule)
forall (f :: * -> *) a. HasName f => String -> Mod f a
long (Text -> String
T.unpack Text
shorthand)
                          Mod FlagFields (Maybe IndividualTestModule)
-> Mod FlagFields (Maybe IndividualTestModule)
-> Mod FlagFields (Maybe IndividualTestModule)
forall a. Semigroup a => a -> a -> a
<> String -> Mod FlagFields (Maybe IndividualTestModule)
forall (f :: * -> *) a. String -> Mod f a
help (String
nodeModuleInfoModuleName
                          String -> String -> String
forall a. Semigroup a => a -> a -> a
<> (if Maybe (IO ()) -> Bool
forall a. Maybe a -> Bool
isJust Maybe (IO ())
nodeModuleInfoFn then String
"*" else String
""))
                          Mod FlagFields (Maybe IndividualTestModule)
-> Mod FlagFields (Maybe IndividualTestModule)
-> Mod FlagFields (Maybe IndividualTestModule)
forall a. Semigroup a => a -> a -> a
<> Mod FlagFields (Maybe IndividualTestModule)
maybeInternal)
         , case Maybe (IO ())
nodeModuleInfoFn of
             Maybe (IO ())
Nothing -> Maybe (Parser (Maybe IndividualTestModule))
forall a. Maybe a
Nothing
             Just IO ()
fn -> Parser (Maybe IndividualTestModule)
-> Maybe (Parser (Maybe IndividualTestModule))
forall a. a -> Maybe a
Just (Parser (Maybe IndividualTestModule)
 -> Maybe (Parser (Maybe IndividualTestModule)))
-> Parser (Maybe IndividualTestModule)
-> Maybe (Parser (Maybe IndividualTestModule))
forall a b. (a -> b) -> a -> b
$ Maybe IndividualTestModule
-> Mod FlagFields (Maybe IndividualTestModule)
-> Parser (Maybe IndividualTestModule)
forall a. a -> Mod FlagFields a -> Parser a
flag' (IndividualTestModule -> Maybe IndividualTestModule
forall a. a -> Maybe a
Just (IndividualTestModule -> Maybe IndividualTestModule)
-> IndividualTestModule -> Maybe IndividualTestModule
forall a b. (a -> b) -> a -> b
$ IO () -> IndividualTestModule
IndividualTestMainFn IO ()
fn)
                                     (String -> Mod FlagFields (Maybe IndividualTestModule)
forall (f :: * -> *) a. HasName f => String -> Mod f a
long (Text -> String
T.unpack (Text
shorthand Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"-main"))
                                       Mod FlagFields (Maybe IndividualTestModule)
-> Mod FlagFields (Maybe IndividualTestModule)
-> Mod FlagFields (Maybe IndividualTestModule)
forall a. Semigroup a => a -> a -> a
<> String -> Mod FlagFields (Maybe IndividualTestModule)
forall (f :: * -> *) a. String -> Mod f a
help String
nodeModuleInfoModuleName
                                       Mod FlagFields (Maybe IndividualTestModule)
-> Mod FlagFields (Maybe IndividualTestModule)
-> Mod FlagFields (Maybe IndividualTestModule)
forall a. Semigroup a => a -> a -> a
<> Mod FlagFields (Maybe IndividualTestModule)
forall (f :: * -> *) a. Mod f a
internal
                                     )
         ]
        | (NodeModuleInfo {String
Maybe (IO ())
nodeModuleInfoModuleName :: NodeModuleInfo -> String
nodeModuleInfoModuleName :: String
nodeModuleInfoFn :: Maybe (IO ())
nodeModuleInfoFn :: NodeModuleInfo -> Maybe (IO ())
..}, Text
shorthand) <- [(NodeModuleInfo, Text)]
modulesAndShorthands]
  let individualTestParser :: Mod FlagFields (Maybe IndividualTestModule)
-> Parser (Maybe IndividualTestModule)
individualTestParser Mod FlagFields (Maybe IndividualTestModule)
maybeInternal = (Parser (Maybe IndividualTestModule)
 -> Parser (Maybe IndividualTestModule)
 -> Parser (Maybe IndividualTestModule))
-> Parser (Maybe IndividualTestModule)
-> [Parser (Maybe IndividualTestModule)]
-> Parser (Maybe IndividualTestModule)
forall a b. (a -> b -> b) -> b -> [a] -> b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr Parser (Maybe IndividualTestModule)
-> Parser (Maybe IndividualTestModule)
-> Parser (Maybe IndividualTestModule)
forall a. Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
(<|>) (Maybe IndividualTestModule -> Parser (Maybe IndividualTestModule)
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe IndividualTestModule
forall a. Maybe a
Nothing) ([Maybe (Parser (Maybe IndividualTestModule))]
-> [Parser (Maybe IndividualTestModule)]
forall a. [Maybe a] -> [a]
catMaybes ([Maybe (Parser (Maybe IndividualTestModule))]
 -> [Parser (Maybe IndividualTestModule)])
-> [Maybe (Parser (Maybe IndividualTestModule))]
-> [Parser (Maybe IndividualTestModule)]
forall a b. (a -> b) -> a -> b
$ [[Maybe (Parser (Maybe IndividualTestModule))]]
-> [Maybe (Parser (Maybe IndividualTestModule))]
forall a. Monoid a => [a] -> a
mconcat ([[Maybe (Parser (Maybe IndividualTestModule))]]
 -> [Maybe (Parser (Maybe IndividualTestModule))])
-> [[Maybe (Parser (Maybe IndividualTestModule))]]
-> [Maybe (Parser (Maybe IndividualTestModule))]
forall a b. (a -> b) -> a -> b
$ Mod FlagFields (Maybe IndividualTestModule)
-> [[Maybe (Parser (Maybe IndividualTestModule))]]
individualTestFlags Mod FlagFields (Maybe IndividualTestModule)
maybeInternal)

  CommandLineOptions a
clo <- ParserInfo (CommandLineOptions a) -> IO (CommandLineOptions a)
forall a. ParserInfo a -> IO a
OA.execParser (Parser a
-> Parser (Maybe IndividualTestModule)
-> ParserInfo (CommandLineOptions a)
forall a.
Parser a
-> Parser (Maybe IndividualTestModule)
-> ParserInfo (CommandLineOptions a)
commandLineOptionsWithInfo Parser a
userOptionsParser (Mod FlagFields (Maybe IndividualTestModule)
-> Parser (Maybe IndividualTestModule)
individualTestParser Mod FlagFields (Maybe IndividualTestModule)
forall (f :: * -> *) a. Mod f a
internal))
  (CommandLineOptions a,
 Mod FlagFields (Maybe IndividualTestModule)
 -> Parser (Maybe IndividualTestModule),
 [(NodeModuleInfo, Text)])
-> IO
     (CommandLineOptions a,
      Mod FlagFields (Maybe IndividualTestModule)
      -> Parser (Maybe IndividualTestModule),
      [(NodeModuleInfo, Text)])
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (CommandLineOptions a
clo, Mod FlagFields (Maybe IndividualTestModule)
-> Parser (Maybe IndividualTestModule)
individualTestParser, [(NodeModuleInfo, Text)]
modulesAndShorthands)

-- * Merge command line args with base options

addOptionsFromArgs :: Options -> CommandLineOptions a -> IO (Options, Int)
addOptionsFromArgs :: forall a. Options -> CommandLineOptions a -> IO (Options, Int)
addOptionsFromArgs Options
baseOptions (CommandLineOptions {a
Int
[String]
Maybe Bool
Maybe Int
Maybe String
Maybe LogLevel
Maybe IndividualTestModule
CommandLineWebdriverOptions
CommandLineSlackOptions
CommandLineHedgehogOptions
CommandLineQuickCheckOptions
CommandLineGoldenOptions
FormatterType
optFormatter :: FormatterType
optLogLevel :: Maybe LogLevel
optVisibilityThreshold :: Maybe Int
optTreePrune :: [String]
optTreeFilter :: [String]
optRepeatCount :: Int
optFixedRoot :: Maybe String
optDryRun :: Maybe Bool
optMarkdownSummaryPath :: Maybe String
optListAvailableTests :: Maybe Bool
optPrintGoldenFlags :: Maybe Bool
optPrintQuickCheckFlags :: Maybe Bool
optPrintHedgehogFlags :: Maybe Bool
optPrintSlackFlags :: Maybe Bool
optPrintWebDriverFlags :: Maybe Bool
optIndividualTestModule :: Maybe IndividualTestModule
optGoldenOptions :: CommandLineGoldenOptions
optQuickCheckOptions :: CommandLineQuickCheckOptions
optHedgehogOptions :: CommandLineHedgehogOptions
optSlackOptions :: CommandLineSlackOptions
optWebdriverOptions :: CommandLineWebdriverOptions
optUserOptions :: a
optFormatter :: forall a. CommandLineOptions a -> FormatterType
optLogLevel :: forall a. CommandLineOptions a -> Maybe LogLevel
optVisibilityThreshold :: forall a. CommandLineOptions a -> Maybe Int
optTreePrune :: forall a. CommandLineOptions a -> [String]
optTreeFilter :: forall a. CommandLineOptions a -> [String]
optRepeatCount :: forall a. CommandLineOptions a -> Int
optFixedRoot :: forall a. CommandLineOptions a -> Maybe String
optDryRun :: forall a. CommandLineOptions a -> Maybe Bool
optMarkdownSummaryPath :: forall a. CommandLineOptions a -> Maybe String
optListAvailableTests :: forall a. CommandLineOptions a -> Maybe Bool
optPrintGoldenFlags :: forall a. CommandLineOptions a -> Maybe Bool
optPrintQuickCheckFlags :: forall a. CommandLineOptions a -> Maybe Bool
optPrintHedgehogFlags :: forall a. CommandLineOptions a -> Maybe Bool
optPrintSlackFlags :: forall a. CommandLineOptions a -> Maybe Bool
optPrintWebDriverFlags :: forall a. CommandLineOptions a -> Maybe Bool
optIndividualTestModule :: forall a. CommandLineOptions a -> Maybe IndividualTestModule
optGoldenOptions :: forall a. CommandLineOptions a -> CommandLineGoldenOptions
optQuickCheckOptions :: forall a. CommandLineOptions a -> CommandLineQuickCheckOptions
optHedgehogOptions :: forall a. CommandLineOptions a -> CommandLineHedgehogOptions
optSlackOptions :: forall a. CommandLineOptions a -> CommandLineSlackOptions
optWebdriverOptions :: forall a. CommandLineOptions a -> CommandLineWebdriverOptions
optUserOptions :: forall a. CommandLineOptions a -> a
..}) = do
  let printFormatter :: SomeFormatter
printFormatter = PrintFormatter -> SomeFormatter
forall f. (Formatter f, Show f, Typeable f) => f -> SomeFormatter
SomeFormatter (PrintFormatter -> SomeFormatter)
-> PrintFormatter -> SomeFormatter
forall a b. (a -> b) -> a -> b
$ PrintFormatter
defaultPrintFormatter { printFormatterLogLevel = optLogLevel }
  let failureReportFormatter :: SomeFormatter
failureReportFormatter = FailureReportFormatter -> SomeFormatter
forall f. (Formatter f, Show f, Typeable f) => f -> SomeFormatter
SomeFormatter (FailureReportFormatter -> SomeFormatter)
-> FailureReportFormatter -> SomeFormatter
forall a b. (a -> b) -> a -> b
$ FailureReportFormatter
defaultFailureReportFormatter { failureReportLogLevel = optLogLevel }
  let silentFormatter :: SomeFormatter
silentFormatter = SilentFormatter -> SomeFormatter
forall f. (Formatter f, Show f, Typeable f) => f -> SomeFormatter
SomeFormatter SilentFormatter
defaultSilentFormatter

  let mainFormatter :: SomeFormatter
mainFormatter = case (Int
optRepeatCount, FormatterType
optFormatter) of
        (Int
x, FormatterType
_) | Int
x Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
/= Int
1 -> case FormatterType
optFormatter of
                   FormatterType
TUI -> SomeFormatter
printFormatter
                   FormatterType
PrintFailures -> SomeFormatter
failureReportFormatter
                   FormatterType
Silent -> SomeFormatter
silentFormatter
                   FormatterType
Print -> SomeFormatter
printFormatter
                   FormatterType
Auto -> SomeFormatter
printFormatter
        (Int
_, FormatterType
Auto) ->
          -- Formerly this tried to use the TUI formatter by default after checking isTuiFormatterSupported.
          -- Unfortunately, this function returns true under "cabal test", which also redirects stdout. So
          -- you end up with no output and a hanging process (until you hit 'q'; stdin is still attached).
          -- Seems like the best default is just the print formatter.
          SomeFormatter
printFormatter
        (Int
_, FormatterType
TUI) ->
          let mainTerminalUiFormatter :: Maybe TerminalUIFormatter
mainTerminalUiFormatter = [TerminalUIFormatter] -> Maybe TerminalUIFormatter
forall a. [a] -> Maybe a
headMay [TerminalUIFormatter
x | SomeFormatter (f -> Maybe TerminalUIFormatter
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast -> Just x :: TerminalUIFormatter
x@(TerminalUIFormatter {})) <- Options -> [SomeFormatter]
optionsFormatters Options
baseOptions]
          in TerminalUIFormatter -> SomeFormatter
forall f. (Formatter f, Show f, Typeable f) => f -> SomeFormatter
SomeFormatter (TerminalUIFormatter -> SomeFormatter)
-> TerminalUIFormatter -> SomeFormatter
forall a b. (a -> b) -> a -> b
$ (TerminalUIFormatter
-> Maybe TerminalUIFormatter -> TerminalUIFormatter
forall a. a -> Maybe a -> a
fromMaybe TerminalUIFormatter
defaultTerminalUIFormatter Maybe TerminalUIFormatter
mainTerminalUiFormatter) { terminalUILogLevel = optLogLevel }
        (Int
_, FormatterType
Print) -> SomeFormatter
printFormatter
        (Int
_, FormatterType
PrintFailures) -> SomeFormatter
failureReportFormatter
        (Int
_, FormatterType
Silent) -> SomeFormatter
silentFormatter

  -- Strip out any "main" formatters since the options control that
  let baseFormatters :: [SomeFormatter]
baseFormatters = Options -> [SomeFormatter]
optionsFormatters Options
baseOptions
                     [SomeFormatter]
-> ([SomeFormatter] -> [SomeFormatter]) -> [SomeFormatter]
forall a b. a -> (a -> b) -> b
& Maybe String -> [SomeFormatter] -> [SomeFormatter]
tryAddMarkdownSummaryFormatter Maybe String
optMarkdownSummaryPath
                     [SomeFormatter]
-> ([SomeFormatter] -> [SomeFormatter]) -> [SomeFormatter]
forall a b. a -> (a -> b) -> b
& (SomeFormatter -> Bool) -> [SomeFormatter] -> [SomeFormatter]
forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not (Bool -> Bool) -> (SomeFormatter -> Bool) -> SomeFormatter -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SomeFormatter -> Bool
isMainFormatter)

  let finalFormatters :: [SomeFormatter]
finalFormatters = [SomeFormatter]
baseFormatters [SomeFormatter] -> [SomeFormatter] -> [SomeFormatter]
forall a. Semigroup a => a -> a -> a
<> [SomeFormatter
mainFormatter]
                      [SomeFormatter]
-> ([SomeFormatter] -> [SomeFormatter]) -> [SomeFormatter]
forall a b. a -> (a -> b) -> b
& (SomeFormatter -> SomeFormatter)
-> [SomeFormatter] -> [SomeFormatter]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Maybe Int -> SomeFormatter -> SomeFormatter
setVisibilityThreshold Maybe Int
optVisibilityThreshold)

  let options :: Options
options = Options
baseOptions {
    optionsTestArtifactsDirectory = case optFixedRoot of
      Maybe String
Nothing -> String -> IO String -> TestArtifactsDirectory
TestArtifactsGeneratedDirectory String
"test_runs" (UTCTime -> String
formatTime (UTCTime -> String) -> IO UTCTime -> IO String
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IO UTCTime
getCurrentTime)
      Just String
path -> String -> TestArtifactsDirectory
TestArtifactsFixedDirectory String
path
    , optionsPruneTree = case optTreePrune of
        [] -> Maybe TreeFilter
forall a. Maybe a
Nothing
        [String]
xs -> TreeFilter -> Maybe TreeFilter
forall a. a -> Maybe a
Just (TreeFilter -> Maybe TreeFilter) -> TreeFilter -> Maybe TreeFilter
forall a b. (a -> b) -> a -> b
$ [String] -> TreeFilter
TreeFilter [String]
xs
    , optionsFilterTree = case optTreeFilter of
        [] -> Maybe TreeFilter
forall a. Maybe a
Nothing
        [String]
xs -> TreeFilter -> Maybe TreeFilter
forall a. a -> Maybe a
Just (TreeFilter -> Maybe TreeFilter) -> TreeFilter -> Maybe TreeFilter
forall a b. (a -> b) -> a -> b
$ [String] -> TreeFilter
TreeFilter [String]
xs
    , optionsFormatters = finalFormatters
    , optionsDryRun = fromMaybe (optionsDryRun baseOptions) optDryRun
    }

  (Options, Int) -> IO (Options, Int)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Options
options, Int
optRepeatCount)

  where
    isMainFormatter :: SomeFormatter -> Bool
    isMainFormatter :: SomeFormatter -> Bool
isMainFormatter (SomeFormatter f
x) = case f -> Maybe PrintFormatter
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast f
x of
      Just (PrintFormatter
_ :: PrintFormatter) -> Bool
True
      Maybe PrintFormatter
Nothing -> case f -> Maybe TerminalUIFormatter
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast f
x of
        Just (TerminalUIFormatter
_ :: TerminalUIFormatter) -> Bool
True
        Maybe TerminalUIFormatter
Nothing -> Bool
False

    setVisibilityThreshold :: Maybe Int -> SomeFormatter -> SomeFormatter
setVisibilityThreshold Maybe Int
Nothing SomeFormatter
x = SomeFormatter
x
    setVisibilityThreshold (Just Int
v) x :: SomeFormatter
x@(SomeFormatter f
f) = case f -> Maybe PrintFormatter
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast f
f of
      Just pf :: PrintFormatter
pf@(PrintFormatter {}) -> PrintFormatter -> SomeFormatter
forall f. (Formatter f, Show f, Typeable f) => f -> SomeFormatter
SomeFormatter (PrintFormatter
pf { printFormatterVisibilityThreshold = v })
      Maybe PrintFormatter
Nothing -> case f -> Maybe TerminalUIFormatter
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast f
f of
        Just tuif :: TerminalUIFormatter
tuif@(TerminalUIFormatter {}) -> TerminalUIFormatter -> SomeFormatter
forall f. (Formatter f, Show f, Typeable f) => f -> SomeFormatter
SomeFormatter (TerminalUIFormatter
tuif { terminalUIVisibilityThreshold = v })
        Maybe TerminalUIFormatter
Nothing -> case f -> Maybe FailureReportFormatter
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast f
f of
          Just (FailureReportFormatter
frf :: FailureReportFormatter) -> FailureReportFormatter -> SomeFormatter
forall f. (Formatter f, Show f, Typeable f) => f -> SomeFormatter
SomeFormatter (FailureReportFormatter
frf { failureReportVisibilityThreshold = v })
          Maybe FailureReportFormatter
Nothing -> SomeFormatter
x

    isMarkdownSummaryFormatter :: SomeFormatter -> Bool
    isMarkdownSummaryFormatter :: SomeFormatter -> Bool
isMarkdownSummaryFormatter (SomeFormatter f
x) = case f -> Maybe MarkdownSummaryFormatter
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast f
x of
      Just (MarkdownSummaryFormatter
_ :: MarkdownSummaryFormatter) -> Bool
True
      Maybe MarkdownSummaryFormatter
Nothing -> Bool
False

    setMarkdownSummaryFormatterPath :: FilePath -> SomeFormatter -> SomeFormatter
    setMarkdownSummaryFormatterPath :: String -> SomeFormatter -> SomeFormatter
setMarkdownSummaryFormatterPath String
path (SomeFormatter f
x) = case f -> Maybe MarkdownSummaryFormatter
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast f
x of
      Just (MarkdownSummaryFormatter
y :: MarkdownSummaryFormatter) -> MarkdownSummaryFormatter -> SomeFormatter
forall f. (Formatter f, Show f, Typeable f) => f -> SomeFormatter
SomeFormatter (MarkdownSummaryFormatter
y { markdownSummaryPath = path })
      Maybe MarkdownSummaryFormatter
Nothing -> f -> SomeFormatter
forall f. (Formatter f, Show f, Typeable f) => f -> SomeFormatter
SomeFormatter f
x

    tryAddMarkdownSummaryFormatter :: Maybe FilePath -> [SomeFormatter] -> [SomeFormatter]
    tryAddMarkdownSummaryFormatter :: Maybe String -> [SomeFormatter] -> [SomeFormatter]
tryAddMarkdownSummaryFormatter Maybe String
Nothing [SomeFormatter]
xs = [SomeFormatter]
xs
    tryAddMarkdownSummaryFormatter (Just String
path) [SomeFormatter]
xs
      | (SomeFormatter -> Bool) -> [SomeFormatter] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
L.any SomeFormatter -> Bool
isMarkdownSummaryFormatter [SomeFormatter]
xs = (SomeFormatter -> SomeFormatter)
-> [SomeFormatter] -> [SomeFormatter]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (String -> SomeFormatter -> SomeFormatter
setMarkdownSummaryFormatterPath String
path) [SomeFormatter]
xs
      | Bool
otherwise = (MarkdownSummaryFormatter -> SomeFormatter
forall f. (Formatter f, Show f, Typeable f) => f -> SomeFormatter
SomeFormatter (String -> MarkdownSummaryFormatter
defaultMarkdownSummaryFormatter String
path)) SomeFormatter -> [SomeFormatter] -> [SomeFormatter]
forall a. a -> [a] -> [a]
: [SomeFormatter]
xs