{-# LANGUAGE NoImplicitPrelude #-}

module Stack.Options.TestParser
  ( testOptsParser
  ) where

import           Options.Applicative
import           Options.Applicative.Args
import           Options.Applicative.Builder.Extra
import           Stack.Options.Utils
import           Stack.Prelude
import           Stack.Types.Config

-- | Parser for test arguments.

-- FIXME hide args

testOptsParser :: Bool -> Parser TestOptsMonoid
testOptsParser :: Bool -> Parser TestOptsMonoid
testOptsParser Bool
hide0 = FirstTrue
-> [String]
-> FirstFalse
-> FirstFalse
-> First (Maybe Int)
-> FirstTrue
-> TestOptsMonoid
TestOptsMonoid
  forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> String -> Mod FlagFields FirstTrue -> Parser FirstTrue
firstBoolFlagsTrue
        String
"rerun-tests"
        String
"running already successful tests"
        forall {f :: * -> *} {a}. Mod f a
hide
  forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat (forall (f :: * -> *) a. Alternative f => f a -> f [a]
many (Mod OptionFields [String] -> Parser [String]
argsOption
        (  forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"test-arguments"
        forall a. Semigroup a => a -> a -> a
<> forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"ta"
        forall a. Semigroup a => a -> a -> a
<> forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
metavar String
"TEST_ARGS"
        forall a. Semigroup a => a -> a -> a
<> forall (f :: * -> *) a. String -> Mod f a
help String
"Arguments passed in to the test suite program"
        forall a. Semigroup a => a -> a -> a
<> forall {f :: * -> *} {a}. Mod f a
hide
        )))
  forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (f :: * -> *). Alternative f => f Bool -> f FirstFalse
optionalFirstFalse (forall a. a -> Mod FlagFields a -> Parser a
flag' Bool
True
        (  forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"coverage"
        forall a. Semigroup a => a -> a -> a
<> forall (f :: * -> *) a. String -> Mod f a
help String
"Generate a code coverage report"
        forall a. Semigroup a => a -> a -> a
<> forall {f :: * -> *} {a}. Mod f a
hide
        ))
  forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (f :: * -> *). Alternative f => f Bool -> f FirstFalse
optionalFirstFalse (forall a. a -> Mod FlagFields a -> Parser a
flag' Bool
True
        (  forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"no-run-tests"
        forall a. Semigroup a => a -> a -> a
<> forall (f :: * -> *) a. String -> Mod f a
help String
"Disable running of tests. (Tests will still be built.)"
        forall a. Semigroup a => a -> a -> a
<> forall {f :: * -> *} {a}. Mod f a
hide
        ))
  forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (f :: * -> *) a. Alternative f => f a -> f (First a)
optionalFirst (forall a. ReadM a -> Mod OptionFields a -> Parser a
option (forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. a -> Maybe a
Just forall a. Read a => ReadM a
auto)
        (  forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"test-suite-timeout"
        forall a. Semigroup a => a -> a -> a
<> forall (f :: * -> *) a. String -> Mod f a
help String
"Maximum test suite run time in seconds."
        forall a. Semigroup a => a -> a -> a
<> forall {f :: * -> *} {a}. Mod f a
hide
        ))
  forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> String -> String -> Mod FlagFields FirstTrue -> Parser FirstTrue
firstBoolFlagsTrue
        String
"tests-allow-stdin"
        String
"allow standard input in test executables"
        forall {f :: * -> *} {a}. Mod f a
hide
 where
  hide :: Mod f a
hide = forall (f :: * -> *) a. Bool -> Mod f a
hideMods Bool
hide0