{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE RankNTypes #-}
module Test.Sandwich.Types.ArgParsing where
import Control.Monad.Logger
import GHC.Int
data FormatterType = Print | TUI | Auto | Silent
instance Show FormatterType where
show :: FormatterType -> String
show FormatterType
Print = String
"print"
show FormatterType
TUI = String
"tui"
show FormatterType
Auto = String
"auto"
show FormatterType
Silent = String
"silent"
instance Read FormatterType where
readsPrec :: Int -> ReadS FormatterType
readsPrec Int
_ String
"print" = [(FormatterType
Print, String
"")]
readsPrec Int
_ String
"tui" = [(FormatterType
TUI, String
"")]
readsPrec Int
_ String
"auto" = [(FormatterType
Auto, String
"")]
readsPrec Int
_ String
"silent" = [(FormatterType
Silent, String
"")]
readsPrec Int
_ String
_ = []
data DisplayType = Current | Headless | Xvfb
instance Show DisplayType where
show :: DisplayType -> String
show DisplayType
Current = String
"current"
show DisplayType
Headless = String
"headless"
show DisplayType
Xvfb = String
"xvfb"
instance Read DisplayType where
readsPrec :: Int -> ReadS DisplayType
readsPrec Int
_ String
"current" = [(DisplayType
Current, String
"")]
readsPrec Int
_ String
"headless" = [(DisplayType
Headless, String
"")]
readsPrec Int
_ String
"xvfb" = [(DisplayType
Xvfb, String
"")]
readsPrec Int
_ String
_ = []
data CommandLineOptions a = CommandLineOptions {
CommandLineOptions a -> FormatterType
optFormatter :: FormatterType
, CommandLineOptions a -> Maybe LogLevel
optLogLevel :: Maybe LogLevel
, CommandLineOptions a -> Maybe String
optTreeFilter :: Maybe String
, CommandLineOptions a -> Int
optRepeatCount :: Int
, CommandLineOptions a -> Maybe String
optFixedRoot :: Maybe String
, CommandLineOptions a -> Maybe Bool
optListAvailableTests :: Maybe Bool
, CommandLineOptions a -> Maybe Bool
optPrintSlackFlags :: Maybe Bool
, CommandLineOptions a -> Maybe Bool
optPrintWebDriverFlags :: Maybe Bool
, CommandLineOptions a -> Maybe IndividualTestModule
optIndividualTestModule :: Maybe IndividualTestModule
, CommandLineOptions a -> CommandLineWebdriverOptions
optWebdriverOptions :: CommandLineWebdriverOptions
, CommandLineOptions a -> CommandLineSlackOptions
optSlackOptions :: CommandLineSlackOptions
, CommandLineOptions a -> a
optUserOptions :: a
} deriving Int -> CommandLineOptions a -> ShowS
[CommandLineOptions a] -> ShowS
CommandLineOptions a -> String
(Int -> CommandLineOptions a -> ShowS)
-> (CommandLineOptions a -> String)
-> ([CommandLineOptions a] -> ShowS)
-> Show (CommandLineOptions a)
forall a. Show a => Int -> CommandLineOptions a -> ShowS
forall a. Show a => [CommandLineOptions a] -> ShowS
forall a. Show a => CommandLineOptions a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CommandLineOptions a] -> ShowS
$cshowList :: forall a. Show a => [CommandLineOptions a] -> ShowS
show :: CommandLineOptions a -> String
$cshow :: forall a. Show a => CommandLineOptions a -> String
showsPrec :: Int -> CommandLineOptions a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> CommandLineOptions a -> ShowS
Show
data IndividualTestModule = IndividualTestModuleName String
| IndividualTestMainFn (IO ())
instance Show IndividualTestModule where
show :: IndividualTestModule -> String
show (IndividualTestModuleName String
moduleName) = String
moduleName
show (IndividualTestMainFn IO ()
_) = String
"<main function>"
data CommandLineSlackOptions = CommandLineSlackOptions {
CommandLineSlackOptions -> Maybe String
optSlackToken :: Maybe String
, CommandLineSlackOptions -> Maybe String
optSlackChannel :: Maybe String
, CommandLineSlackOptions -> Maybe String
optSlackTopMessage :: Maybe String
, CommandLineSlackOptions -> Maybe Int
optSlackMaxFailures :: Maybe Int
, CommandLineSlackOptions -> Maybe Int
optSlackMaxFailureReasonLines :: Maybe Int
, CommandLineSlackOptions -> Maybe Int
optSlackMaxCallStackLines :: Maybe Int
, CommandLineSlackOptions -> Maybe Int
optSlackVisibilityThreshold :: Maybe Int
, CommandLineSlackOptions -> Maybe Int64
optSlackMaxMessageSize :: Maybe Int64
} deriving Int -> CommandLineSlackOptions -> ShowS
[CommandLineSlackOptions] -> ShowS
CommandLineSlackOptions -> String
(Int -> CommandLineSlackOptions -> ShowS)
-> (CommandLineSlackOptions -> String)
-> ([CommandLineSlackOptions] -> ShowS)
-> Show CommandLineSlackOptions
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CommandLineSlackOptions] -> ShowS
$cshowList :: [CommandLineSlackOptions] -> ShowS
show :: CommandLineSlackOptions -> String
$cshow :: CommandLineSlackOptions -> String
showsPrec :: Int -> CommandLineSlackOptions -> ShowS
$cshowsPrec :: Int -> CommandLineSlackOptions -> ShowS
Show
data BrowserToUse = UseChrome | UseFirefox
deriving Int -> BrowserToUse -> ShowS
[BrowserToUse] -> ShowS
BrowserToUse -> String
(Int -> BrowserToUse -> ShowS)
-> (BrowserToUse -> String)
-> ([BrowserToUse] -> ShowS)
-> Show BrowserToUse
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BrowserToUse] -> ShowS
$cshowList :: [BrowserToUse] -> ShowS
show :: BrowserToUse -> String
$cshow :: BrowserToUse -> String
showsPrec :: Int -> BrowserToUse -> ShowS
$cshowsPrec :: Int -> BrowserToUse -> ShowS
Show
data CommandLineWebdriverOptions = CommandLineWebdriverOptions {
CommandLineWebdriverOptions -> Maybe BrowserToUse
optFirefox :: Maybe BrowserToUse
, CommandLineWebdriverOptions -> Maybe DisplayType
optDisplay :: Maybe DisplayType
, CommandLineWebdriverOptions -> Bool
optFluxbox :: Bool
, CommandLineWebdriverOptions -> Bool
optIndividualVideos :: Bool
, CommandLineWebdriverOptions -> Bool
optErrorVideos :: Bool
} deriving Int -> CommandLineWebdriverOptions -> ShowS
[CommandLineWebdriverOptions] -> ShowS
CommandLineWebdriverOptions -> String
(Int -> CommandLineWebdriverOptions -> ShowS)
-> (CommandLineWebdriverOptions -> String)
-> ([CommandLineWebdriverOptions] -> ShowS)
-> Show CommandLineWebdriverOptions
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CommandLineWebdriverOptions] -> ShowS
$cshowList :: [CommandLineWebdriverOptions] -> ShowS
show :: CommandLineWebdriverOptions -> String
$cshow :: CommandLineWebdriverOptions -> String
showsPrec :: Int -> CommandLineWebdriverOptions -> ShowS
$cshowsPrec :: Int -> CommandLineWebdriverOptions -> ShowS
Show