{-# LANGUAGE NoImplicitPrelude #-}
module Stack.Options.BuildMonoidParser
( buildOptsMonoidParser
, cabalVerboseParser
, cabalVerbosityOptsParser
, cabalVerbosityParser
) where
import qualified Data.Text as T
import Distribution.Parsec ( eitherParsec )
import Options.Applicative
( Parser, eitherReader, flag, help, long, metavar, option
, strOption
)
import Options.Applicative.Builder.Extra
( firstBoolFlagsFalse, firstBoolFlagsNoDefault
, firstBoolFlagsTrue, optionalFirst
)
import Stack.Build ( splitObjsWarning )
import Stack.Prelude
import Stack.Options.BenchParser ( benchOptsParser )
import Stack.Options.TestParser ( testOptsParser )
import Stack.Options.HaddockParser ( haddockOptsParser )
import Stack.Options.Utils ( GlobalOptsContext (..), hideMods )
import Stack.Types.BuildOpts
( BuildOptsMonoid (..), CabalVerbosity, readProgressBarFormat
, toFirstCabalVerbosity
)
buildOptsMonoidParser :: GlobalOptsContext -> Parser BuildOptsMonoid
buildOptsMonoidParser :: GlobalOptsContext -> Parser BuildOptsMonoid
buildOptsMonoidParser GlobalOptsContext
hide0 = Any
-> Any
-> Any
-> FirstFalse
-> FirstFalse
-> FirstTrue
-> FirstTrue
-> FirstFalse
-> HaddockOptsMonoid
-> FirstFalse
-> First Bool
-> FirstFalse
-> FirstTrue
-> FirstFalse
-> FirstFalse
-> FirstFalse
-> FirstFalse
-> First Bool
-> FirstFalse
-> FirstFalse
-> FirstFalse
-> TestOptsMonoid
-> FirstFalse
-> BenchmarkOptsMonoid
-> FirstFalse
-> First CabalVerbosity
-> FirstFalse
-> [Text]
-> FirstTrue
-> First ProgressBarFormat
-> First Text
-> BuildOptsMonoid
BuildOptsMonoid
(Any
-> Any
-> Any
-> FirstFalse
-> FirstFalse
-> FirstTrue
-> FirstTrue
-> FirstFalse
-> HaddockOptsMonoid
-> FirstFalse
-> First Bool
-> FirstFalse
-> FirstTrue
-> FirstFalse
-> FirstFalse
-> FirstFalse
-> FirstFalse
-> First Bool
-> FirstFalse
-> FirstFalse
-> FirstFalse
-> TestOptsMonoid
-> FirstFalse
-> BenchmarkOptsMonoid
-> FirstFalse
-> First CabalVerbosity
-> FirstFalse
-> [Text]
-> FirstTrue
-> First ProgressBarFormat
-> First Text
-> BuildOptsMonoid)
-> Parser Any
-> Parser
(Any
-> Any
-> FirstFalse
-> FirstFalse
-> FirstTrue
-> FirstTrue
-> FirstFalse
-> HaddockOptsMonoid
-> FirstFalse
-> First Bool
-> FirstFalse
-> FirstTrue
-> FirstFalse
-> FirstFalse
-> FirstFalse
-> FirstFalse
-> First Bool
-> FirstFalse
-> FirstFalse
-> FirstFalse
-> TestOptsMonoid
-> FirstFalse
-> BenchmarkOptsMonoid
-> FirstFalse
-> First CabalVerbosity
-> FirstFalse
-> [Text]
-> FirstTrue
-> First ProgressBarFormat
-> First Text
-> BuildOptsMonoid)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser Any
trace'
Parser
(Any
-> Any
-> FirstFalse
-> FirstFalse
-> FirstTrue
-> FirstTrue
-> FirstFalse
-> HaddockOptsMonoid
-> FirstFalse
-> First Bool
-> FirstFalse
-> FirstTrue
-> FirstFalse
-> FirstFalse
-> FirstFalse
-> FirstFalse
-> First Bool
-> FirstFalse
-> FirstFalse
-> FirstFalse
-> TestOptsMonoid
-> FirstFalse
-> BenchmarkOptsMonoid
-> FirstFalse
-> First CabalVerbosity
-> FirstFalse
-> [Text]
-> FirstTrue
-> First ProgressBarFormat
-> First Text
-> BuildOptsMonoid)
-> Parser Any
-> Parser
(Any
-> FirstFalse
-> FirstFalse
-> FirstTrue
-> FirstTrue
-> FirstFalse
-> HaddockOptsMonoid
-> FirstFalse
-> First Bool
-> FirstFalse
-> FirstTrue
-> FirstFalse
-> FirstFalse
-> FirstFalse
-> FirstFalse
-> First Bool
-> FirstFalse
-> FirstFalse
-> FirstFalse
-> TestOptsMonoid
-> FirstFalse
-> BenchmarkOptsMonoid
-> FirstFalse
-> First CabalVerbosity
-> FirstFalse
-> [Text]
-> FirstTrue
-> First ProgressBarFormat
-> First Text
-> BuildOptsMonoid)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Any
profile
Parser
(Any
-> FirstFalse
-> FirstFalse
-> FirstTrue
-> FirstTrue
-> FirstFalse
-> HaddockOptsMonoid
-> FirstFalse
-> First Bool
-> FirstFalse
-> FirstTrue
-> FirstFalse
-> FirstFalse
-> FirstFalse
-> FirstFalse
-> First Bool
-> FirstFalse
-> FirstFalse
-> FirstFalse
-> TestOptsMonoid
-> FirstFalse
-> BenchmarkOptsMonoid
-> FirstFalse
-> First CabalVerbosity
-> FirstFalse
-> [Text]
-> FirstTrue
-> First ProgressBarFormat
-> First Text
-> BuildOptsMonoid)
-> Parser Any
-> Parser
(FirstFalse
-> FirstFalse
-> FirstTrue
-> FirstTrue
-> FirstFalse
-> HaddockOptsMonoid
-> FirstFalse
-> First Bool
-> FirstFalse
-> FirstTrue
-> FirstFalse
-> FirstFalse
-> FirstFalse
-> FirstFalse
-> First Bool
-> FirstFalse
-> FirstFalse
-> FirstFalse
-> TestOptsMonoid
-> FirstFalse
-> BenchmarkOptsMonoid
-> FirstFalse
-> First CabalVerbosity
-> FirstFalse
-> [Text]
-> FirstTrue
-> First ProgressBarFormat
-> First Text
-> BuildOptsMonoid)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Any
noStrip
Parser
(FirstFalse
-> FirstFalse
-> FirstTrue
-> FirstTrue
-> FirstFalse
-> HaddockOptsMonoid
-> FirstFalse
-> First Bool
-> FirstFalse
-> FirstTrue
-> FirstFalse
-> FirstFalse
-> FirstFalse
-> FirstFalse
-> First Bool
-> FirstFalse
-> FirstFalse
-> FirstFalse
-> TestOptsMonoid
-> FirstFalse
-> BenchmarkOptsMonoid
-> FirstFalse
-> First CabalVerbosity
-> FirstFalse
-> [Text]
-> FirstTrue
-> First ProgressBarFormat
-> First Text
-> BuildOptsMonoid)
-> Parser FirstFalse
-> Parser
(FirstFalse
-> FirstTrue
-> FirstTrue
-> FirstFalse
-> HaddockOptsMonoid
-> FirstFalse
-> First Bool
-> FirstFalse
-> FirstTrue
-> FirstFalse
-> FirstFalse
-> FirstFalse
-> FirstFalse
-> First Bool
-> FirstFalse
-> FirstFalse
-> FirstFalse
-> TestOptsMonoid
-> FirstFalse
-> BenchmarkOptsMonoid
-> FirstFalse
-> First CabalVerbosity
-> FirstFalse
-> [Text]
-> FirstTrue
-> First ProgressBarFormat
-> First Text
-> BuildOptsMonoid)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser FirstFalse
libProfiling
Parser
(FirstFalse
-> FirstTrue
-> FirstTrue
-> FirstFalse
-> HaddockOptsMonoid
-> FirstFalse
-> First Bool
-> FirstFalse
-> FirstTrue
-> FirstFalse
-> FirstFalse
-> FirstFalse
-> FirstFalse
-> First Bool
-> FirstFalse
-> FirstFalse
-> FirstFalse
-> TestOptsMonoid
-> FirstFalse
-> BenchmarkOptsMonoid
-> FirstFalse
-> First CabalVerbosity
-> FirstFalse
-> [Text]
-> FirstTrue
-> First ProgressBarFormat
-> First Text
-> BuildOptsMonoid)
-> Parser FirstFalse
-> Parser
(FirstTrue
-> FirstTrue
-> FirstFalse
-> HaddockOptsMonoid
-> FirstFalse
-> First Bool
-> FirstFalse
-> FirstTrue
-> FirstFalse
-> FirstFalse
-> FirstFalse
-> FirstFalse
-> First Bool
-> FirstFalse
-> FirstFalse
-> FirstFalse
-> TestOptsMonoid
-> FirstFalse
-> BenchmarkOptsMonoid
-> FirstFalse
-> First CabalVerbosity
-> FirstFalse
-> [Text]
-> FirstTrue
-> First ProgressBarFormat
-> First Text
-> BuildOptsMonoid)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser FirstFalse
exeProfiling
Parser
(FirstTrue
-> FirstTrue
-> FirstFalse
-> HaddockOptsMonoid
-> FirstFalse
-> First Bool
-> FirstFalse
-> FirstTrue
-> FirstFalse
-> FirstFalse
-> FirstFalse
-> FirstFalse
-> First Bool
-> FirstFalse
-> FirstFalse
-> FirstFalse
-> TestOptsMonoid
-> FirstFalse
-> BenchmarkOptsMonoid
-> FirstFalse
-> First CabalVerbosity
-> FirstFalse
-> [Text]
-> FirstTrue
-> First ProgressBarFormat
-> First Text
-> BuildOptsMonoid)
-> Parser FirstTrue
-> Parser
(FirstTrue
-> FirstFalse
-> HaddockOptsMonoid
-> FirstFalse
-> First Bool
-> FirstFalse
-> FirstTrue
-> FirstFalse
-> FirstFalse
-> FirstFalse
-> FirstFalse
-> First Bool
-> FirstFalse
-> FirstFalse
-> FirstFalse
-> TestOptsMonoid
-> FirstFalse
-> BenchmarkOptsMonoid
-> FirstFalse
-> First CabalVerbosity
-> FirstFalse
-> [Text]
-> FirstTrue
-> First ProgressBarFormat
-> First Text
-> BuildOptsMonoid)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser FirstTrue
libStripping
Parser
(FirstTrue
-> FirstFalse
-> HaddockOptsMonoid
-> FirstFalse
-> First Bool
-> FirstFalse
-> FirstTrue
-> FirstFalse
-> FirstFalse
-> FirstFalse
-> FirstFalse
-> First Bool
-> FirstFalse
-> FirstFalse
-> FirstFalse
-> TestOptsMonoid
-> FirstFalse
-> BenchmarkOptsMonoid
-> FirstFalse
-> First CabalVerbosity
-> FirstFalse
-> [Text]
-> FirstTrue
-> First ProgressBarFormat
-> First Text
-> BuildOptsMonoid)
-> Parser FirstTrue
-> Parser
(FirstFalse
-> HaddockOptsMonoid
-> FirstFalse
-> First Bool
-> FirstFalse
-> FirstTrue
-> FirstFalse
-> FirstFalse
-> FirstFalse
-> FirstFalse
-> First Bool
-> FirstFalse
-> FirstFalse
-> FirstFalse
-> TestOptsMonoid
-> FirstFalse
-> BenchmarkOptsMonoid
-> FirstFalse
-> First CabalVerbosity
-> FirstFalse
-> [Text]
-> FirstTrue
-> First ProgressBarFormat
-> First Text
-> BuildOptsMonoid)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser FirstTrue
exeStripping
Parser
(FirstFalse
-> HaddockOptsMonoid
-> FirstFalse
-> First Bool
-> FirstFalse
-> FirstTrue
-> FirstFalse
-> FirstFalse
-> FirstFalse
-> FirstFalse
-> First Bool
-> FirstFalse
-> FirstFalse
-> FirstFalse
-> TestOptsMonoid
-> FirstFalse
-> BenchmarkOptsMonoid
-> FirstFalse
-> First CabalVerbosity
-> FirstFalse
-> [Text]
-> FirstTrue
-> First ProgressBarFormat
-> First Text
-> BuildOptsMonoid)
-> Parser FirstFalse
-> Parser
(HaddockOptsMonoid
-> FirstFalse
-> First Bool
-> FirstFalse
-> FirstTrue
-> FirstFalse
-> FirstFalse
-> FirstFalse
-> FirstFalse
-> First Bool
-> FirstFalse
-> FirstFalse
-> FirstFalse
-> TestOptsMonoid
-> FirstFalse
-> BenchmarkOptsMonoid
-> FirstFalse
-> First CabalVerbosity
-> FirstFalse
-> [Text]
-> FirstTrue
-> First ProgressBarFormat
-> First Text
-> BuildOptsMonoid)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser FirstFalse
haddock
Parser
(HaddockOptsMonoid
-> FirstFalse
-> First Bool
-> FirstFalse
-> FirstTrue
-> FirstFalse
-> FirstFalse
-> FirstFalse
-> FirstFalse
-> First Bool
-> FirstFalse
-> FirstFalse
-> FirstFalse
-> TestOptsMonoid
-> FirstFalse
-> BenchmarkOptsMonoid
-> FirstFalse
-> First CabalVerbosity
-> FirstFalse
-> [Text]
-> FirstTrue
-> First ProgressBarFormat
-> First Text
-> BuildOptsMonoid)
-> Parser HaddockOptsMonoid
-> Parser
(FirstFalse
-> First Bool
-> FirstFalse
-> FirstTrue
-> FirstFalse
-> FirstFalse
-> FirstFalse
-> FirstFalse
-> First Bool
-> FirstFalse
-> FirstFalse
-> FirstFalse
-> TestOptsMonoid
-> FirstFalse
-> BenchmarkOptsMonoid
-> FirstFalse
-> First CabalVerbosity
-> FirstFalse
-> [Text]
-> FirstTrue
-> First ProgressBarFormat
-> First Text
-> BuildOptsMonoid)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Bool -> Parser HaddockOptsMonoid
haddockOptsParser Bool
hideBool
Parser
(FirstFalse
-> First Bool
-> FirstFalse
-> FirstTrue
-> FirstFalse
-> FirstFalse
-> FirstFalse
-> FirstFalse
-> First Bool
-> FirstFalse
-> FirstFalse
-> FirstFalse
-> TestOptsMonoid
-> FirstFalse
-> BenchmarkOptsMonoid
-> FirstFalse
-> First CabalVerbosity
-> FirstFalse
-> [Text]
-> FirstTrue
-> First ProgressBarFormat
-> First Text
-> BuildOptsMonoid)
-> Parser FirstFalse
-> Parser
(First Bool
-> FirstFalse
-> FirstTrue
-> FirstFalse
-> FirstFalse
-> FirstFalse
-> FirstFalse
-> First Bool
-> FirstFalse
-> FirstFalse
-> FirstFalse
-> TestOptsMonoid
-> FirstFalse
-> BenchmarkOptsMonoid
-> FirstFalse
-> First CabalVerbosity
-> FirstFalse
-> [Text]
-> FirstTrue
-> First ProgressBarFormat
-> First Text
-> BuildOptsMonoid)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser FirstFalse
openHaddocks
Parser
(First Bool
-> FirstFalse
-> FirstTrue
-> FirstFalse
-> FirstFalse
-> FirstFalse
-> FirstFalse
-> First Bool
-> FirstFalse
-> FirstFalse
-> FirstFalse
-> TestOptsMonoid
-> FirstFalse
-> BenchmarkOptsMonoid
-> FirstFalse
-> First CabalVerbosity
-> FirstFalse
-> [Text]
-> FirstTrue
-> First ProgressBarFormat
-> First Text
-> BuildOptsMonoid)
-> Parser (First Bool)
-> Parser
(FirstFalse
-> FirstTrue
-> FirstFalse
-> FirstFalse
-> FirstFalse
-> FirstFalse
-> First Bool
-> FirstFalse
-> FirstFalse
-> FirstFalse
-> TestOptsMonoid
-> FirstFalse
-> BenchmarkOptsMonoid
-> FirstFalse
-> First CabalVerbosity
-> FirstFalse
-> [Text]
-> FirstTrue
-> First ProgressBarFormat
-> First Text
-> BuildOptsMonoid)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser (First Bool)
haddockDeps
Parser
(FirstFalse
-> FirstTrue
-> FirstFalse
-> FirstFalse
-> FirstFalse
-> FirstFalse
-> First Bool
-> FirstFalse
-> FirstFalse
-> FirstFalse
-> TestOptsMonoid
-> FirstFalse
-> BenchmarkOptsMonoid
-> FirstFalse
-> First CabalVerbosity
-> FirstFalse
-> [Text]
-> FirstTrue
-> First ProgressBarFormat
-> First Text
-> BuildOptsMonoid)
-> Parser FirstFalse
-> Parser
(FirstTrue
-> FirstFalse
-> FirstFalse
-> FirstFalse
-> FirstFalse
-> First Bool
-> FirstFalse
-> FirstFalse
-> FirstFalse
-> TestOptsMonoid
-> FirstFalse
-> BenchmarkOptsMonoid
-> FirstFalse
-> First CabalVerbosity
-> FirstFalse
-> [Text]
-> FirstTrue
-> First ProgressBarFormat
-> First Text
-> BuildOptsMonoid)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser FirstFalse
haddockInternal
Parser
(FirstTrue
-> FirstFalse
-> FirstFalse
-> FirstFalse
-> FirstFalse
-> First Bool
-> FirstFalse
-> FirstFalse
-> FirstFalse
-> TestOptsMonoid
-> FirstFalse
-> BenchmarkOptsMonoid
-> FirstFalse
-> First CabalVerbosity
-> FirstFalse
-> [Text]
-> FirstTrue
-> First ProgressBarFormat
-> First Text
-> BuildOptsMonoid)
-> Parser FirstTrue
-> Parser
(FirstFalse
-> FirstFalse
-> FirstFalse
-> FirstFalse
-> First Bool
-> FirstFalse
-> FirstFalse
-> FirstFalse
-> TestOptsMonoid
-> FirstFalse
-> BenchmarkOptsMonoid
-> FirstFalse
-> First CabalVerbosity
-> FirstFalse
-> [Text]
-> FirstTrue
-> First ProgressBarFormat
-> First Text
-> BuildOptsMonoid)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser FirstTrue
haddockHyperlinkSource
Parser
(FirstFalse
-> FirstFalse
-> FirstFalse
-> FirstFalse
-> First Bool
-> FirstFalse
-> FirstFalse
-> FirstFalse
-> TestOptsMonoid
-> FirstFalse
-> BenchmarkOptsMonoid
-> FirstFalse
-> First CabalVerbosity
-> FirstFalse
-> [Text]
-> FirstTrue
-> First ProgressBarFormat
-> First Text
-> BuildOptsMonoid)
-> Parser FirstFalse
-> Parser
(FirstFalse
-> FirstFalse
-> FirstFalse
-> First Bool
-> FirstFalse
-> FirstFalse
-> FirstFalse
-> TestOptsMonoid
-> FirstFalse
-> BenchmarkOptsMonoid
-> FirstFalse
-> First CabalVerbosity
-> FirstFalse
-> [Text]
-> FirstTrue
-> First ProgressBarFormat
-> First Text
-> BuildOptsMonoid)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser FirstFalse
haddockForHackage
Parser
(FirstFalse
-> FirstFalse
-> FirstFalse
-> First Bool
-> FirstFalse
-> FirstFalse
-> FirstFalse
-> TestOptsMonoid
-> FirstFalse
-> BenchmarkOptsMonoid
-> FirstFalse
-> First CabalVerbosity
-> FirstFalse
-> [Text]
-> FirstTrue
-> First ProgressBarFormat
-> First Text
-> BuildOptsMonoid)
-> Parser FirstFalse
-> Parser
(FirstFalse
-> FirstFalse
-> First Bool
-> FirstFalse
-> FirstFalse
-> FirstFalse
-> TestOptsMonoid
-> FirstFalse
-> BenchmarkOptsMonoid
-> FirstFalse
-> First CabalVerbosity
-> FirstFalse
-> [Text]
-> FirstTrue
-> First ProgressBarFormat
-> First Text
-> BuildOptsMonoid)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser FirstFalse
copyBins
Parser
(FirstFalse
-> FirstFalse
-> First Bool
-> FirstFalse
-> FirstFalse
-> FirstFalse
-> TestOptsMonoid
-> FirstFalse
-> BenchmarkOptsMonoid
-> FirstFalse
-> First CabalVerbosity
-> FirstFalse
-> [Text]
-> FirstTrue
-> First ProgressBarFormat
-> First Text
-> BuildOptsMonoid)
-> Parser FirstFalse
-> Parser
(FirstFalse
-> First Bool
-> FirstFalse
-> FirstFalse
-> FirstFalse
-> TestOptsMonoid
-> FirstFalse
-> BenchmarkOptsMonoid
-> FirstFalse
-> First CabalVerbosity
-> FirstFalse
-> [Text]
-> FirstTrue
-> First ProgressBarFormat
-> First Text
-> BuildOptsMonoid)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser FirstFalse
copyCompilerTool
Parser
(FirstFalse
-> First Bool
-> FirstFalse
-> FirstFalse
-> FirstFalse
-> TestOptsMonoid
-> FirstFalse
-> BenchmarkOptsMonoid
-> FirstFalse
-> First CabalVerbosity
-> FirstFalse
-> [Text]
-> FirstTrue
-> First ProgressBarFormat
-> First Text
-> BuildOptsMonoid)
-> Parser FirstFalse
-> Parser
(First Bool
-> FirstFalse
-> FirstFalse
-> FirstFalse
-> TestOptsMonoid
-> FirstFalse
-> BenchmarkOptsMonoid
-> FirstFalse
-> First CabalVerbosity
-> FirstFalse
-> [Text]
-> FirstTrue
-> First ProgressBarFormat
-> First Text
-> BuildOptsMonoid)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser FirstFalse
preFetch
Parser
(First Bool
-> FirstFalse
-> FirstFalse
-> FirstFalse
-> TestOptsMonoid
-> FirstFalse
-> BenchmarkOptsMonoid
-> FirstFalse
-> First CabalVerbosity
-> FirstFalse
-> [Text]
-> FirstTrue
-> First ProgressBarFormat
-> First Text
-> BuildOptsMonoid)
-> Parser (First Bool)
-> Parser
(FirstFalse
-> FirstFalse
-> FirstFalse
-> TestOptsMonoid
-> FirstFalse
-> BenchmarkOptsMonoid
-> FirstFalse
-> First CabalVerbosity
-> FirstFalse
-> [Text]
-> FirstTrue
-> First ProgressBarFormat
-> First Text
-> BuildOptsMonoid)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser (First Bool)
keepGoing
Parser
(FirstFalse
-> FirstFalse
-> FirstFalse
-> TestOptsMonoid
-> FirstFalse
-> BenchmarkOptsMonoid
-> FirstFalse
-> First CabalVerbosity
-> FirstFalse
-> [Text]
-> FirstTrue
-> First ProgressBarFormat
-> First Text
-> BuildOptsMonoid)
-> Parser FirstFalse
-> Parser
(FirstFalse
-> FirstFalse
-> TestOptsMonoid
-> FirstFalse
-> BenchmarkOptsMonoid
-> FirstFalse
-> First CabalVerbosity
-> FirstFalse
-> [Text]
-> FirstTrue
-> First ProgressBarFormat
-> First Text
-> BuildOptsMonoid)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser FirstFalse
keepTmpFiles
Parser
(FirstFalse
-> FirstFalse
-> TestOptsMonoid
-> FirstFalse
-> BenchmarkOptsMonoid
-> FirstFalse
-> First CabalVerbosity
-> FirstFalse
-> [Text]
-> FirstTrue
-> First ProgressBarFormat
-> First Text
-> BuildOptsMonoid)
-> Parser FirstFalse
-> Parser
(FirstFalse
-> TestOptsMonoid
-> FirstFalse
-> BenchmarkOptsMonoid
-> FirstFalse
-> First CabalVerbosity
-> FirstFalse
-> [Text]
-> FirstTrue
-> First ProgressBarFormat
-> First Text
-> BuildOptsMonoid)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser FirstFalse
forceDirty
Parser
(FirstFalse
-> TestOptsMonoid
-> FirstFalse
-> BenchmarkOptsMonoid
-> FirstFalse
-> First CabalVerbosity
-> FirstFalse
-> [Text]
-> FirstTrue
-> First ProgressBarFormat
-> First Text
-> BuildOptsMonoid)
-> Parser FirstFalse
-> Parser
(TestOptsMonoid
-> FirstFalse
-> BenchmarkOptsMonoid
-> FirstFalse
-> First CabalVerbosity
-> FirstFalse
-> [Text]
-> FirstTrue
-> First ProgressBarFormat
-> First Text
-> BuildOptsMonoid)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser FirstFalse
tests
Parser
(TestOptsMonoid
-> FirstFalse
-> BenchmarkOptsMonoid
-> FirstFalse
-> First CabalVerbosity
-> FirstFalse
-> [Text]
-> FirstTrue
-> First ProgressBarFormat
-> First Text
-> BuildOptsMonoid)
-> Parser TestOptsMonoid
-> Parser
(FirstFalse
-> BenchmarkOptsMonoid
-> FirstFalse
-> First CabalVerbosity
-> FirstFalse
-> [Text]
-> FirstTrue
-> First ProgressBarFormat
-> First Text
-> BuildOptsMonoid)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Bool -> Parser TestOptsMonoid
testOptsParser Bool
hideBool
Parser
(FirstFalse
-> BenchmarkOptsMonoid
-> FirstFalse
-> First CabalVerbosity
-> FirstFalse
-> [Text]
-> FirstTrue
-> First ProgressBarFormat
-> First Text
-> BuildOptsMonoid)
-> Parser FirstFalse
-> Parser
(BenchmarkOptsMonoid
-> FirstFalse
-> First CabalVerbosity
-> FirstFalse
-> [Text]
-> FirstTrue
-> First ProgressBarFormat
-> First Text
-> BuildOptsMonoid)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser FirstFalse
benches
Parser
(BenchmarkOptsMonoid
-> FirstFalse
-> First CabalVerbosity
-> FirstFalse
-> [Text]
-> FirstTrue
-> First ProgressBarFormat
-> First Text
-> BuildOptsMonoid)
-> Parser BenchmarkOptsMonoid
-> Parser
(FirstFalse
-> First CabalVerbosity
-> FirstFalse
-> [Text]
-> FirstTrue
-> First ProgressBarFormat
-> First Text
-> BuildOptsMonoid)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Bool -> Parser BenchmarkOptsMonoid
benchOptsParser Bool
hideBool
Parser
(FirstFalse
-> First CabalVerbosity
-> FirstFalse
-> [Text]
-> FirstTrue
-> First ProgressBarFormat
-> First Text
-> BuildOptsMonoid)
-> Parser FirstFalse
-> Parser
(First CabalVerbosity
-> FirstFalse
-> [Text]
-> FirstTrue
-> First ProgressBarFormat
-> First Text
-> BuildOptsMonoid)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser FirstFalse
reconfigure
Parser
(First CabalVerbosity
-> FirstFalse
-> [Text]
-> FirstTrue
-> First ProgressBarFormat
-> First Text
-> BuildOptsMonoid)
-> Parser (First CabalVerbosity)
-> Parser
(FirstFalse
-> [Text]
-> FirstTrue
-> First ProgressBarFormat
-> First Text
-> BuildOptsMonoid)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser (First CabalVerbosity)
cabalVerbose
Parser
(FirstFalse
-> [Text]
-> FirstTrue
-> First ProgressBarFormat
-> First Text
-> BuildOptsMonoid)
-> Parser FirstFalse
-> Parser
([Text]
-> FirstTrue
-> First ProgressBarFormat
-> First Text
-> BuildOptsMonoid)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser FirstFalse
splitObjs
Parser
([Text]
-> FirstTrue
-> First ProgressBarFormat
-> First Text
-> BuildOptsMonoid)
-> Parser [Text]
-> Parser
(FirstTrue
-> First ProgressBarFormat -> First Text -> BuildOptsMonoid)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser [Text]
skipComponents
Parser
(FirstTrue
-> First ProgressBarFormat -> First Text -> BuildOptsMonoid)
-> Parser FirstTrue
-> Parser
(First ProgressBarFormat -> First Text -> BuildOptsMonoid)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser FirstTrue
interleavedOutput
Parser (First ProgressBarFormat -> First Text -> BuildOptsMonoid)
-> Parser (First ProgressBarFormat)
-> Parser (First Text -> BuildOptsMonoid)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser (First ProgressBarFormat)
progressBar
Parser (First Text -> BuildOptsMonoid)
-> Parser (First Text) -> Parser BuildOptsMonoid
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser (First Text)
ddumpDir
where
hideBool :: Bool
hideBool = GlobalOptsContext
hide0 GlobalOptsContext -> GlobalOptsContext -> Bool
forall a. Eq a => a -> a -> Bool
/= GlobalOptsContext
BuildCmdGlobalOpts
hide :: Mod f a
hide = Bool -> Mod f a
forall (f :: * -> *) a. Bool -> Mod f a
hideMods Bool
hideBool
hideExceptGhci :: Mod f a
hideExceptGhci =
Bool -> Mod f a
forall (f :: * -> *) a. Bool -> Mod f a
hideMods (GlobalOptsContext
hide0 GlobalOptsContext -> [GlobalOptsContext] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`notElem` [GlobalOptsContext
BuildCmdGlobalOpts, GlobalOptsContext
GhciCmdGlobalOpts])
trace' :: Parser Any
trace' = Bool -> Any
Any (Bool -> Any) -> Parser Bool -> Parser Any
forall (f :: * -> *) a b. Functor 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
"trace"
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
"Enable profiling in libraries, executables, etc. for all \
\expressions and generate a backtrace on 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
hideExceptGhci
)
profile :: Parser Any
profile = Bool -> Any
Any (Bool -> Any) -> Parser Bool -> Parser Any
forall (f :: * -> *) a b. Functor 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
"profile"
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
"Enable profiling in libraries, executables, etc. for all \
\expressions and generate a profiling report in tests or \
\benchmarks."
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
hideExceptGhci
)
noStrip :: Parser Any
noStrip = Bool -> Any
Any (Bool -> Any) -> Parser Bool -> Parser Any
forall (f :: * -> *) a b. Functor 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
"no-strip"
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
"Disable DWARF debugging symbol stripping in libraries, \
\executables, etc. for all expressions, producing larger \
\executables but allowing the use of standard \
\debuggers/profiling tools/other utilities that use \
\debugging symbols."
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
hideExceptGhci
)
libProfiling :: Parser FirstFalse
libProfiling = String -> String -> Mod FlagFields FirstFalse -> Parser FirstFalse
firstBoolFlagsFalse
String
"library-profiling"
String
"library profiling for TARGETs and all its dependencies."
Mod FlagFields FirstFalse
forall {f :: * -> *} {a}. Mod f a
hide
exeProfiling :: Parser FirstFalse
exeProfiling = String -> String -> Mod FlagFields FirstFalse -> Parser FirstFalse
firstBoolFlagsFalse
String
"executable-profiling"
String
"executable profiling for TARGETs and all its dependencies."
Mod FlagFields FirstFalse
forall {f :: * -> *} {a}. Mod f a
hide
libStripping :: Parser FirstTrue
libStripping = String -> String -> Mod FlagFields FirstTrue -> Parser FirstTrue
firstBoolFlagsTrue
String
"library-stripping"
String
"library stripping for TARGETs and all its dependencies."
Mod FlagFields FirstTrue
forall {f :: * -> *} {a}. Mod f a
hide
exeStripping :: Parser FirstTrue
exeStripping = String -> String -> Mod FlagFields FirstTrue -> Parser FirstTrue
firstBoolFlagsTrue
String
"executable-stripping"
String
"executable stripping for TARGETs and all its dependencies."
Mod FlagFields FirstTrue
forall {f :: * -> *} {a}. Mod f a
hide
haddock :: Parser FirstFalse
haddock = String -> String -> Mod FlagFields FirstFalse -> Parser FirstFalse
firstBoolFlagsFalse
String
"haddock"
String
"generating Haddock documentation for the package(s) in this \
\directory/configuration."
Mod FlagFields FirstFalse
forall {f :: * -> *} {a}. Mod f a
hide
openHaddocks :: Parser FirstFalse
openHaddocks = String -> String -> Mod FlagFields FirstFalse -> Parser FirstFalse
firstBoolFlagsFalse
String
"open"
String
"opening the local Haddock documentation in the browser."
Mod FlagFields FirstFalse
forall {f :: * -> *} {a}. Mod f a
hide
haddockDeps :: Parser (First Bool)
haddockDeps = String
-> String -> Mod FlagFields (Maybe Bool) -> Parser (First Bool)
firstBoolFlagsNoDefault
String
"haddock-deps"
String
"building Haddock documentation for dependencies. (default: if building \
\Haddock documentation, true; otherwise, false)"
Mod FlagFields (Maybe Bool)
forall {f :: * -> *} {a}. Mod f a
hide
haddockInternal :: Parser FirstFalse
haddockInternal = String -> String -> Mod FlagFields FirstFalse -> Parser FirstFalse
firstBoolFlagsFalse
String
"haddock-internal"
String
"building Haddock documentation for internal modules (like \
\'cabal haddock --internal')."
Mod FlagFields FirstFalse
forall {f :: * -> *} {a}. Mod f a
hide
haddockHyperlinkSource :: Parser FirstTrue
haddockHyperlinkSource = String -> String -> Mod FlagFields FirstTrue -> Parser FirstTrue
firstBoolFlagsTrue
String
"haddock-hyperlink-source"
String
"building hyperlinked source for Haddock documentation (like \
\'haddock --hyperlinked-source')."
Mod FlagFields FirstTrue
forall {f :: * -> *} {a}. Mod f a
hide
haddockForHackage :: Parser FirstFalse
haddockForHackage = String -> String -> Mod FlagFields FirstFalse -> Parser FirstFalse
firstBoolFlagsFalse
String
"haddock-for-hackage"
String
"building with flags to generate Haddock documentation suitable for upload \
\to Hackage."
Mod FlagFields FirstFalse
forall {f :: * -> *} {a}. Mod f a
hide
copyBins :: Parser FirstFalse
copyBins = String -> String -> Mod FlagFields FirstFalse -> Parser FirstFalse
firstBoolFlagsFalse
String
"copy-bins"
String
"copying binaries to local-bin (see 'stack path')."
Mod FlagFields FirstFalse
forall {f :: * -> *} {a}. Mod f a
hide
copyCompilerTool :: Parser FirstFalse
copyCompilerTool = String -> String -> Mod FlagFields FirstFalse -> Parser FirstFalse
firstBoolFlagsFalse
String
"copy-compiler-tool"
String
"copying binaries of targets to compiler-tools-bin (see 'stack path')."
Mod FlagFields FirstFalse
forall {f :: * -> *} {a}. Mod f a
hide
keepGoing :: Parser (First Bool)
keepGoing = String
-> String -> Mod FlagFields (Maybe Bool) -> Parser (First Bool)
firstBoolFlagsNoDefault
String
"keep-going"
String
"continue running after a step fails. (default: for 'build', false; for \
\'test' or 'bench', true)"
Mod FlagFields (Maybe Bool)
forall {f :: * -> *} {a}. Mod f a
hide
keepTmpFiles :: Parser FirstFalse
keepTmpFiles = String -> String -> Mod FlagFields FirstFalse -> Parser FirstFalse
firstBoolFlagsFalse
String
"keep-tmp-files"
String
"keep intermediate files and build directories."
Mod FlagFields FirstFalse
forall {f :: * -> *} {a}. Mod f a
hide
preFetch :: Parser FirstFalse
preFetch = String -> String -> Mod FlagFields FirstFalse -> Parser FirstFalse
firstBoolFlagsFalse
String
"prefetch"
String
"fetching packages necessary for the build immediately. Useful with \
\--dry-run."
Mod FlagFields FirstFalse
forall {f :: * -> *} {a}. Mod f a
hide
forceDirty :: Parser FirstFalse
forceDirty = String -> String -> Mod FlagFields FirstFalse -> Parser FirstFalse
firstBoolFlagsFalse
String
"force-dirty"
String
"forcing the treatment of all local packages as having dirty files. \
\Useful for cases where Stack can't detect a file change."
Mod FlagFields FirstFalse
forall {f :: * -> *} {a}. Mod f a
hide
tests :: Parser FirstFalse
tests = String -> String -> Mod FlagFields FirstFalse -> Parser FirstFalse
firstBoolFlagsFalse
String
"test"
String
"testing the package(s) in this directory/configuration."
Mod FlagFields FirstFalse
forall {f :: * -> *} {a}. Mod f a
hideExceptGhci
benches :: Parser FirstFalse
benches = String -> String -> Mod FlagFields FirstFalse -> Parser FirstFalse
firstBoolFlagsFalse
String
"bench"
String
"benchmarking the package(s) in this directory/configuration."
Mod FlagFields FirstFalse
forall {f :: * -> *} {a}. Mod f a
hideExceptGhci
reconfigure :: Parser FirstFalse
reconfigure = String -> String -> Mod FlagFields FirstFalse -> Parser FirstFalse
firstBoolFlagsFalse
String
"reconfigure"
String
"performing the configure step, even if unnecessary. Useful in some \
\corner cases with custom Setup.hs files."
Mod FlagFields FirstFalse
forall {f :: * -> *} {a}. Mod f a
hide
cabalVerbose :: Parser (First CabalVerbosity)
cabalVerbose = Bool -> Parser (First CabalVerbosity)
cabalVerbosityOptsParser Bool
hideBool
splitObjs :: Parser FirstFalse
splitObjs = String -> String -> Mod FlagFields FirstFalse -> Parser FirstFalse
firstBoolFlagsFalse
String
"split-objs"
( String
"split-objs, to reduce output size (at the cost of build time). "
String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
splitObjsWarning
)
Mod FlagFields FirstFalse
forall {f :: * -> *} {a}. Mod f a
hide
skipComponents :: Parser [Text]
skipComponents = Parser Text -> Parser [Text]
forall a. Parser a -> Parser [a]
forall (f :: * -> *) a. Alternative f => f a -> f [a]
many ((String -> Text) -> Parser String -> Parser Text
forall a b. (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap String -> Text
T.pack (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
"skip"
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
"Skip given component (can be specified multiple times)."
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
hide
)))
interleavedOutput :: Parser FirstTrue
interleavedOutput = String -> String -> Mod FlagFields FirstTrue -> Parser FirstTrue
firstBoolFlagsTrue
String
"interleaved-output"
String
"printing concurrent GHC output to the console with a prefix for the \
\package name."
Mod FlagFields FirstTrue
forall {f :: * -> *} {a}. Mod f a
hide
progressBar :: Parser (First ProgressBarFormat)
progressBar = Maybe ProgressBarFormat -> First ProgressBarFormat
forall a. Maybe a -> First a
First (Maybe ProgressBarFormat -> First ProgressBarFormat)
-> Parser (Maybe ProgressBarFormat)
-> Parser (First ProgressBarFormat)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser ProgressBarFormat -> Parser (Maybe ProgressBarFormat)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (ReadM ProgressBarFormat
-> Mod OptionFields ProgressBarFormat -> Parser ProgressBarFormat
forall a. ReadM a -> Mod OptionFields a -> Parser a
option ((String -> Either String ProgressBarFormat)
-> ReadM ProgressBarFormat
forall a. (String -> Either String a) -> ReadM a
eitherReader String -> Either String ProgressBarFormat
readProgressBarFormat)
( String -> Mod OptionFields ProgressBarFormat
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"progress-bar"
Mod OptionFields ProgressBarFormat
-> Mod OptionFields ProgressBarFormat
-> Mod OptionFields ProgressBarFormat
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields ProgressBarFormat
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
metavar String
"FORMAT"
Mod OptionFields ProgressBarFormat
-> Mod OptionFields ProgressBarFormat
-> Mod OptionFields ProgressBarFormat
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields ProgressBarFormat
forall (f :: * -> *) a. String -> Mod f a
help String
"Progress bar format (accepts none, count-only, capped and full). \
\(default: capped)"
Mod OptionFields ProgressBarFormat
-> Mod OptionFields ProgressBarFormat
-> Mod OptionFields ProgressBarFormat
forall a. Semigroup a => a -> a -> a
<> Mod OptionFields ProgressBarFormat
forall {f :: * -> *} {a}. Mod f a
hide
))
ddumpDir :: Parser (First Text)
ddumpDir = Parser Text -> Parser (First Text)
forall (f :: * -> *) a. Alternative f => f a -> f (First a)
optionalFirst (Mod OptionFields Text -> Parser Text
forall s. IsString s => Mod OptionFields s -> Parser s
strOption
( String -> Mod OptionFields Text
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"ddump-dir"
Mod OptionFields Text
-> Mod OptionFields Text -> Mod OptionFields Text
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields Text
forall (f :: * -> *) a. String -> Mod f a
help String
"Specify output directory for ddump-files."
Mod OptionFields Text
-> Mod OptionFields Text -> Mod OptionFields Text
forall a. Semigroup a => a -> a -> a
<> Mod OptionFields Text
forall {f :: * -> *} {a}. Mod f a
hide
))
cabalVerbosityOptsParser :: Bool -> Parser (First CabalVerbosity)
cabalVerbosityOptsParser :: Bool -> Parser (First CabalVerbosity)
cabalVerbosityOptsParser Bool
hide =
Bool -> Parser (First CabalVerbosity)
cabalVerbosityParser Bool
hide Parser (First CabalVerbosity)
-> Parser (First CabalVerbosity) -> Parser (First CabalVerbosity)
forall a. Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Bool -> Parser (First CabalVerbosity)
cabalVerboseParser Bool
hide
cabalVerbosityParser :: Bool -> Parser (First CabalVerbosity)
cabalVerbosityParser :: Bool -> Parser (First CabalVerbosity)
cabalVerbosityParser Bool
hide =
let pCabalVerbosity :: Parser CabalVerbosity
pCabalVerbosity = ReadM CabalVerbosity
-> Mod OptionFields CabalVerbosity -> Parser CabalVerbosity
forall a. ReadM a -> Mod OptionFields a -> Parser a
option ((String -> Either String CabalVerbosity) -> ReadM CabalVerbosity
forall a. (String -> Either String a) -> ReadM a
eitherReader String -> Either String CabalVerbosity
forall a. Parsec a => String -> Either String a
eitherParsec)
( String -> Mod OptionFields CabalVerbosity
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"cabal-verbosity"
Mod OptionFields CabalVerbosity
-> Mod OptionFields CabalVerbosity
-> Mod OptionFields CabalVerbosity
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields CabalVerbosity
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
metavar String
"VERBOSITY"
Mod OptionFields CabalVerbosity
-> Mod OptionFields CabalVerbosity
-> Mod OptionFields CabalVerbosity
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields CabalVerbosity
forall (f :: * -> *) a. String -> Mod f a
help String
"Cabal verbosity (accepts Cabal's numerical and extended \
\syntax)."
Mod OptionFields CabalVerbosity
-> Mod OptionFields CabalVerbosity
-> Mod OptionFields CabalVerbosity
forall a. Semigroup a => a -> a -> a
<> Bool -> Mod OptionFields CabalVerbosity
forall (f :: * -> *) a. Bool -> Mod f a
hideMods Bool
hide)
in Maybe CabalVerbosity -> First CabalVerbosity
forall a. Maybe a -> First a
First (Maybe CabalVerbosity -> First CabalVerbosity)
-> (CabalVerbosity -> Maybe CabalVerbosity)
-> CabalVerbosity
-> First CabalVerbosity
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CabalVerbosity -> Maybe CabalVerbosity
forall a. a -> Maybe a
Just (CabalVerbosity -> First CabalVerbosity)
-> Parser CabalVerbosity -> Parser (First CabalVerbosity)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser CabalVerbosity
pCabalVerbosity
cabalVerboseParser :: Bool -> Parser (First CabalVerbosity)
cabalVerboseParser :: Bool -> Parser (First CabalVerbosity)
cabalVerboseParser Bool
hide =
let pVerboseFlag :: Parser FirstFalse
pVerboseFlag = String -> String -> Mod FlagFields FirstFalse -> Parser FirstFalse
firstBoolFlagsFalse
String
"cabal-verbose"
String
"asking Cabal to be verbose in its output."
(Bool -> Mod FlagFields FirstFalse
forall (f :: * -> *) a. Bool -> Mod f a
hideMods Bool
hide)
in FirstFalse -> First CabalVerbosity
toFirstCabalVerbosity (FirstFalse -> First CabalVerbosity)
-> Parser FirstFalse -> Parser (First CabalVerbosity)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser FirstFalse
pVerboseFlag