{-# LANGUAGE NoImplicitPrelude #-}
module Stack.Options.ExecParser
( execOptsParser
, execOptsExtraParser
) where
import Options.Applicative
( Parser, completer, help, idm, long, metavar, strArgument
, strOption
)
import Options.Applicative.Builder.Extra ( boolFlags, dirCompleter )
import Options.Applicative.Args ( argsOption )
import Stack.Exec
( ExecOpts (..), ExecOptsExtra (..), SpecialExecCmd (..) )
import Stack.Options.Completion ( projectExeCompleter )
import Stack.Prelude
import Stack.Types.EnvSettings ( EnvSettings (..) )
execOptsParser :: Maybe SpecialExecCmd -> Parser ExecOpts
execOptsParser :: Maybe SpecialExecCmd -> Parser ExecOpts
execOptsParser Maybe SpecialExecCmd
mcmd = SpecialExecCmd -> [FilePath] -> ExecOptsExtra -> ExecOpts
ExecOpts
(SpecialExecCmd -> [FilePath] -> ExecOptsExtra -> ExecOpts)
-> Parser SpecialExecCmd
-> Parser ([FilePath] -> ExecOptsExtra -> ExecOpts)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser SpecialExecCmd
-> (SpecialExecCmd -> Parser SpecialExecCmd)
-> Maybe SpecialExecCmd
-> Parser SpecialExecCmd
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Parser SpecialExecCmd
eoCmdParser SpecialExecCmd -> Parser SpecialExecCmd
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe SpecialExecCmd
mcmd
Parser ([FilePath] -> ExecOptsExtra -> ExecOpts)
-> Parser [FilePath] -> Parser (ExecOptsExtra -> ExecOpts)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser [FilePath]
eoArgsParser
Parser (ExecOptsExtra -> ExecOpts)
-> Parser ExecOptsExtra -> Parser ExecOpts
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser ExecOptsExtra
execOptsExtraParser
where
eoCmdParser :: Parser SpecialExecCmd
eoCmdParser = FilePath -> SpecialExecCmd
ExecCmd
(FilePath -> SpecialExecCmd)
-> Parser FilePath -> Parser SpecialExecCmd
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Mod ArgumentFields FilePath -> Parser FilePath
forall s. IsString s => Mod ArgumentFields s -> Parser s
strArgument
( FilePath -> Mod ArgumentFields FilePath
forall (f :: * -> *) a. HasMetavar f => FilePath -> Mod f a
metavar FilePath
"COMMAND"
Mod ArgumentFields FilePath
-> Mod ArgumentFields FilePath -> Mod ArgumentFields FilePath
forall a. Semigroup a => a -> a -> a
<> Completer -> Mod ArgumentFields FilePath
forall (f :: * -> *) a. HasCompleter f => Completer -> Mod f a
completer Completer
projectExeCompleter
)
eoArgsParser :: Parser [FilePath]
eoArgsParser = Parser FilePath -> Parser [FilePath]
forall a. Parser a -> Parser [a]
forall (f :: * -> *) a. Alternative f => f a -> f [a]
many (Mod ArgumentFields FilePath -> Parser FilePath
forall s. IsString s => Mod ArgumentFields s -> Parser s
strArgument (FilePath -> Mod ArgumentFields FilePath
forall (f :: * -> *) a. HasMetavar f => FilePath -> Mod f a
metavar FilePath
txt))
where
txt :: FilePath
txt = case Maybe SpecialExecCmd
mcmd of
Maybe SpecialExecCmd
Nothing -> FilePath
normalTxt
Just ExecCmd{} -> FilePath
normalTxt
Just SpecialExecCmd
ExecRun -> FilePath
"-- ARGUMENT(S) (e.g. stack run -- file.txt)"
Just SpecialExecCmd
ExecGhc -> FilePath
"-- ARGUMENT(S) (e.g. stack ghc -- X.hs -o x)"
Just SpecialExecCmd
ExecRunGhc -> FilePath
"-- ARGUMENT(S) (e.g. stack runghc -- X.hs)"
normalTxt :: FilePath
normalTxt = FilePath
"-- ARGUMENT(S) (e.g. stack exec ghc-pkg -- describe base)"
execOptsExtraParser :: Parser ExecOptsExtra
= EnvSettings
-> [FilePath] -> [FilePath] -> Maybe FilePath -> ExecOptsExtra
ExecOptsExtra
(EnvSettings
-> [FilePath] -> [FilePath] -> Maybe FilePath -> ExecOptsExtra)
-> Parser EnvSettings
-> Parser
([FilePath] -> [FilePath] -> Maybe FilePath -> ExecOptsExtra)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser EnvSettings
eoEnvSettingsParser
Parser
([FilePath] -> [FilePath] -> Maybe FilePath -> ExecOptsExtra)
-> Parser [FilePath]
-> Parser ([FilePath] -> Maybe FilePath -> ExecOptsExtra)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser [FilePath]
eoPackagesParser
Parser ([FilePath] -> Maybe FilePath -> ExecOptsExtra)
-> Parser [FilePath] -> Parser (Maybe FilePath -> ExecOptsExtra)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser [FilePath]
eoRtsOptionsParser
Parser (Maybe FilePath -> ExecOptsExtra)
-> Parser (Maybe FilePath) -> Parser ExecOptsExtra
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 FilePath)
eoCwdParser
where
eoEnvSettingsParser :: Parser EnvSettings
eoEnvSettingsParser :: Parser EnvSettings
eoEnvSettingsParser = Bool -> Bool -> Bool -> Bool -> Bool -> EnvSettings
EnvSettings Bool
True
(Bool -> Bool -> Bool -> Bool -> EnvSettings)
-> Parser Bool -> Parser (Bool -> Bool -> Bool -> EnvSettings)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Bool -> FilePath -> FilePath -> Mod FlagFields Bool -> Parser Bool
boolFlags Bool
True
FilePath
"ghc-package-path"
FilePath
"setting the GHC_PACKAGE_PATH variable for the subprocess."
Mod FlagFields Bool
forall m. Monoid m => m
idm
Parser (Bool -> Bool -> Bool -> EnvSettings)
-> Parser Bool -> Parser (Bool -> Bool -> EnvSettings)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Bool -> FilePath -> FilePath -> Mod FlagFields Bool -> Parser Bool
boolFlags Bool
True
FilePath
"stack-exe"
FilePath
"setting the STACK_EXE environment variable to the path for the \
\stack executable."
Mod FlagFields Bool
forall m. Monoid m => m
idm
Parser (Bool -> Bool -> EnvSettings)
-> Parser Bool -> Parser (Bool -> EnvSettings)
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 Bool
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Bool
False
Parser (Bool -> EnvSettings) -> Parser Bool -> Parser EnvSettings
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 Bool
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Bool
True
eoPackagesParser :: Parser [String]
eoPackagesParser :: Parser [FilePath]
eoPackagesParser = Parser FilePath -> Parser [FilePath]
forall a. Parser a -> Parser [a]
forall (f :: * -> *) a. Alternative f => f a -> f [a]
many (Mod OptionFields FilePath -> Parser FilePath
forall s. IsString s => Mod OptionFields s -> Parser s
strOption
( FilePath -> Mod OptionFields FilePath
forall (f :: * -> *) a. HasName f => FilePath -> Mod f a
long FilePath
"package"
Mod OptionFields FilePath
-> Mod OptionFields FilePath -> Mod OptionFields FilePath
forall a. Semigroup a => a -> a -> a
<> FilePath -> Mod OptionFields FilePath
forall (f :: * -> *) a. HasMetavar f => FilePath -> Mod f a
metavar FilePath
"PACKAGE"
Mod OptionFields FilePath
-> Mod OptionFields FilePath -> Mod OptionFields FilePath
forall a. Semigroup a => a -> a -> a
<> FilePath -> Mod OptionFields FilePath
forall (f :: * -> *) a. FilePath -> Mod f a
help FilePath
"Add a package (can be specified multiple times)."
))
eoRtsOptionsParser :: Parser [String]
eoRtsOptionsParser :: Parser [FilePath]
eoRtsOptionsParser = [[FilePath]] -> [FilePath]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([[FilePath]] -> [FilePath])
-> Parser [[FilePath]] -> Parser [FilePath]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser [FilePath] -> Parser [[FilePath]]
forall a. Parser a -> Parser [a]
forall (f :: * -> *) a. Alternative f => f a -> f [a]
many (Mod OptionFields [FilePath] -> Parser [FilePath]
argsOption
( FilePath -> Mod OptionFields [FilePath]
forall (f :: * -> *) a. HasName f => FilePath -> Mod f a
long FilePath
"rts-options"
Mod OptionFields [FilePath]
-> Mod OptionFields [FilePath] -> Mod OptionFields [FilePath]
forall a. Semigroup a => a -> a -> a
<> FilePath -> Mod OptionFields [FilePath]
forall (f :: * -> *) a. FilePath -> Mod f a
help FilePath
"Explicit RTS options to pass to application."
Mod OptionFields [FilePath]
-> Mod OptionFields [FilePath] -> Mod OptionFields [FilePath]
forall a. Semigroup a => a -> a -> a
<> FilePath -> Mod OptionFields [FilePath]
forall (f :: * -> *) a. HasMetavar f => FilePath -> Mod f a
metavar FilePath
"RTSFLAG"
))
eoCwdParser :: Parser (Maybe FilePath)
eoCwdParser :: Parser (Maybe FilePath)
eoCwdParser = Parser FilePath -> Parser (Maybe FilePath)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (Mod OptionFields FilePath -> Parser FilePath
forall s. IsString s => Mod OptionFields s -> Parser s
strOption
( FilePath -> Mod OptionFields FilePath
forall (f :: * -> *) a. HasName f => FilePath -> Mod f a
long FilePath
"cwd"
Mod OptionFields FilePath
-> Mod OptionFields FilePath -> Mod OptionFields FilePath
forall a. Semigroup a => a -> a -> a
<> FilePath -> Mod OptionFields FilePath
forall (f :: * -> *) a. FilePath -> Mod f a
help FilePath
"Sets the working directory before executing."
Mod OptionFields FilePath
-> Mod OptionFields FilePath -> Mod OptionFields FilePath
forall a. Semigroup a => a -> a -> a
<> FilePath -> Mod OptionFields FilePath
forall (f :: * -> *) a. HasMetavar f => FilePath -> Mod f a
metavar FilePath
"DIR"
Mod OptionFields FilePath
-> Mod OptionFields FilePath -> Mod OptionFields FilePath
forall a. Semigroup a => a -> a -> a
<> Completer -> Mod OptionFields FilePath
forall (f :: * -> *) a. HasCompleter f => Completer -> Mod f a
completer Completer
dirCompleter
))